Link here

Forth v6 Function Glossary (!-A-D)


This glossary provides detailed definitions for the general purpose words (Forth functions) available in the v6 Forth kernel. Separate glossaries define the assembler and C debugging words available. A separate page lists all the Functions that Disable Interrupts.

For help in understanding the notation used in the following function definitions, consult the description of stack symbols, abbreviations and naming conventions.

Software development in Forth uses the Codeblocks-based Mosaic IDE Plus Integrated Development Environment; this is the same IDE used for software development in C. While Forth programmers will not use the IDE's GNU C (GCC) compiler, the IDE provides a full-featured text editor and customized terminal for rapid Forth code downloads and interactive Forth debugging sessions with the 9S12 (HCS12) processor on the controller board.

This glossary is split into three web pages, for words beginning with the following characters (in ASCII alphabetical) order:

Page Starting character
This page ! " # $ ' ( * + , - . / 0 1 2 3 4 8 : ; < = > ? @ A B C D
Page E-O E F G H I J K L M N O
Page P-Z-} P Q R S T U V W X Y Z [ \ ] | }

Listed functions are alphabetized in the following ASCII order. Forth words are not case sensitive. You can click on the following characters to be taken directly to the glossary entries starting with that character.
!  "  #  $  '  (  *  +  ,  -  .  /  0  1  2  3  4  8  :  ;  <  =  >  ?  @  A  B  C  D 

Page E-O

Page P-Z-}



 
!

! ( w\xaddr -- )

Stores a 16-bit number w at the extended address xaddr.  The high order byte is stored at xaddr and the low order byte at xaddr+1. Note that in paged memory, the address immediately following 0xBFFF is address 0x8000 on the following page.
Pronunciation: store

 
"

" ( -- x$addr )

Compile Time: ( <text> – )

Parses the <text> string in the input stream delimited by a terminating " character.  If compiling, emplaces the text in the dictionary as a counted string along with a call to a routine that pushes x$addr to the stack at runtime.  If executing, emplaces the string in the dictionary at HERE and leave x$addr (the address of the string) on the stack.
Pronunciation: quote
Attributes: I

 
#

# ( ud1 -- ud2 )

Divides unsigned double number ud1 by the value in BASE to compute the unsigned double quotient ud2 and the integer remainder n.  Converts n to an appropriate single ASCII digit character in the current number base and inserts it into the pictured numeric output string below PAD. # is used between <# and #> commands to create a pictured numeric string.
Pronunciation: number-sign
Attributes: S

 
#>

#> ( d -- xaddr\cnt )

Drops d and leaves the xaddr under the count of the pictured numeric output string resulting from the number conversion process initiated by <#. The character count is also stored in location xaddr - 1, so xaddr - 1 can be used as an x$addr.  Used to terminate a pictured numeric output sequence which was opened by <# . The pictured numeric output string is located below PAD.
Pronunciation: num-greater-than

 
#ENDSAVETO

#ENDSAVETO ( -- )

This is a directive that is printed by the library management routines such as BUILD.SEGMENTS and COMPOSE.C.HEADERS.  The directive is trapped by the terminal program running on the PC to end a file-save operation that was started by the #SAVETO directive (see its glossary entry).  This word and all remaining text on the same line is ignored by the Forth interpreter, so the interpreter can accept a download that contains the #ENDSAVETO command.
Pronunciation: num-end-save-to

 
#FIND

#FIND ( <name> -- [ segment.xhandle\xcfa\xnfa\segment\flag ] or [ 0 ] )

Executes BL WORD to parse the next space-delimited word from the input stream, and then searches the dictionary for a match of the parsed word, returning the information needed to execute or compile the word.

If a definition that includes the LOCALS{ statement is compiling, #FIND first searches the VLOCALS vocabulary for a match to <name>. If no match is found, #FIND searches the CONTEXT vocabulary.  Then, if the word is not found and if the CONTEXT and CURRENT vocabularies are different, it searches the CURRENT vocabulary.  If the word is not found in the dictionary, it leaves a 0 on the stack.  If the word is found, #FIND leaves the word's extended segment handle address, extended code field address, extended name field address, segment index and a flag on the stack.

If <name> is in the kernel or the currently compiling segment (as indicated by THIS.SEGMENT), then the returned segment.xhandle is 0\0. For non-kernel non-local segments, the segment.xhandle is obtained by searching the current segment’s required.segment table for a match to the segment.index stored in <name>’s header, and returning the xaddress of the matching table entry. #FIND aborts if a matching segment entry is not found in required.segment table.  Only the lower 6 bits of the segment index are matched.  The 2 msbits of the byte-sized entry in the required segment table byte encode additional information: bit6 is set if the target xcfa is in a non-local library (as opposed to an application segment), and bit7 is set if a page-relative call is required (e.g., if <name> is in the currently compiling segment).  These 2 msbits from the matching required.segment table entry are transferred to the ms.page.byte of the xcfa for use by the compiler.  The returned xcfa is the absolute code field address.  For kernel routines, this is the xcfa stored in the header of <name>, while for nonkernel routines, the returned xcfa is calculated as:

{xcfa.offset from header} + {segment.xbase from eeprom segment table}

The returned segment.index is copied from the header, and bit6 of the segment index is set if <name> is in a library segment.  The returned flag at the top of the stack has an msbyte = 0xFF (to guarantee a nonzero flag) and the lsbyte equals the header.type field from the header of <name>.  An error occurs if the input stream is exhausted while WORD executes.  A COLD restart will occur if more than 255 page changes are made during the search through either vocabulary.  This prevents the interpreter from going on an infinite search through a corrupted dictionary.  A COLD restart will also occur if POCKET is not in common memory.
Pronunciation: num-find

 
#S

#S ( ud1 -- ud2 | ud2 = 0\0 )

Converts all digits of the unsigned double number ud1 by iteratively dividing quotients by BASE and inserting the ASCII symbol for the remainder into the pictured numeric output starting at the left of the string and working towards the right.  ud2 is a double number zero.  If ud1 equals zero, a single 0 is added to the pictured output buffer below PAD. #S is used between <# and #> commands to create pictured numeric output.
Pronunciation: number-sign-s
Attributes: S

 
#SAVETO

#SAVETO ( -- )

This is a directive that is printed by the library management routines such as BUILD.SEGMENTS and COMPOSE.C.HEADERS.  The directive is trapped by the terminal program running on the PC to begin a file-save operation to the quote-delimited filename that follows #SAVETO.  This word and all remaining text on the same line is ignored by the Forth interpreter, so the interpreter can accept a download that contains the #SAVETO command.
Pronunciation: num-save-to

 
#TIB

#TIB ( -- xaddr )

User variable that contains the number of characters in the terminal input buffer (TIB).

See also QUERY
Pronunciation: number-t-i-b
Attributes: U

 
#USER.BYTES

#USER.BYTES ( -- n )

n is the number of USER bytes already allocated by QED-Forth.  This quantity is useful if the programmer wants to define more user variables.  The first additional user variable would be defined as #USER.BYTES USER <name>

 
$>F

$>F ( x$addr -- [r\-1] or [0] )

Converts the counted ascii string at x$addr representing an integer, double integer, or floating point number into a binary floating point representation under a true flag.  Otherwise returns a false flag.  See FNUMBER for a numeric string input function that does not accept integer or double integer inputs.

Note: The number base at the time of execution should be DECIMAL to avoid mis-converting hexadecimal numbers that contain the letter E or e, as these are interpreted by $>F as the exponent identifier.
Pronunciation: string-to-f
Attributes: S

 
$COMPARE

$COMPARE ( xaddr1\xaddr2\+n1 -- +n2 )

Finds the number of common characters +n2 in the strings whose first characters are stored at xaddr1 and xaddr2, respectively. +n1 specifies the maximum number of characters to be compared.  Comparison starts at the specified addresses and terminates as soon as an unmatched pair of characters is encountered. +n2 = 0 if there are no common characters found (i.e., if the character at xaddr1 is different from that at xaddr2) or if +n1 is negative.  The strings may cross page boundaries.
Pronunciation: string-compare

 
$MOVE

$MOVE ( x$addr\xaddr\n -- )

Moves the contents of the counted string specified by x$addr to the destination starting at xaddr.  Does not move the count byte.  The number of characters moved is clamped to a maximum of n bytes.
Pronunciation: string-move

 
${

${ ( -- x$addr )

Compile Time: ( < text }$> – )

Parses a long string from one or more lines of the input stream, terminating when either the maximum number of characters (=65,533) have been parsed, or the }$ 2-byte delimiter is encountered.  If executing, emplaces the long-string in the dictionary at HERE and leaves x$addr (the address of the string) on the stack; the stored string may cross page boundaries.  If compiling, emplaces the text in the dictionary as a counted long-string along with a call to a routine that pushes x$addr to the stack at runtime; in this case, the stored string may not cross a page boundary because a definition cannot cross the page boundary.  The string is stored in memory as a 2-byte count followed by the parsed text followed by a null (not included in the count).  DP is incremented by the total number of bytes in the string (= the parsed count + 3 bytes).  This routine calls LPARSE to perform the parsing as:

DP 0xFFFD 0x0D0A  0x7D24  LPARSE

where 0xFFFD is the maximum number of allowed characters (decimal 65533), DP indicates that the string resides in the dictionary area, 0x0D0A is the ascii CRLF end-of-line sequence, and 0x7D24 is the ascii representation of the terminating }$ delimiter.  Leading spaces are not skipped.  Each time the input line is parsed without encountering the specified delimiter, this routine emplaces the specified 2-byte EOL (end-of-line) sequence = 0x0D0A (CRLF) into the string and executes QUERY to acquire the next input line.  The input stream is the terminal input buffer TIB, and the contents of >IN specify the offset from the start of the input stream to the first character to be parsed.  Parsing starts after the required space that follows ${. This routine leaves >IN pointing 1 byte past the terminating delimiter.  NOTE: If parsing has been terminated by reaching the specified max#chars = 65533, then the remainder of the input line on which the termination occurred will not be interpreted by the compiler; these remaining characters are effectively removed from the input stream.  Note that, for strings containing 255 characters or fewer, you can simply add 1 to the output x$addr using 1XN+ if you want to treat the string as a standard byte-counted string.  To unpack a long string, use LCOUNT.

See also and LPARSE
Pronunciation: string-start
Attributes: I, M

 
'

' ( -- [xpfa] or [0\0] )

Compile Time: ( <name> – )

Removes <name> from the input stream and returns <name>'s extended parameter field address.  Returns 0\0 if <name> has no parameter field (see ?HAS.PFA).  If in execution mode, leaves the xpfa on the stack.  If in compilation mode, compiles the xpfa as a 2-cell literal in the current definition; the xpfa is pushed to the stack when the definition later executes.  An error occurs if no <name> is given or if <name> cannot be found in the dictionary. In compilation mode, an error occurs if <name> is in a different library or application segment than the segment that ' is located in; the error message is Can't compile deferred lib-to-lib call. To resolve this condition, simply define in the current library or application segment a synonym for <name>, and use the synonym as the argument of '.
Pronunciation: tick
Attributes: I

 
(

( ( -- )

Compile Time: ( <text)> – )

Ignores all further input until ) or the end of the input stream is encountered.  Used to enclose comments.  No error occurs if the end of the input stream (that is, the end of the line) is encountered; the following line is interpreted normally.

See also \
Pronunciation: paren
Attributes: I

 
(!)

(!) ( w\addr -- )

Stores a 16-bit number at addr on the current page or in common memory.  The high order byte is stored at addr and the low order byte at addr+1.
Pronunciation: paren-store

 
(#FIND)

(#FIND) ( $addr -- [ segment.xhandle\xcfa\xnfa\segment\flag ] or [ 0 ] )

Searches the dictionary for a match of the counted string at $addr in the common memory, returning the information needed to execute or compile the word.  If a definition that includes the LOCALS{ statement is compiling, (#FIND) first searches the VLOCALS vocabulary for a match to $addr.  If no match is found, (#FIND) searches the CONTEXT vocabulary.  Then, if the word is not found and if the CONTEXT and CURRENT vocabularies are different, it searches the CURRENT vocabulary.  If the word is not found in the dictionary, it leaves a 0 on the stack.  If the word is found, (#FIND) leaves the word's extended segment handle address, extended code field address, extended name field address, segment index and a flag on the stack.

If the word is in the kernel or the currently compiling segment (as indicated by THIS.SEGMENT), then the returned segment.xhandle is 0\0.  For non-kernel non-local segments, the segment.xhandle is obtained by searching the current segment’s required.segment table for a match to the segment.index stored in the found word’s header, and returning the xaddress of the matching table entry.

(#FIND) aborts if a matching segment entry is not found in required.segment table.  Only the lower 6 bits of the segment index are matched.  The 2 msbits of the byte-sized entry in the required segment table byte encode additional information: bit6 is set if the target xcfa is in a non-local library (as opposed to an application segment), and bit7 is set if a page-relative call is required (e.g., if the found word is in the currently compiling segment).  These 2 msbits from the matching required.segment table entry are transferred to the ms.page.byte of the xcfa for use by the compiler.  The returned xcfa is the absolute code field address.  For kernel routines, this is the xcfa stored in the header of the found word, while for nonkernel routines, the returned xcfa is calculated as:

{xcfa.offset from header} + {segment.xbase from eeprom segment table}

The returned segment.index is copied from the header, and bit6 of the segment index is set if the found word is in a library segment.  The returned flag at the top of the stack has an msbyte = 0xFF (to guarantee a nonzero flag) and the lsbyte equals the header.type field from the header of the found word.  A COLD restart will occur if more than 255 page changes are made during the search through either vocabulary.  This prevents the interpreter from going on an infinite search through a corrupted dictionary.  A COLD restart will also occur if $addr is not in common memory.
Pronunciation: paren-num-find

 
((ERROR))

((ERROR)) ( [...]\error.id -- )

The default routine called by (ERROR) if a system error is detected and the CUSTOM.ERROR flag is false.  Prints a descriptive error message, if possible printing the name of the routine that detected the error and any arrays or matrices involved in producing the error condition.  Unlike (ERROR), ((ERROR)) does not execute ABORT.  In multitasking applications, the availability of ((ERROR)) allows a task with access to the serial line to print intelligible system error messages without executing ABORT.  Since ABORT invokes the user-installed autostart routine in a turnkeyed system, the ability to handle errors without invoking ABORT increases the programmer's options.  For example, the following user-defined error handler can be installed in UERROR to allow a task to print standard error messages without calling ABORT or invoking an installed autostart routine:

: MY.ERROR.HANDLER   ( -- )
   ((ERROR))           \ prints proper error messages
   SP!  RP!            \ initialize data & return stacks
   FORTH DEFINITIONS   \ initialize vocabulary
   QUIT                \ enter interpreter
   ;
CFA.FOR MY.ERROR.HANDLER UERROR X!
CUSTOM.ERROR ON        \ install task's error handler

See (ERROR), CUSTOM.ERROR, UERROR, and ABORT
Pronunciation: paren-paren-error

 
(+!)

(+!) ( w\addr -- )

Adds w to the 16-bit value stored at addr on the current page or in common memory and stores the result at addr.
Pronunciation: paren-plus-store

 
(+C!)

(+C!) ( byte\addr -- )

Adds byte to the 8-bit value at addr on the current page or in common memory and stores the result at addr.
Pronunciation: paren-plus-c-store

 
(2!)

(2!) ( w1\w2\addr -- | [addr] gets w2, [addr+2] gets w1 )

Stores two 16-bit integers at addr on the current page or in common memory.  w2 is stored at addr and w1 is stored at addr+2. Can also be used to store a double number at addr.
Pronunciation: paren-two-store

 
(2@)

(2@) ( addr -- w1\w2 )

Fetches two 16-bit integers from addr and addr+2 on the current page or in common memory.  w2 is taken from addr and the w1 is from addr+2. Can also be used to fetch a double number from addr.
Pronunciation: paren-two-fetch

 
(@)

(@) ( addr -- w )

Fetches a 16-bit number from addr on the current page or in common memory.  The high order byte is taken from addr and the low order byte from addr+1.
Pronunciation: paren-fetch

 
(ABORT)

(ABORT) ( [...] -- )
Return stack: ( R: [...] -- )

The default abort routine called by ABORT if the CUSTOM.ABORT flag is false.  Clears the data and return stacks, sets the page to the default page (0), and executes FORTH DEFINITIONS to set CONTEXT and CURRENT equal to FORTH.  If an autostart vector has been installed (see AUTOSTART: and IS.AUTOSTART), (ABORT) executes the specified routine; otherwise it executes QUIT which sets the compilation mode and enters the interpreter.  If R0 and S0 aren't in common RAM, a COLD restart is initiated.
Pronunciation: paren-abort

 
(BENCHMARK:)

(BENCHMARK:) ( <name> -- u1\ud | u1=#msec, ud=#sec )

Removes the next <name> from the input stream and measures and places on the stack the execution time and operations count of <name>. Use as:

(BENCHMARK:) <name>

The multitasker's timeslicer clock must be running for the execution time to be measured; use START.TIMESLICER to start it before calling (BENCHMARK:).  Any stack arguments needed by <name> should be placed on the stack before (BENCHMARK:) is invoked.  If <name> leaves any items on the stack, they will be below the stack items left by (BENCHMARK:).  Net execution time of <name> is represented by ud seconds + u1 msec.  The resolution of the measurement equals the timeslice period which can be set using the command MSEC.TIMESLICE.PERIOD; the default is 1 msec.  This word is a subsidiary to BENCHMARK: which prints the results instead of leaving them on the stack.

NOTE: If a library is currently compiling, then <name> cannot be in a different library.
Pronunciation: paren-benchmark
Attributes: S

 
(C!)

(C!) ( byte\addr -- )

Stores the byte at addr on the current page or in common memory.
Pronunciation: paren-c-store

 
(C@)

(C@) ( addr -- byte )

Fetches the byte stored at addr on the current page or in common memory.
Pronunciation: paren-c-fetch

 
(CMOVE)

(CMOVE) ( addr1\addr2\u -- | addr1=src, addr2=dest, u = byte count )

If u is greater than 0, u consecutive bytes starting at addr1 are copied to the destination addresses starting at addr2 on the current page or in common memory.  Does not change the page.  Speed is approximately 2 microseconds overhead plus 0.2 microseconds per byte.  If the source and destination regions overlap and addr1 < addr2, (CMOVE) starts at high memory and moves toward low memory to avoid propagation of the moved contents. (CMOVE) always moves the contents in such a way as to avoid memory propagation.
Pronunciation: paren-c-move

 
(COMPILE.CALL)

(COMPILE.CALL) ( cfa -- )

Compiles a call to the specified cfa.  Compiles a JSR (jump to subroutine) opcode followed by cfa into the definitions area at HERE and increments DP by 3. No page change is compiled.
Pronunciation: paren-compile-call

 
(COMPILE.REL.CALL)

(COMPILE.REL.CALL) ( cfa -- )

Compiles a call to the specified cfa.  Compiles a relative JSR,PCR (program-counter relative jump to subroutine) 2-byte opcode followed by a 2-byte offset that, when executed, calls the specified cfa.  The DP is incremented by 4 bytes.  No page change is compiled.
Pronunciation: paren-compile-rel-call

 
(CREATE)

(CREATE) ( $addr -- )

Similar to CREATE which creates a header for <name>. The difference is that CREATE removes <name> from the input stream by executing BL WORD, while (CREATE) accepts <name> as a counted string at $addr in common memory.

Converts the counted string at $addr to upper case letters and searches the dictionary via (FIND) to check for uniqueness.  Issues a warning if <name> is not unique.  If the system variable NP.NOBUMP is in its default false state, checks to see if the names pointer NP is within 88 bytes of top of the names page, and if so bumps NP to the start of the next page, and aborts if the allotted names page region as indicated by the system variable LAST.NP.PAG has been exceeded.  Creates a new header for <name> starting at the address pointed to by NP, updates NP to point to the byte after <name>'s header, and initializes the fields in the header.  This routine links the header to LATEST in the CURRENT vocabulary via a standard (chronological) link and, if <name> is in the VFORTH vocabulary, the hash link is set and the relevant hash table entry is updated.  The number of characters saved in the header is the lesser of the value in WIDTH or the actual number of characters in <name>. If locals.are.compiling or C.CALLABLE is true, or if a library is compiling and PRIVATE is false, then all characters are saved in the header.  This ensures the uniqueness of local variables, C-callable functions, and published library functions.

This routine sets the size of the header to the standard size if C.CALLABLE is false, or to the extended size if C.CALLABLE is true.  Certain defining words such as XCREATE, X:, and XCODE set the system variable C.CALLABLE true before calling CREATE) to ensure that a C-callable extended header is formed.  Uses the contents of the system variable THIS.SEGMENT and the user variable WIDTH to initialize the corresponding header fields.  Copies the contents of the system variable FUNCTION.TYPE to the function.type field in the header, then zeros the FUNCTION.TYPE system variable.  Sets the bitmasks in the header.type field subject to the following conditions: if THIS.SEGMENT = 0, sets bit 2 (in.kernel.mask); if C.CALLABLE is true, sets bit 3 (c.callable.mask); if PRIVATE is true, sets bit 4 (private.mask).  Other bits in the header field encode whether the header is immediate, has a pfa, or is a segment header; these bits are set by other functions.  The cfa.offset and cfa.page.offset fields are set according to the equation

[cfa(page) - segment.base(page)]

where segment.base(page) is calculated by looking in the eeprom segment table entry pointed to by the system variable THIS.SEGMENT.  Finally, the contents of the vocabulary pointed to by CURRENT is set equal to the newly created nfa, where the nfa (name field address) is the address of the name count in the header.  An abort error occurs if the header cannot be stored (e.g.  if NP does not point to RAM).  If WIDTH is less than or equal to 1, (CREATE) resets WIDTH to 2.
Pronunciation: paren-create
Attributes: D

 
(EE!)

(EE!) ( w\addr -- | addr is an EEPROM address )

Stores w at the specified addr in EEPROM.  Based on the prior contents at the one or two 4-byte aligned EEPROM cells corresponding to the specified addr, this routine determines if the contents will be changed by this operation.  If not, then no programming action is performed, and this helps lengthen the lifetime of the EEPROM.  Requires up to 30 msec per programmed 4-byte-aligned EEPROM cell.  Disables interrupts during the programming of each EEPROM cell.  Caution: the prolonged disabling of interrupts by (EE!) can adversely affect real-time servicing of interrupts.
Pronunciation: paren-e-e-store

 
(EE2!)

(EE2!) ( w1\w2\addr -- | [addr] gets w2, [addr+2] gets w1 )

Stores w1 and w2 at the specified addr in EEPROM.  w2 is stored at addr and w1 is stored at addr+2. Can also be used to store a double number at addr.  Based on the prior contents at the one or two 4-byte aligned EEPROM cells corresponding to the specified addr, this routine determines if the contents will be changed by this operation.  If not, then no programming action is performed, and this helps lengthen the lifetime of the EEPROM.  Requires up to 30 msec per programmed 4-byte-aligned EEPROM cell.  Disables interrupts during the programming of each EEPROM cell.  Caution: the prolonged disabling of interrupts by (EE2!) can adversely affect real-time servicing of interrupts.
Pronunciation: paren-e-e-two-store

 
(EEC!)

(EEC!) ( byte\addr -- | addr is an EEPROM address )

Stores byte at the specified addr in EEPROM.  Based on the prior contents at the 4-byte aligned EEPROM cell corresponding to the specified addr, this routine determines if the contents will be changed by this operation.  If not, then no programming action is performed, and this helps lengthen the lifetime of the EEPROM.  Requires up to 30 msec per programmed 4-byte-aligned EEPROM cell.  Disables interrupts during the programming of each EEPROM cell.  Caution: the prolonged disabling of interrupts by (EEC!) can adversely affect real-time servicing of interrupts.
Pronunciation: paren-e-e-c-store

 
(EEF!)

(EEF!) ( r\addr -- | addr is an EEPROM address )

Stores r at the specified addr in EEPROM.  Based on the prior contents at the one or two 4-byte aligned EEPROM cells corresponding to the specified addr, this routine determines if the contents will be changed by this operation.  If not, then no programming action is performed, and this helps lengthen the lifetime of the EEPROM.  Requires up to 30 msec per programmed 4-byte-aligned EEPROM cell.  Disables interrupts during the programming of each EEPROM cell.  Caution: the prolonged disabling of interrupts by (EEF!) can adversely affect real-time servicing of interrupts.
Pronunciation: paren-e-e-f-store

 
(EEX!)

(EEX!) ( xaddr\addr -- | addr is an EEPROM address )

Stores xaddr at the specified addr in EEPROM.  Based on the prior contents at the one or two 4-byte aligned EEPROM cells corresponding to the specified addr, this routine determines if the contents will be changed by this operation.  If not, then no programming action is performed, and this helps lengthen the lifetime of the EEPROM.  Requires up to 30 msec per programmed 4-byte-aligned EEPROM cell.  Disables interrupts during the programming of each EEPROM cell.  Caution: the prolonged disabling of interrupts by (EEX!) can adversely affect real-time servicing of interrupts.
Pronunciation: paren-e-e-x-store

 
(ERROR)

(ERROR) ( [...] -- )
Return stack: ( R: [...] -- )

The default routine called if a system error is detected and the CUSTOM.ERROR flag is false.  Prints a descriptive error message, if possible printing the name of the routine that detected the error and any arrays or matrices involved in producing the error condition.  After printing the message, executes ABORT.

See also ((ERROR)), CUSTOM.ERROR, UERROR, and ABORT
Pronunciation: paren-error

 
(EXECUTE)

(EXECUTE) ( cfa -- )

Executes (calls) the routine whose executable machine instructions begin at the specified code field address cfa on the current page or in common memory.
Pronunciation: paren-execute

 
(F!)

(F!) ( r\addr -- )

Stores a floating point number at addr on the current page or in common memory.
Pronunciation: paren-f-store

 
(F@)

(F@) ( addr -- r )

Fetches a floating point number from addr on the current page or in common memory.
Pronunciation: paren-f-fetch

 
(FIND)

(FIND) ( $addr -- [ xcfa\flag ] or [ 0 ] )

Searches the dictionary for a match of the counted string at $addr in the common memory.  Calls (#FIND); see its glossary entry for implementation details.  If a definition that includes the LOCALS{ statement is compiling, (FIND) first searches the VLOCALS vocabulary for a match to $addr.  If no match is found, (FIND) searches the CONTEXT vocabulary.  Then, if the word is not found and if the CONTEXT and CURRENT vocabularies are different, it searches the CURRENT vocabulary.  If the word is not found in the dictionary, it leaves a 0 on the stack.  If the word is found, (FIND) leaves the word's extended code field address and a flag on the stack.  For non-kernel non-local segments, (FIND) aborts if a matching segment entry is not found in required.segment table.  The 2 msbits of the returned xcfa encode additional information: bit6 is set if the target xcfa is in a non-local library (as opposed to an application segment), and bit7 is set if a page-relative call is required (e.g., if the found word is in the currently compiling segment).  The returned xcfa is the absolute code field address.  For kernel routines, this is the xcfa stored in the header of the found word, while for nonkernel routines, the returned xcfa is calculated as:

{xcfa.offset from header} + {segment.xbase from eeprom segment table}

The returned flag at the top of the stack has an msbyte = 0xFF (to guarantee a nonzero flag) and the lsbyte equals the header.type field from the header of the found word.  A COLD restart will occur if more than 255 page changes are made during the search through either vocabulary.  This prevents the interpreter from going on an infinite search through a corrupted dictionary.  A COLD restart will also occur if $addr is not in common memory.
Pronunciation: paren-find

 
(FIND.LIB2LIB)

(FIND.LIB2LIB) ( $addr -- [ segment.xhandle\xcfa.offset&segment.index\flag ] or [ 0 ] )

This primitive searches the dictionary for a match of the counted string at $addr in the common memory, returning the information needed to compile a handle-relative call to the found word if the word is defined in a different library than the library that is now compiling.  If a definition that includes the LOCALS{ statement is compiling, (FIND.LIB2LIB) first searches the VLOCALS vocabulary for a match to $addr.  If no match is found, it searches the CONTEXT vocabulary.  Then, if the word is not found and if the CONTEXT and CURRENT vocabularies are different, it searches the CURRENT vocabulary.  If the word is not found in the dictionary, it leaves a 0 on the stack.  If the word is found, (FIND.LIB2LIB) leaves the word's segment.xhandle under its code field address offset under its code page offset (in the least significant byte) augmented by the segment index (in the most significant byte) under a flag on the stack.  If the word is in the kernel or the currently compiling segment (as indicated by THIS.SEGMENT), then the returned segment.xhandle is 0\0. For non-kernel non-local segments, the segment.xhandle is obtained by searching the current segment’s required.segment table for a match to the segment.index stored in the found word’s header, and returning the xaddress of the matching table entry.  This routine aborts if a matching segment entry is not found in required.segment table.  The code address- and page-offsets and the segment index are fetched directly from the found word’s header.  Note that the returned code field address parameters are offsets that must be added to the segment xbase.addr which is stored in the eeprom segment table indexed by the returned segment index.  The returned flag at the top of the stack has an msbyte = 0xFF (to guarantee a nonzero flag) and the lsbyte equals the header.type field from the header of the found word.  A COLD restart will occur if more than 255 page changes are made during the search through either vocabulary.  This prevents the interpreter from going on an infinite search through a corrupted dictionary.  A COLD restart will also occur if $addr is not in common memory.
Pronunciation: paren-find-lib-to-lib

 
(FIND.RELATIVE)

(FIND.RELATIVE) ( $addr -- [ xcfa.offset&segment.index\flag ] or [ 0 ] )

This primitive searches the dictionary for a match of the counted string at $addr in the common memory, returning the information needed to compile a relative call to the found word.  This function performs the same actions as (FIND.LIB2LIB), with the simple difference that this function does not return the segment.xhandle.

Also See the glossary entry for (FIND.LIB2LIB)
Pronunciation: paren-find-relative

 
(HERE)

(HERE) ( -- addr )

Places on the stack the addr of the next available location in the definitions area.  Equivalent to DP 2XN+ @
Pronunciation: paren-here
Attributes: U

 
(MOVE)

(MOVE) ( addr1\addr2\u -- | addr1=src, addr2=dest, u = count )

If u is greater than 0, u consecutive 16-bit numbers (i.e., 2*u consecutive bytes) starting at addr1 are copied to the destination addresses starting at addr2 on the current page or in common memory.  Does not change the page.  Execution time is 2 microseconds overhead plus 0.4 microseconds per 2-byte cell.  If the source and destination regions overlap and addr1 < addr2, (MOVE) starts at high memory and moves toward low memory to avoid propagation of the moved contents. (MOVE) always moves the contents in such a way as to avoid memory propagation.
Pronunciation: paren-move

 
(PAGE.LATCH)

(PAGE.LATCH) ( -- addr )

Returns the address of the page latch (the processor’s PPAGE register at address 0x0030) whose byte-contents indicate the current page.  See THIS.PAGE.  Be careful when explicitly changing the contents of the page latch.  Note that the word C! cannot be used to alter the contents of the page latch because C! saves and restores the page.  Rather, the page-less store operator (C!) must be used.
Pronunciation: paren-page-latch

 
(RP)

(RP) ( -- addr )

Places on the stack the address of the most significant byte of the top item on the return stack.
Pronunciation: paren-r-p
Attributes: U

 
(SP)

(SP) ( -- addr )

Places on the stack the address of the most significant byte of the top cell of the data stack just before (SP) is executed.
Pronunciation: paren-s-p
Attributes: U

 
(STATUS)

(STATUS) ( -- addr | addr is also the base addr of the user area )

Returns the address but not the page of the STATUS user variable which is also the task identification address at the base of the task's user area.  Because STATUS must be in common memory, a 16-bit address is sufficient to specify its location.  Using (STATUS) instead of STATUS leads to faster code because page-less memory operators execute more rapidly than operators that take full extended addresses.

See also STATUS
Pronunciation: paren-status
Attributes: U

 
(X!)

(X!) ( xaddr\addr -- )

Stores a 4-byte extended address xaddr at addr on the current page or in common memory.
Pronunciation: paren-x-store

 
(X@)

(X@) ( addr -- xaddr )

Fetches a 4-byte extended address from addr on the current page or from common memory.
Pronunciation: paren-x-fetch

 
*

* ( n1\n2 -- n3 )

Multiplies n1 by n2 giving n3 which is the least significant cell of the product.
Pronunciation: star

 
*/

*/ ( n1\n2\n3 -- n4 | do n1*n2/n3 ; n4 = quotient )

Multiplies n1 and n2 producing an intermediate double number result which is divided by n3 to yield the integer quotient n4. Uses signed math.  An unchecked error occurs on overflow.  Division by zero (n2=0) yields n4 = -1.
Pronunciation: star-slash

 
*/MOD

*/MOD ( n1\n2\n3 -- n4\n5 | do n1*n2/n3; n4 = remainder; n5 = quotient )

Multiplies n1 and n2 producing an intermediate double number result which is divided by n3 to yield remainder n4 and quotient n5. Uses signed math.  An unchecked error occurs on overflow.  Division by zero (n2=0) yields n4 = -1 and n5 = -1.

See also U*/MOD
Pronunciation: star-slash-mod

 
+

+ ( n1\n2 -- n3 )

Adds n1 to n2 and puts the sum n3 on the data stack.
Pronunciation: plus

 
+!

+! ( w\xaddr -- )

Adds w to the 16-bit value stored at xaddr and stores the result at xaddr.
Pronunciation: plus-store

 
+C!

+C! ( byte\xaddr -- )

Adds byte to the 8-bit value stored at xaddr and stores the result at xaddr.
Pronunciation: plus-c-store

 
+CURRENT.HEAP

+CURRENT.HEAP ( xpfa -- xpfa+u )

Adds the offset u to the extended parameter field address xpfa. +CURRENT.HEAP is defined as a member of the structure HEAP.STRUCTURE.PF.  Use as:

' <name.of.heap.item> +CURRENT.HEAP

to find the address in the heap item's parameter field where the 16-bit current.heap address is stored.  CURRENT.HEAP specifies the heap in which the item is allocated.

See also HEAP.STRUCTURE.PF, CURRENT.HEAP, +HEAP.PAGE
Pronunciation: plus-current-heap

 
+HEAP.HANDLE

+HEAP.HANDLE ( xpfa -- xpfa+u )

Adds the offset u to the extended parameter field address xpfa. +HEAP.HANDLE is defined as a member of the structure HEAP.STRUCTURE.PF.  Use as:

' <name.of.heap.item> +HEAP.HANDLE

to find the address in the parameter field that contains of the handle which contains the base xaddr of the heap item.

See also HEAP.STRUCTURE.PF and +HEAP.PAGE
Pronunciation: plus-heap-handle

 
+HEAP.PAGE

+HEAP.PAGE ( xpfa -- xpfa+u )

Adds the offset u to the extended parameter field address xpfa. +HEAP.PAGE is defined as a member of the structure HEAP.STRUCTURE.PF.  Use as:

' <name.of.heap.item> +HEAP.PAGE

to find the address of the page of the heap as saved in the item's parameter field.  This is the page of the handle as well as the page of CURRENT.HEAP in which the item resides.

See also HEAP.STRUCTURE.PF
Pronunciation: plus-heap-page

 
+LOOP

+LOOP ( n -- )

Return Stack: ( R: w1\w2 – [w1\w2] or [] | drops w1,w2 when loop terminates)

+LOOP adds the signed integer n to the loop index. If the index crossed the boundary between limit-1 and limit (in either direction), the loop parameters are removed from the return stack and execution continues at the word following +LOOP. Otherwise, execution continues at the word following DO. See DO for examples.

Use as:

w1 w2 DO      words to be executed         n +LOOP

where w1 is the loop limit and w2 is the starting index. An error is issued if +LOOP is not properly paired with DO inside a colon definition.

See also DO    LOOP    I    J    I'   K and LEAVE
Pronunciation: plus-loop
Attributes: C, I

 
,

, ( w -- )

Stores w at the next available location in the definitions area and increments the definitions pointer DP by 2. An error occurs if w is not correctly stored (for example, if DP does not point to RAM).  An error occurs if the operation causes DP to be incremented across the boundary between 0xBFFF (the last valid address in a given page) and 0xC000 (the start of the common kernel area).
Pronunciation: comma

 
,"

," ( -- )

Compile Time: ( <text> – )

Parses the <text> string delimited by a " character from the input stream and emplaces the string in the dictionary starting at HERE.  An error occurs if the compiled string crosses a page boundary.
Pronunciation: comma-quote

 
-

- ( n1\n2 -- n3 | n3 = n1 - n2 )

Subtracts n2 from n1 and puts the result n3 on the data stack.
Pronunciation: minus

 
-1

-1 ( -- -1 )

Puts the value negative one on the data stack.
Pronunciation: minus-one

 
-1/INFINITY

-1/INFINITY ( -- r )

Pushes the smallest representable negative floating point number onto the data stack.
Pronunciation: minus-one-over-infinity

 
-2

-2 ( -- -2 )

Puts the value negative two on the data stack.
Pronunciation: minus-two

 
-INFINITY

-INFINITY ( -- r )

Pushes the negative of the largest representable floating point number onto the data stack.
Pronunciation: minus-infinity

 
-ROLL

-ROLL ( wn\...\w0\+n -- w0\wn\...\w1 | 0 ≤ +n ≤ 255 )

Transfers the top item (not including +n) on the data stack to the nth position from the top of the data stack, where the top stack item is item#0, the next is item#1, etc.  For example, 0 ROLL does nothing, 1 -ROLL is equivalent to SWAP, and 2 -ROLL is equivalent to -ROT.
Pronunciation: minus-roll

 
-ROT

-ROT ( w1\w2\w3 -- w3\w1\w2 )

Rotates the top three stack entries by moving the top cell below the next two cells on the data stack.
Pronunciation: minus-rot

 
-TRAILING

-TRAILING ( xaddr\u1 -- xaddr\u2 )

Strips trailing space characters from the string located at xaddr by returning the new character count, u2, of the text string with spaces removed.  Equivalent to BL SKIP>
Pronunciation: dash-trailing

 
.

. ( w -- )

Prints w with no leading spaces and 1 trailing space.  If the number base is decimal, w is printed as a signed number in the range -32,768 to +32,767. In other bases w is printed as an unsigned positive number.  Use U. to print w as a positive unsigned number in decimal base.
Pronunciation: dot
Attributes: M, S

 
."

." ( -- )

Compile Time: ( <text> – )

Parses the <text> string in the input stream delimited by a terminating " character.  If executing, types the <text>. If compiling, emplaces the text in the dictionary as a counted string along with a call to a routine that types the <text> at runtime.  An error occurs if the compiled string crosses a page boundary.
Pronunciation: dot-quote
Attributes: I, M

 
.HANDLES

.HANDLES ( -- )

Prints the allocated handles of the current heap in tabular format, listing the size, base xaddress, and handle xaddress of each heap item.  All quantities are displayed in hexadecimal base.  An asterisk (*) displayed in the size field indicates that the handle is not in use (i.e., it has been returned to the heap) or its contents are invalid.  This routine can be useful as a debugging aid.
Pronunciation: dot-handles
Attributes: M, S

 
.MAP

.MAP ( -- )

Prints a two line summary of the forth memory map and segment information.  Reports the DP (current dictionary pointer to the code area), NP (names area pointer), VP (variable area pointer), EEP (EEProm area pointer), heap start and end xaddresses, and the name, segment index, code base xaddress, names area base xaddress, and segment type of the currently compiling segment.  For example:

DP: 0x18000 NP: 0x109000 VP: 0x2000 EEP: 0x400 HEAP: 0x188000 to 0x1CBFFF
Segment: ''MYLIB'' ID: 0xF  Code base: 0x108000  Name base: 0x128000

This routine is invoked automatically by WARM and COLD, and provides a useful overview of the current memory map.

Type: LIB
Pronunciation: dot-map
Attributes: M, S

 
.R

.R ( w\+byte -- | +byte is field width )

Prints w right-justified in a field of +byte characters.  If +byte is less than or equal to the number of characters to be printed, the number is printed with no extra spaces.  If the number base is decimal, w is printed as a signed number in the range -32,768 to +32,767. In other bases w is printed as an unsigned positive number.  To print w as a positive unsigned number in decimal base, place a 0 on the stack above w to convert it into a positive double number and call UD.R
Pronunciation: dot-r
Attributes: M, S

 
.S

.S ( -- )

Displays the contents of the data stack without modifying the contents of the stack.  Prints the number of 1-cell stack items in brackets and displays the stack items separated by \ (read as under).  A maximum of 5 items are displayed.  For example, if there are 7 stack items having values 1…7 with 1 on top of the stack and 7 farthest down, executing .S yields

( 7 ) \ 5 \ 4 \ 3 \ 2 \ 1   ok

In execution mode, the stack contents are automatically displayed after each line is interpreted if the DEBUG flag is true.  The stack is also displayed during a TRACE of a compiled routine.
Pronunciation: dot-s
Attributes: M, S

 
.SEGMENTS

.SEGMENTS ( -- )

Prints the name and segment index of each defined segment (not including the kernel).  If the code checksum is incorrect for a given segment, a warning is printed on the segment’s line.

For example:

Segment 1 MYLIB  at code base = 0x18000  Checksum error! Reload this segment.
Segment 2 MYAPP  at code base = 0x29000


Pronunciation: dot-segments
Attributes: M, S

 
.TASKS

.TASKS ( -- )

Prints the hexadecimal task base (status) addresses of each built task.  Useful for debugging.
Pronunciation: dot-tasks
Attributes: M, S

 
/

/ ( n1\n2 -- n3 | n3 = n1/n2 )

Divide n1 by n2, giving the quotient n3. If the division does not produce an integer quotient, the quotient is rounded towards 0. Division by 0 (n2=0) produces a quotient of -1.

See also U/
Pronunciation: slash

 
//

// ( -- )

Ignores all remaining input on the current line.  A C-compatible synonym for the Forth \ comment character.  Note that // must be followed by a space character.  Very useful for inserting descriptive comments into source code.
Pronunciation: slash-slash
Attributes: I

 
/MOD

/MOD ( n1\n2 -- n3\n4 | n3 = remainder, n4 = quotient )

Divide n1 by n2, giving the remainder n3 and the quotient n4. The quotient is rounded towards 0, and the remainder carries the sign of n1. Division by 0 (n2=0) yields n3=n4=-1.

See also U/MOD
Pronunciation: slash-mod

 
/STRING

/STRING ( xaddr1\u1\n -- xaddr2\u2 )

Shortens the text string whose first character is at xaddr1 by computing xaddr2 = xaddr1 + n and u2 = u1 - n.  u1 and u2 are 16 bit text string counts.  n may be negative, and the string may cross a page boundary.
Pronunciation: slash-string

 
0

0 ( -- 0 )

Puts the value zero on the data stack.
Pronunciation: zero

 
0<

0< ( n -- flag )

Flag is TRUE if n is less than zero and FALSE otherwise.
Pronunciation: zero-less-than

 
0<>

0<> ( w -- flag )

Flag is TRUE if w is not equal to zero and FALSE otherwise.
Pronunciation: zero-not-equal

 
0=

0= ( w -- flag )

Flag is TRUE if w is equal to zero and FALSE otherwise.
Pronunciation: zero-equals

 
0>

0> ( n -- flag )

Flag is true if n is greater than zero and FALSE otherwise.
Pronunciation: zero-greater-than

 
0\0

0\0 ( -- 0\0 )

Places two zeros on the top of the stack.
Pronunciation: 0-under-0

 
1

1 ( -- 1 )

Puts the value one on the data stack.
Pronunciation: one

 
1+

1+ ( w1 -- w2 | w2 = w1 + 1 )

Adds 1 to w1 giving the sum w2.
Pronunciation: one-plus

 
1-

1- ( w1 -- w2 | w2 = w1 - 1 )

Subtracts 1 from w1 giving w2.
Pronunciation: one-minus

 
1/F

1/F ( r1 -- r2 )

r2 is the multiplicative inverse of r1; r2 = 1.0/r1.
Pronunciation: one-over-f
Attributes: S

 
1/INFINITY

1/INFINITY ( -- r )

Places the smallest representable positive floating point number on the data stack.
Pronunciation: one-over-infinity

 
1/LN(2)

1/LN(2) ( -- r )

Places the floating point representation of the inverse of the natural logarithm of 2 (1.4427) on the stack.
Pronunciation: one-over-l-n-of-two

 
1/LOG10(2)

1/LOG10(2) ( -- r )

Places the floating point representation of the inverse of the base 10 logarithm of 2 (3.3219) on the stack.
Pronunciation: one-over-log-ten-of-two

 
1/PI

1/PI ( -- r )

Places the floating point representation of 1/pi (0.3183) on the stack.
Pronunciation: one-over-pi

 
1/SQRT(2)

1/SQRT(2) ( -- r )

Places the floating point representation of the inverse of the square root of 2 (0.7071) on the stack.
Pronunciation: one-over-square-root-of-two

 
1/TEN

1/TEN ( -- r )

Places r = 0.1 on the data stack.
Pronunciation: one-over-ten

 
10^N

10^N ( n -- r )

r equals 10 to the nth power; r = 10^n.
Pronunciation: ten-to-the-n
Attributes: S

 
1XN+

1XN+ ( xaddr1 -- xaddr2 )

Adds 1 to xaddr1 yielding xaddr2. Equivalent to 1 XN+
Pronunciation: one-x-n-plus

 
1XN-

1XN- ( xaddr1 -- xaddr2 )

Subtracts 1 from xaddr1 yielding xaddr2. Equivalent to 1 XN-
Pronunciation: one-x-n-minus

 
2

2 ( -- 2 )

Puts the value two on the data stack.
Pronunciation: two

 
2!

2! ( w1\w2\xaddr -- | [xaddr] gets w2, [xaddr+2] gets w1 )

Stores two 16-bit integers at xaddr.  w2 is stored at xaddr and w1 is stored at xaddr+2. Can also be used to store a double number at xaddr.  Note that in paged memory, the address immediately following 0xBFFF is address 0x8000 on the following page.
Pronunciation: two-store

 
2*

2* ( n1 -- n2 | n2 = n1 * 2 )

Multiplies n1 by 2 giving n2.
Pronunciation: two-star

 
2+

2+ ( w1 -- w2 | w2 = w1 + 2 )

Adds 2 to w1 giving the sum w2.
Pronunciation: two-plus

 
2-

2- ( w1 -- w2 | w2 = w1 - 2 )

Subtracts 2 from w1 giving w2.
Pronunciation: two-minus

 
2/

2/ ( n1 -- n2 | n2 = n1 / 2 )

Divides n1 by 2 giving n2.

See also U2/
Pronunciation: two-slash

 
2@

2@ ( xaddr -- w1\w2 )

Fetches two 16-bit integers from xaddr.  w2 is taken from xaddr and w1 is from xaddr+2. Can also be used to fetch a double number from xaddr.  Note that in paged memory, the address immediately following 0xBFFF is address 0x8000 on the following page.
Pronunciation: two-fetch

 
2ARRAY.FETCH

2ARRAY.FETCH ( row#\col#\xpfa -- d )

Fetches and places on the data stack the contents of the element at row#, column# in the specified 2-dimensional array or matrix.  The size of the element that is fetched depends upon the number of bytes per element of the array or matrix as specified by DIMENSIONED or DIMMED, and the result is always padded out to 4 bytes on the stack.  There is an unchecked error if the specified array or matrix does not have 2 dimensions or if the number of bytes per element does not equal 1, 2, or 4.

See also M[]@
Pronunciation: two-array-fetch

 
2ARRAY.STORE

2ARRAY.STORE ( d\ row#\col#\xpfa -- )

Stores the specified byte-, 2 byte-, or 4 byte-data at the element specified by row#, column# in the specified 2-dimensional array or matrix.  The size of the element that is stored can be 1 byte, 2 bytes, or 4 bytes depending upon the number of bytes per element of the array or matrix as set by DIMENSIONED or DIMMED.  There is an unchecked error if the specified array or matrix does not have 2 dimensions or if the number of bytes per element does not equal 1, 2, or 4.

See also M[]!
Pronunciation: two-array-store

 
2CONSTANT

2CONSTANT ( wd <name> -- )

Removes the next <name> from the input stream and defines a child word called <name> which when executed leaves the 32-bit value wd on the data stack.  wd is stored in the definitions area of the dictionary. <name> is referred to as a 2constant. Use as:

wd  2CONSTANT  <name>

See the glossary entry comments for XCONSTANT and XCONSTANT.REL regarding the creation of constants in relocatable segments.
Pronunciation: two-constant
Attributes: D

 
2DROP

2DROP ( w1\w2 -- )

Drops the top two cells from the data stack.
Pronunciation: two-drop

 
2DUP

2DUP ( w1\w2 -- w1\w2\w1\w2 )

Duplicates the top two cells on the data stack.
Pronunciation: two-dupe

 
2DUP>R

2DUP>R ( w1\w2 -- w1\w2 )
Return stack: ( R: -- w1\w2 )

Copies the top cell pair on the data stack to the return stack.
Pronunciation: 2-dup-to-r
Attributes: C

 
2LITERAL

2LITERAL ( -- wd )

Compile Time: ( wd – )

If QED-Forth is in execution mode when 2LITERAL is invoked, 2LITERAL does nothing.  If QED-Forth is in compilation mode, 2LITERAL removes wd from the stack and compiles it into the dictionary along with code that, when later executed, pushes wd to the stack. 2LITERAL can be used within a colon definition to compile a numeric value into the definition.  For example,

: <name>
   ... [ 1234 1000 * ] 2LITERAL ...
;

This compiles the value calculated between [ and ] as a double literal into the definition of <name>. When <name> is executed, this value will be placed on the stack.
Pronunciation: two-literal
Attributes: C, I

 
2OVER

2OVER ( w1\w2\w3\w4 -- w1\w2\w3\w4\w1\w2 )

Places a copy of cell pair w1\w2 on the top of the stack.
Pronunciation: two-over

 
2PI/360

2PI/360 ( -- r )

Places the floating point representation of 2pi/360 (0.017453) on the stack.
Pronunciation: two-pi-over-three-sixty

 
2ROT

2ROT ( w1\w2\w3\w4\w5\w6 -- w3\w4\w5\w6\w1\w2 )

Rotates the top three cell pairs on the data stack.
Pronunciation: two-rote

 
2SWAP

2SWAP ( w1\w2\w3\w4 -- w3\w4\w1\w2 )

Exchanges the top two cell pairs on the data stack.
Pronunciation: two-swap

 
2VARIABLE

2VARIABLE ( <name> -- )

Removes the next <name> from the input stream, defines a child word called <name>, and VALLOTs 2 cells in the variable area.  When <name> is executed it leaves the extended address xaddr of the two cells reserved in the variable area that hold <name>'s contents. <name> is referred to as a 2variable. Use as:

  2VARIABLE <name>

2VARIABLE is segment-relocation-smart, and performs the correct actions even when invoked inside a library or application segment that is relocated to a code location and variable area starting xaddress that are different from its initial compilation address.
Pronunciation: 2-variable
Attributes: D

 
2XN+

2XN+ ( xaddr1 -- xaddr2 )

Adds 2 to xaddr1 yielding xaddr2. Equivalent to 2 XN+
Pronunciation: two-x-n-plus

 
2XN-

2XN- ( xaddr1 -- xaddr2 )

Subtracts 2 from xaddr1 yielding xaddr2. Equivalent to 2 XN-
Pronunciation: two-x-n-minus

 
3

3 ( -- 3 )

Puts the value three on the data stack.
Pronunciation: three

 
360/2PI

360/2PI ( -- r )

Places the floating point representation of 360/2pi (57.296) on the stack.
Pronunciation: three-sixty-over-two-pi

 
3DROP

3DROP ( w1\w2\w3 -- )

Drops the top three cells from the data stack.
Pronunciation: three-drop

 
3DUP

3DUP ( w1\w2\w3 -- w1\w2\w3\w1\w2\w3 )

Duplicates the top three cells on the data stack.
Pronunciation: three-dupe

 
4

4 ( -- 4 )

Puts the value four on the data stack.
Pronunciation: four

 
4+

4+ ( w1 -- w2 | w2 = w1 + 4 )

Adds 4 to w1 giving the sum w2.
Pronunciation: four-plus

 
4-

4- ( w1 -- w2 | w2 = w1 - 4 )

Subtracts 4 from w1 giving w2.
Pronunciation: four-minus

 
4DROP

4DROP ( w1\w2\w3\w4 -- )

Drops the top 4 cells from the data stack.
Pronunciation: four-drop

 
4DUP

4DUP ( w1\w2\w3\w4 -- w1\w2\w3\w4\w1\w2\w3\w4 )

Duplicates the top four cells on the data stack.
Pronunciation: four-dupe

 
4XN+

4XN+ ( xaddr1 -- xaddr2 )

Adds 4 to xaddr1 yielding xaddr2. Equivalent to 4 XN+
Pronunciation: four-x-n-plus

 
4XN-

4XN- ( xaddr1 -- xaddr2 )

Subtracts 4 from xaddr1 yielding xaddr2. Equivalent to 4 XN-
Pronunciation: four-x-n-minus

 
8XN+

8XN+ ( xaddr1 -- xaddr2 )

Adds 8 to xaddr1 yielding xaddr2. Equivalent to 8 XN+
Pronunciation: eight-x-n-plus

 
:

: ( < name> -- )

Starts the compilation of a new definition.  Removes <name> from the input stream and creates a header for <name> in the dictionary.  The header is SMUDGEd so that it cannot be found until ; executes to successfully terminate the definition.  Enters the compile mode so that words following : are compiled into the code field of <name> (but IMMEDIATE words are executed immediately instead of being compiled).  A <name> isn't unique warning is issued if <name> already exists in the dictionary.  The contents of CONTEXT and CURRENT are not modified.  Use as

: <name>
   ...body of new definition...
;

See also R: and X:
Pronunciation: colon
Attributes: D

 
;

; ( -- )

Marks the end of a colon definition and enters the execution mode.  Checks the stack to make sure that no extra items were placed on or removed from the data stack during compilation of the definition.  Toggles the smudge bit of the header created by : so that the new word can be found in the dictionary.  Compiles code to cause control to be passed to the calling word when the definition is later executed.  If locals were used in the definition, the code compiled by ; also removes the local variables from the return stack.
Pronunciation: semicolon
Attributes: C, I

 
<

< ( n1\n2 -- flag )

Flag is TRUE if n1 is less than n2 and FALSE otherwise.
Pronunciation: less-than

 
<#

<# ( -- )

Prepares for pictured numeric output by initializing the headerless user variable #PTR to be equal to PAD. #PTR points to the current character position in the pictured numeric output, which starts 1 byte below PAD and builds towards low memory.
Pronunciation: less-than-num
Attributes: S

 
<=

<= ( n1\n2 -- flag )

Flag is TRUE if n1 is less than or equal to n2 and FALSE otherwise.
Pronunciation: less-than-or-equal

 
<>

<> ( w1\w2 -- flag )

Flag is TRUE if w1 is not equal to w2 and FALSE otherwise.
Pronunciation: not-equal

 
<DBUILDS

<DBUILDS ( <name> -- )

Used in a high level defining word to mark the beginning of the specification of the action taken when a child word is defined.  Removes <name> from the input stream and creates a header for <name> in the dictionary.  Sets the HAS.PFA bit in the header to indicate that <name> has a parameter field.  Use as:

: <namex>
   <DBUILDS
      (code to set up child's parameter field)
   DOES>
      (run time action)
;

where <namex> is referred to as a defining word. Executing the statement

<namex> <child's.name>

defines the child word.  The code after <DBUILDS specifies the action to be taken while defining the child word.  This usually involves allotting and/or initializing the parameter field of the child.  The D in <DBUILDS stands for definitions area; the parameter field is located at the next available location in the definitions area pointed to by DP.  Thus the words ALLOT and , (as opposed to VALLOT and V,) should be used after <DBUILDS to reserve and initialize locations in the child's parameter field.  Use <DBUILDS to define child words whose parameter fields are to be in non-modifiable write-protected memory once the application program is finished. <DBUILDS is segment-relocation-smart, and performs the correct actions even when invoked inside a library or application segment that is relocated to a location that is different from its initial compilation address.

Example of use: a version of CONSTANT could be defined using <DBUILDS:

: MYCONSTANT    ( n <name> -- )
   <DBUILDS  ,
   DOES>     @
;

MYCONSTANT is a defining word.  To define a child word named THIS.CON initialized to the value 1234 execute

1234 MYCONSTANT  THIS.CON

When MYCONSTANT executes, it initializes the first 2 bytes in the child's parameter field to 1234 and increments DP by 2. Executing THIS.CON places on the stack the value stored at the extended pfa.

Restrictions: While <DBUILDS compiles relocation-smart code, there is one case that is disallowed: If the defining word which contains <DBUILDS is defined in a library, then the daughter word cannot be defined in a different library.  If this is attempted, it causes a Can't compile deferred lib-to-lib call error.  If you have the source code of the defining word available, you can get around this limitation by redefining the defining word in the local library in which it will be used.

See also DOES>
Pronunciation: d-builds
Attributes: D

 
<VBUILDS

<VBUILDS ( -- )

Used in a high level defining word to mark the beginning of the specification of the action taken when a child word is defined.  Removes <name> from the input stream and creates a header for <name> in the dictionary.  Sets the HAS.PFA bit in the header to indicate that <name> has a parameter field.  Use as:

: <namex>
   <VBUILDS  (code to set up child's parameter field)
   DOES>     (run time action)
;

where <namex> is referred to as a defining word. Executing the statement,

<namex>  <child's.name>

defines the child word.  The code after <VBUILDS specifies the action to be taken while defining the child word.  This usually involves allotting and/or initializing the parameter field of the child.  The V in <VBUILDS stands for variable area; the parameter field is located at the next available location in the variable area.  Thus the words VALLOT and V, (as opposed to ALLOT and ,) should be used after <VBUILDS to reserve and initialize locations in the child's parameter field.  Use <VBUILDS to define child words whose parameter fields must always be in modifiable non-write-protected RAM.  consult the definition of <DBUILDS. <VBUILDS is segment-relocation-smart, and performs the correct actions even when invoked inside a library or application segment that is relocated to a location that is different from its initial compilation address.

Example of use: a version of VARIABLE that initializes the variable's contents could be defined using <VBUILDS as,

: INITIALIZED.VAR    ( n <name> -- )
   <VBUILDS    V,
   DOES>
;

INITIALIZED.VAR is a defining word.  To define a child word named MYVAR initialized to the value 1234 execute

1234 INITIALIZED.VAR  MYVAR

When INITIALIZED.VAR executes, it initializes the first 2 bytes in the child's parameter field to 1234 and increments VP by 2. Executing MYVAR leaves the extended pfa on the stack (see DOES>) and a fetch from this address will return the value 1234.

Restrictions: While <VBUILDS compiles relocation-smart code that is tolerant of relocation, there is one case that is disallowed: If the defining word which contains <VBUILDS is defined in a library, then the daughter word cannot be defined in a different library.  If this is attempted, it causes a Can't compile deferred lib-to-lib call error.  If you have the source code of the defining word available, you can get around this limitation by redefining the defining word in the local library in which it will be used.

See also <DBUILDS DOES>
Pronunciation: v-builds
Attributes: D

 
=

= ( w1\w2 -- flag )

Flag is TRUE if w1 is equal to w2 and FALSE otherwise.
Pronunciation: equals

 
>

> ( n1\n2 -- flag )

Flag is TRUE if n1 is greater than n2 and FALSE otherwise.
Pronunciation: greater-than

 
><

>< ( w1 -- w2 | w2 has upper and lower bytes of w1 swapped )

Swaps the two bytes of the top data stack cell.
Pronunciation: swap-bytes

 
>=

>= ( n1\n2 -- flag )

Flag is TRUE if n1 is greater than or equal to n2 and FALSE otherwise.
Pronunciation: greater-than-or-equal

 
>ASSM

>ASSM ( -- )

Executes ASSEMBLER so that assembler mnemonics can be found in the dictionary, and enters execution mode.  Normally used to compile in-line assembly code into a high level FORTH definition, or to return to assembly after using >FORTH in a CODE definition.

See also >FORTH
Pronunciation: to-assembly
Attributes: I

 
>DEGREES

>DEGREES ( r1 -- r2 )

Converts r1 in radians into r2 in degrees.
Pronunciation: to-degrees
Attributes: S

 
>FORTH

>FORTH ( -- )

Sets vocabulary equal to FORTH and enters compilation mode.  Normally used to compile high level FORTH words into an assembly CODE definition, or to return to high level after using >ASSM to assemble in-line code.

See also >ASSM
Pronunciation: to-forth

 
>IN

>IN ( -- xaddr )

User variable that contains the offset from the start of the current input stream to the next character to be parsed.  The contents of >IN may range from 0 to the number of characters in the input stream.

See also QUERY, WORD
Pronunciation: to-in
Attributes: U

 
>R

>R ( w -- )
Return stack: ( R: -- w )

Transfers the top cell on the data stack to the return stack.
Pronunciation: to-r
Attributes: C

 
>RADIANS

>RADIANS ( r1 -- r2 )

Converts r1 in degrees into r2 in radians.
Pronunciation: to-radians
Attributes: S

 
?

? ( xaddr -- )

Prints the integer contents of xaddr.
Pronunciation: question
Attributes: S

 
?ARRAY.SIZE

?ARRAY.SIZE ( array.xpfa -- d | d = number of elements in array )

Returns the number of elements d (not the number of bytes!) in the array or matrix designated by array.xpfa. 0\0 is returned for undimensioned arrays and matrices.
Pronunciation: question-array-size

 
?C.CALLABLE

?C.CALLABLE ( xnfa -- flag )

Returns a true flag if the word with the specified xnfa was defined as a C-callable function with an extended header.  To create a C-callable function, one of the defining words X: XCODE or XCREATE must be used, or the C.CALLABLE system variable must be true while the word is being defined.
Pronunciation: question-c-callable

 
?DIM.MATRIX

?DIM.MATRIX ( matrix.xpfa -- #rows\#cols )

Returns the number of rows and columns in the specified matrix.  ABORTs if matrix.xpfa is undimensioned or is not a matrix.
Pronunciation: question-dim-matrix

 
?DIMENSIONS

?DIMENSIONS ( array.xpfa -- [u1\u2\...uN\N\n ] or [0\0] | N=#dim, n=bytes/element )

Returns the number of elements u1, u2, …uN in each dimension under the number of dimensions N under the number of bytes per element n for the array or matrix designated by array.xpfa.  Returns 0\0 if the array is undimensioned.
Pronunciation: question-dimensions

 
?DUP

?DUP ( w -- [w\w] or [0] )

Duplicates the top cell of the data stack if it is non-zero.
Pronunciation: question-dupe

 
?GET

?GET ( xresource -- flag | flag is true if resource is available )

Checks the resource variable xresource.  If the resource is available (i.e., if it contains 0\0 or the current task's xtask.id), ?GET claims the resource by storing the current task's xtask.id in xresource, and returns a true flag.  Otherwise, ?GET returns a false flag.  Does not execute PAUSE.  To ensure that the state of the resource is correctly determined, ?GET disables interrupts for 0.25 to 1 microsecond.

See also GET, RELEASE, and RESOURCE.VARIABLE:
Pronunciation: question-get

 
?HANDLE.SIZE

?HANDLE.SIZE ( xhandle -- +d )

+d is the number of heap bytes allocated to the heap item associated with xhandle.  An unchecked error occurs if xhandle is not a valid heap handle.
Pronunciation: question-handle-size

 
?HAS.PFA

?HAS.PFA ( xnfa -- flag )

Returns a TRUE flag if the word referenced by xnfa has a parameter field address.
Pronunciation: question-has-p-f-a

 
?IMMEDIATE

?IMMEDIATE ( xnfa -- flag )

Returns a TRUE flag if the word referenced by xnfa is an immediate word.
Pronunciation: question-immediate

 
?KEY

?KEY ( -- flag )

Returns a flag indicating receipt of a character.  If flag is TRUE, a character has been received; otherwise, no character has been received.  Depending on the value in SERIAL.ACCESS, may execute SERIAL RELEASE and SERIAL GET. ?KEY is a vectored routine that executes the routine whose xcfa is stored in the user variable U?KEY.  Thus the programmer may install a different routine to tailor the behavior of ?KEY to the application's needs.  For example, ?KEY could access a serial port other than that on the 68HCS12 chip, or different tasks could use different ?KEY routines.

See also ?KEY1 and ?KEY2
Pronunciation: question-key
Attributes: M, U

 
?KEY1

?KEY1 ( -- flag )

Returns a flag indicating whether a character has been received on the primary serial port (serial1).  The serial1 port is supported by the processor’s SCI0 hardware UART.  If a character has been received a TRUE flag is returned; otherwise a FALSE flag is returned. ?KEY1 is the default ?KEY routine installed in the U?KEY user variable after the special cleanup mode is invoked, or if SERIAL1.AT.STARTUP has been executed.  If the value in SERIAL.ACCESS is RELEASE.AFTER.LINE, ?KEY1 does not GET or RELEASE the SERIAL1.RESOURCE.  If SERIAL.ACCESS contains RELEASE.ALWAYS, ?KEY1 GETs and RELEASEs the SERIAL1.RESOURCE.  If SERIAL.ACCESS contains RELEASE.NEVER, ?KEY1 GETs but does not RELEASE the SERIAL1.RESOURCE.

See also SERIAL.ACCESS, ?KEY, U, ?KEY2
Pronunciation: question-key-one
Attributes: M

 
?KEY2

?KEY2 ( -- flag )

Returns a flag indicating whether a character has been received on the secondary serial port (serial2).  The serial2 port is supported by the processor’s SCI1 hardware UART, and it has all the capabilities of the primary serial port.  If a character has been received a TRUE flag is returned; otherwise a FALSE flag is returned. ?KEY2 can be made the default ?KEY routine installed in the U?KEY user variable after each reset or restart by executing SERIAL2.AT.STARTUP.  If the value in SERIAL.ACCESS is RELEASE.AFTER.LINE, ?KEY2 does not GET or RELEASE the SERIAL2.RESOURCE.  If SERIAL.ACCESS contains RELEASE.ALWAYS, ?KEY2 GETs and RELEASEs the SERIAL2.RESOURCE.  If SERIAL.ACCESS contains RELEASE.NEVER, ?KEY2 GETs but does not RELEASE the SERIAL2.RESOURCE.

See also SERIAL.ACCESS, ?KEY, U, ?KEY1
Pronunciation: question-key-two
Attributes: M

 
?MATRIX.SIZE

?MATRIX.SIZE ( matrix.xpfa -- d | d = number of elements in matrix )

Returns the number of elements d (not the number of bytes!) in the specified matrix.  ABORTs if matrix.xpfa is undimensioned or is not a matrix.
Pronunciation: question-matrix-size

 
?RECEIVE

?RECEIVE ( xmailbox -- [wd\true] or [false] | wd = received message )

If xmailbox is empty (i.e., if it contains 0\0), returns a false flag.  If xmailbox contains a message (i.e., if it does not contain 0\0), fetches the contents of xmailbox wd and stores a 0\0 into xmailbox to indicate that the message has been received and that the mailbox is now empty.  Leaves the message wd on the stack under a true flag.  Does not execute PAUSE.  To ensure that the state of the mailbox is correctly determined, ?RECEIVE disables interrupts for 0.55 to 1.7 microseconds.

See also SEND, RECEIVE, and MAILBOX:
Pronunciation: question-receive

 
?SEND

?SEND ( wd\xmailbox -- flag | flag is true if message was sent )

If the mailbox with extended address xmailbox is empty (i.e., contains 0\0), stores the 32-bit message wd in xmailbox and returns a true flag.  If xmailbox is not empty, drops wd and returns a false flag.  Does not execute PAUSE.  The message wd can be any 32-bit quantity except 0\0. For example, the message can be an xaddress that points to a block of data.  To ensure that the state of the mailbox is correctly determined, ?SEND disables interrupts for 0.75 to 1.15 microseconds.

See also SEND, RECEIVE, and MAILBOX:
Pronunciation: question-send

 
@

@ ( xaddr -- w )

Fetches a 16-bit number from the memory location specified by xaddr.  The high order byte is taken from xaddr and the low order byte from xaddr+1. Note that in paged memory, the address immediately following 0xBFFF is address 0x8000 on the following page.
Pronunciation: fetch

 
ABORT

ABORT ( [...] -- )
Return stack: ( R: [...] -- )

If the CUSTOM.ABORT flag is true, executes the abort routine whose xcfa is stored in the user variable UABORT, and then returns to the routine that called ABORT.  If CUSTOM.ABORT is false, executes the default routine (ABORT) which clears the data and return stacks, sets the page to the default page (0), and executes FORTH DEFINITIONS to set CONTEXT and CURRENT equal to FORTH.  If an autostart or priority autostart vector has been installed, (ABORT) executes the specified routine; otherwise it executes QUIT which sets the compilation mode and enters the interpreter.  If R0 and S0 aren't in common RAM, a COLD restart is initiated.

 
ABORT"

ABORT" ( flag -- )

Compile Time: ( <text> – )

If flag is true, prints the <text> string between ABORT" and the terminating " and then executes ABORT.  If flag is false, drops flag and continues execution.  Useful for error detection and reporting.
Pronunciation: abort-quote
Attributes: C, I, M

 
ABS

ABS ( n1 -- +n2 | +n2 = absolute value of n1 )

Replaces n1 with its absolute value +n2. If n1 is positive, +n2 = n1. If n1 is negative, +n2 is the negative of n1.
Pronunciation: abs

 
ACTIVATE

ACTIVATE ( xcfa\xtask.id -- )

Sets up the routine specified by xcfa as the action word of the task whose task identifier (STATUS xaddress) is xtask.id, and leaves the specified task AWAKE with the I bit in its CCR register clear so that it will be entered with interrupts globally enabled on the next pass through the round robin task list.  ACTIVATE assumes that the specified task has already been added to the task list by BUILD.TASK or BUILD.STANDARD.TASK.  The task's action word is typically either an infinite loop or a finite routine that ends with a HALT instruction (which is itself an infinite loop).  ACTIVATE buries a call to HALT in the return stack frame to ensure graceful termination of a finite activation routine.  If cooperative multitasking is used exclusively (i.e., if the timeslicer is not used), then the loop of the action word must contain at least one PAUSE statement (or invoke a word that in turn executes PAUSE).  Otherwise, no task switching occurs.  If timeslicing is used, incorporation of PAUSE statements in the loop of the action word is optional.  The typical form of an action word is:

: <action.name>
   words to be executed once
   BEGIN
      words to be executed infinitely
      PAUSE
      words to be executed infinitely
   AGAIN
;

or:

: <action.name>
   words to be executed
   PAUSE
   words to be executed
   HALT
;

For example, if a task has been defined with

ALLOCATE.TASK: <task.name>

and built using BUILD.TASK or BUILD.STANDARD.TASK, it can be activated by executing

CFA.FOR <action.name>  <task.name>  ACTIVATE
 
ADDR->

ADDR-> ( u1 <name> -- u2 )

Adds a named member to the structure being defined and reserves room for one 16 bit address field in the structure.  Removes <name> from the input stream and creates a structure field called <name>. u1 is the structure offset initialized by STRUCTURE.BEGIN:. u2 is the updated offset to be used by the next member defining word or by STRUCTURE.END.  When <name> is later executed, it adds its offset u1 to the extended address found on the data stack which is typically the start xaddress of an instance of the data structure; the result is the xaddress of the desired member in the structure.
Pronunciation: address
Attributes: D

 
ADDR.SIZE

ADDR.SIZE ( -- n )

Returns the constant value 2 which is the number of bytes in a parameter of type addr that is passed to or returned by a C-callable function.  This size specifier is used in the PARAMS( statement that describes the input and output parameters of a C-callable function.  consult the glossary entry for PARAMS(
Pronunciation: address-size

 
ADDR:

ADDR: ( <name> -- )

ADDR: is a synonym for INTEGER: . It defines a 16-bit self-fetching variable.  ADDR: is meant to hold a 16-bit address.  Consult the glossary entry for INTEGER: .
Pronunciation: address-colon
Attributes: D

 
ADDRS->

ADDRS-> ( u1\u2 <name> -- u3 )

Adds a named member to the structure being defined and reserves room for u2 16-bit addresses in the structure.  Removes <name> from the input stream and creates a structure field called <name>. u1 is the structure offset initialized by STRUCTURE.BEGIN:. u3 is the updated offset to be used by the next member defining word or by STRUCTURE.END.  When <name> is later executed, it adds its offset u1 to the extended address found on the data stack which is typically the start xaddress of an instance of the data structure; the result is the xaddress of the desired member in the structure.
Pronunciation: addresses
Attributes: D

 
AGAIN

AGAIN ( -- )

AGAIN is used within a colon definition to mark the end of an infinite loop structure as:

BEGIN
   <words to be iterated>
AGAIN

The words between BEGIN and AGAIN are executed indefinitely.  AGAIN is equivalent to FALSE UNTIL.  An error is issued if BEGIN and AGAIN are not properly paired inside a definition.

Attributes: C, I

 
ALLOCATE.TASK:

ALLOCATE.TASK: ( <name> -- )

Removes the next <name> from the input stream, allocates a 1 Kbyte task area at VHERE in the variable area, advances VP by 1024 bytes, and creates an XCONSTANT that, when executed, leaves the task identifier xtask.id on the stack.  xtask.id is the base xaddress of the user area of the new task being defined.  An error is issued if xtask.id is not in common RAM.  xtask.id is also referred to as the task's STATUS address.

NOTE: To optimize stack timing on the 68HCS12 processor, all task user areas should be allocated early in the user’s program so that they are located in the user-available on-chip RAM at addresses 0x2000 through 0x3FFF.  Tasks allocated in the off-chip common RAM at 0x4000-0x7FFF will exhibit a slight increase in the number of processor cycles required for stack accesses to odd addresses.

See also TASK: and STATUS Attributes: D

 
ALLOCATED

ALLOCATED ( u\xpfa -- | u is heap item size in bytes )

Allocates u bytes of heap memory and associates it with the item having the specified parameter field address xpfa.  The xpfa is typically associated with a word defined by H.INSTANCE:. Typical use:

size.of.heap.item  H.INSTANCE:  <name>
SIZE.OF <name>  ' <name> ALLOCATED

or:

size.of.heap.item  ' <name> ALLOCATED

See H.INSTANCE: and SIZE.OF.

 
ALLOT

ALLOT ( n -- )

Reserves n bytes in the dictionary by incrementing the definitions pointer DP by n.  An error occurs if the ALLOT operation causes DP to be incremented across the boundary between 0xBFFF (the last valid address in a given page) and 0xC000 (the start of the common kernel area).

 
AND

AND ( w1\w2 -- w3 )

Performs a logical bit-wise 'and' of two 16 bit numbers w1 and w2 to produce the result w3.

 
ANEW

ANEW ( <name> -- )

Tries to find <name> in the CURRENT vocabulary.  If <name> is not found or was not created by ANEW, then creates <name>. If <name> is found, executes <name> which resets the variable pointer VP and the EEPROM pointer EEP to the values they had when ANEW <name> was first executed, then FORGETs all words defined after <name> was created; this resets DP and NP to the values they had when ANEW <name> was first executed.  ANEW should be used to avoid redundancy when reloading code during debugging.  Note that heap items associated with forgotten words are not released by ANEW and should be handled by the programmer using ON.FORGET.  Also note that the segment defining words LIBRARY and APPLICATION perform the ANEW action.

See also LIBRARY, APPLICATION, FORGET and ON.FORGET

Attributes: D

 
APPLICATION

APPLICATION ( <name> -- )

Defines a new application segment.  The kernel supports relocatable code organized as program segments. Device drivers for Wildcards, Graphical User Interface Tools, and other software are distributed as pre-compiled segments that are accessible using Forth or C.  The two types of segments are libraries and applications.  A library is fully relocatable as long as it does not cross a page boundary.  Libraries that are longer than a page, and Application segments, can be relocated from page to page.  The variables and EEPROM variables accessed by a library are offset-based, and can change based on the value of VP and EEP when the library is loaded.  The variables and EEPROM variables compiled into an application segment, on the other hand, have their addresses fixed at the time of compilation.  An application segment has a fixed 16-bit starting address which is set at compilation time, and can be relocated to a parallel set of pages using RELOCATE: or RELOCATE.ONLY: (consult their glossary entries for details), or by storing the desired minimum starting address and page into DP and downloading the installer file to the board (see COMPOSE.FORTH.INSTALLER and COMPOSE.FORTH.INSTALLER.FOR).

This APPLICATION routine creates a non-executable full-width extended segment header <name>. Initializes system variables LIBRARY.IS.COMPILING (to false), THIS.SEGMENT.XBASE (to HERE), and THIS.SEGMENT.XNFA (points to the xnfa of <name>).  Assigns the next available segment index by incrementing the contents of LAST.SEGMENT, then stores the incremented value in THIS.SEGMENT.  Writes the 3-byte segment base xaddress (= HERE), 3-byte segment xnfa (points to <name>), 2-byte variable base address (=VHERE), and 2-byte EEPROM base address (= EEHERE) into the EEPROM segment table entry for the specified segment index.  ALLOTs the segment structure in the dictionary area.  The segment structure contains fields specifying the memory usage of the segment including the starting VP, variable area size, starting EEP, EEPROM area size, total segment size, and starting compilation address, as well as a code-area checksum and the required segment table.  Some of these fields are set by this function, while others are set by END.SEGMENT, REQUIRES.FIXED, or REQUIRES.RELATIVE.

Defining a new library or application also performs the ANEW action, which simplifies reloading and enforces the uniqueness of each segment name.  That is, this routine tries to FIND <name> and, if it already exists and is a segment header, FORGETs it and resets VP and EEP before re-defining <name>. This routine creates <name> using the maximum WIDTH (to assure clean segment dumping and loading) and modifies <name>’s header.type byte, setting the segment.mask bit.  This routine zeros the 3-byte xcfa.offset field in <name>’s header to indicate that segment is compiling; this field is set by END.SEGMENT to contain the offset from the <name> xnfa to the xnfa of the last header defined in segment.  When a segment is forgotten, its EEPROM array entry is erased and LAST.SEGMENT is decremented; see FORGET.

WARNINGS: There is no executable code associated with the segment header, so it is illegal to execute <name>, and CFA.FOR and ' (i.e., tick) do not work with the segment header.  Rather, <name> should should only be used as an argument to segment management routines such as LOAD.SEGMENT, COMPOSE.C.HEADERS.FOR, and BUILD.APPLICATION.  This routine aborts if too many segments have been declared (24 is the maximum, including the kernel which is segment 0).  Attempting to reload a segment whose definition is still in memory does not result in non-unique warnings; rather, it may produce the aborting error message: Memory write failed during segment loading; try reloading all libraries. If this happens, do a COLD restart and reload the code.

Attributes: D

 
ARRAY.PF

ARRAY.PF ( -- u | u = size of an array parameter field )

Places on the stack the number of bytes in an array parameter field.  Typically used to define a stack-based temporary array within a definition; temporary arrays defined in this manner preserve re-entrancy.  For example:

: ARRAY.FUNCTION
   LOCALS{ .... | x&temp.array.pfa }
   ARRAY.PF PF.STACK.FRAME   TO x&temp.array.pfa
   10 1 6 x&temp.array.pfa DIMENSIONED   \ dimension
   ....                                  \ use the temp array
   x&temp.array.pfa DELETED              \ delete from heap
   ARRAY.PF FRAME.DROP                   \ drop temp pf off stack
;

See MATRIX.PF, PF.STACK.FRAME and FRAME.DROP.
Pronunciation: array-p-f

 
ARRAY:

ARRAY: ( <name> -- )

Removes <name> from input stream and defines <name> as an array.  Allots and clears a parameter field for <name> in the variable area.  When executed, <name> returns the extended element address given the indices; its stack picture is:

( indices -- xaddr )

The element xaddress is also returned by the command

indices ' <name> []

ARRAY: does not allocate heap space or dimension the array; see DIMENSIONED.
Pronunciation: array-colon
Attributes: D

 
ASCII

ASCII ( <name> -- char )

Removes <name> from the input stream and converts its first character to its ASCII value char.  In execution mode the ascii value is left on the stack.  In compilation mode the ascii code is compiled as a literal into the current definition.

Attributes: I

 
ASK.FNUMBER

ASK.FNUMBER ( <text> -- [r\-1] or [0] )

Inputs a character string <text> to the PAD buffer, terminating when CHARS/LINE characters are received or a carriage return is received, whichever comes first.  Leaves <text> as a counted string at PAD and, ignoring leading blanks, attempts to convert the <text> string to a valid floating point number.  If <text> is an ascii representation of a valid integer or double number or floating point number, the equivalent floating point representation r is left on the stack under a true flag; otherwise, a false flag is left on the stack.

See also ASK.NUMBER, NEXT.NUMBER, and $>F
Pronunciation: ask-f-number
Attributes: M, S

 
ASK.NUMBER

ASK.NUMBER ( <text> -- [n\1] or [d\2] or [0] )

Inputs a character string <text> to the PAD buffer, terminating when CHARS/LINE characters are received or a carriage return is received, whichever comes first.  Leaves <text> as a counted string at PAD and, ignoring leading blanks, attempts to convert the <text> string to a single or double number.  If the string is converted to a 16-bit integer n, leaves n under a 1 flag.  If the string cannot be represented as a 16-bit integer but is a valid 32-bit double number d, leaves d on the stack under a 2 flag.  Conversion is performed in the current number base unless the number starts with 0x or 0X, in which case hexadecimal base is used.  Leaves a 0 flag on the stack if the <text> string cannot be converted to a valid integer.

See also ASK.FNUMBER and NEXT.NUMBER

Attributes: M, S

 
ASLEEP

ASLEEP ( -- n )

A constant that places the value 1 on the stack.  When stored into a task's STATUS user variable, indicates to the multitasking executive that the task is asleep and cannot be entered.

 
ASSEMBLER

ASSEMBLER ( -- )

Sets CONTEXT equal to the assembler vocabulary's xhandle so that the assembler vocabulary is the first vocabulary searched during dictionary searches.

 
ATD.DIGITAL.INPUTS

ATD.DIGITAL.INPUTS ( n -- )

The input parameter n is a 16-bit mask.  Each 1 bit in the mask configures the corresponding AN0-AN15 bit on the processor’s PortAD0 and PortAD1 as a digital input, and each 0 bit configures the corresponding pin as an analog input.  If you are using some of the AN0-AN15 pins as analog inputs and others as digital inputs, call this routine after invoking the ATD.ON function, as ATD.ON configures a set of 8 pins (either PortAD0 or PortAD1) as analog inputs; See the ATD.ON glossary entry.

CAUTION: If an analog voltage is present on a given input pin, it is not advisable to configure the pin as a digital input, as this can cause high current draw in the processor chip if the analog signal puts the digital input buffer in its linear mode midway between logic levels.

Implementation details: This routine transfers the specified bitmask from the input parameter to the PORTAD0.MODE and PORTAD1.MODE digital-enable registers; See their glossary entries.

 
ATD.MULTIPLE

ATD.MULTIPLE ( xaddr\utime\1byte_flag\numsequences\starting_channel_id\numchannels -- )

The input parameters of this routine have been given names for convenience; with the exception of the 32-bit xaddr, all of the parameters are 16-bit integers.  This is the most versatile routine for performing multiple Analog-To-Digital (ATD) conversions using either of the two 8-input ATD ports on the HCS12 processor.  This routine converts multiple sequences comprising the specified numchannels per sequence, and stores the conversion results as 8- or 16-bit values into a memory buffer starting at the specified xaddr.

If the 1byte_flag is true, each sample occupies 1 byte in the buffer, and this constrains the results to 8-bit resolution per sample, with each sample result in the range 0 to 255. If the one_byte flag is false, each sample occupies 2 bytes in the buffer, each sample has 10-bit resolution, with the 10-bit data left justified in a 16-bit unsigned result, and the least significant 6 bits of each result equal zero.

For mathematical simplicity each 2-byte result can be interpreted as a 16-bit unsigned number spanning the range 0x0000 to 0xFFFF (decimal 0 to 65,535).  For example, converting a 2.5 Volt signal (representing half the 0 to 5V ATD input span) yields a 2-byte result of 0x8000 (decimal 32768) if the one_byte flag is false, or an equivalent 1-byte result of 0x80 (decimal 128) if the one_byte flag is true.  If the 1byte_flag is true, the buffer at xaddr must be at least one byte larger than the number of samples; that is:

buffer_size = (numsequences * numchannels) + 1   \ if 1byte_flag is true

This is because ATD.MULTIPLE actually stores 2 bytes per sample, and, if the 1byte_flag is true, overwrites the least significant byte of the prior sample with the next sample’s most significant byte.  If the 1byte_flag is false, the required buffer size is:

buffer_size = 2 * (numsequences * numchannels)   \ if 1byte_flag is false

This routine performs multiple analog-to-digital conversions with the unsigned integer utime input parameter specifying a programmable inter-sequence sampling time with 2.5 microseconds (us) quantization as explained below.  The starting_channel_id parameter in the range 0 to 15, and the numchannels paramter in the range 1 to 8, together specify a sequence of up to 8 channels converted in order with modulus 8 rollover.  Note that channels 0 to 7 are on the ATD0-7.RESULTS converter, and channels 8 to 15 are on the ATD8-15.RESULTS converter, so the channel after 7 in a sequence is 0, not 8. Similarly, the channel after 15 is 8. Once started, the ATD automatically converts each of the channels in the sequence (up to the specified numchannels in the range 1 to 8) one time at 7 us per conversion.  In other words, the conversion time between channels within a sequence is always 7 microseconds.  The numsequences parameter is an unsigned integer that specifies the number of such sequence conversions that are performed.  The conversion results are stored in the buffer starting at the specified xaddr.  After all the conversions within a sequence have been performed, there is an additional inter-sequence delay of

inter-sequence_delay = (2.5us * utime) + overhead_delay

where the overhead_delay averages 3 us if xaddr is in common RAM, or 6.5 us if xaddr is in paged RAM.  Inter-sequence timing jitter (that is, the variation in overhead_delay from sequence to sequence) is less than 0.2 us, and there is no jitter within a sequence.  If a page crossing occurs between sequences, add 1 us of overhead_delay and an additional 0.2 us of potential jitter to the inter-sequence time.  The user-specified utime parameter is an unsigned integer which is multiplied by 2.5 us and added to the overhead_delay after each sequence to specify the conversion timing.

Before calling this routine, make sure that you have called ATD.ON for the specified ATD port.  If you are using channels in the range 0 to 7, execute:

0 ATD.ON

If you are using channels in the range 8 to 15, execute:

8 ATD.ON

If you are using channels from both converters, execute:

0 ATD.ON
8 ATD.ON

Calling this routine aborts any prior unfinished ATD conversions on the specified ATD subsystem (channels 0-7 or 8-15).  The conversion uses the current data format, which is set by ATD.ON as 10-bit resolution, left justified unsigned data (although if the 1byte_flag is true, the resolution of the stored data is only 8 bits).  This routine assumes that the AFFC (fast flag clear) bit in ATDCTL2 is set as configured by ATD.ON.  Clearing this AFFC register bit or modifying other ATD control bits can result in unpredictable operation.

Timing Analysis: This routine uses a software timing delay to set the inter-sequence timing interval.  The following timing analysis is accurate for a single-task application with no interrupts running.  Multitasking or interrupt service routines will increase the sampling intervals.  The simplest timing case involves calling this routine with 1 channel per sequence (numchannels = 1), in which case the inter-sample time depends on whether the xaddr buffer is in common RAM or paged RAM, as follows: sampling_period = 7us + (2.5us * utime) + 3 us \ if xaddr is in common RAM

sampling_period = 7us + (2.5us * utime) + 6.5 us \ if xaddr is in paged RAM

In the first case, with utime = 0, sampling occurs every 10us = 100KHz sampling.  In the second case, with utime = 0, sampling occurs every 13.5us = 74KHz sampling.  Increasing the utime parameter increases the inter-sequence sample time and decreases the sampling frequency.  For example, with numchannels = 1 (1 channel per sequence), utime = decimal 96, and xaddr in common RAM, the inter-sample time is:

7us + (2.5us * 96) + 3us = 250us

which corresponds to a sampling frequency of 4 KHz.  If there is more than 1 channel per sequence, then the sampling process can be thought of as a burst of samples within the sequence separated by 7 us per sample, followed by an inter-sequence delay.  For example, assume that the starting channel is 4, numchannels = 8, utime = 0, and the storage xaddress is in paged memory.  In this case, the samples are stored in memory in the following order:

4 5 6 7 0 1 2 3   4 5 6 7 0 1 2 3  4 5 6 7 0 1 2 3 ...

Each sample within the sequence takes 7us, and the inter-sequence delay is:

inter-sequence_delay = 0 * 2.5us + 6.5us = 6.5us.

Thus the total time between samples of a given channel equals

sampling_period = numsamples * 7us + 6.5us = 56 us + 6.5us = 62.5us,

corresponding to a 16KHz sampling rate for each channel.  If we modify this example by changing utime to decimal 15, then the total time between samples of a given channel equals:

sampling_period = 8 * 7us + (2.5us * 15) + 6.5us = 56us + 37.5us + 6.5us = 100 us

corresponding to a 10KHz sampling rate for each channel.

 
ATD.OFF

ATD.OFF ( channel_id -- )

The input is any integer channel number between 0 and 15. This routine turns off the associated Analog To Digital (ATD) converter.  The entire 8-channel ATD0-7.RESULTS converter is turned off if the input channel_id is between 0 and 7. The entire 8-channel ATD8-15.RESULTS converter is turned off if the input channel_id is between 8 and 15. To turn off both converters (all 16 ATD channels) on the HCS12 processor, execute:

0 ATD.OFF
8 ATD.OFF

This routine powers down the ATD converter subsystem, but it does not affect the analog-versus-digital input mode of the associated pins.  After a power up or hardware reset, the ATD converters are off by default, and PortAD0 and PortAD1 are not configured for digital inputs.

See also ATD.ON and ATD.DIGITAL.INPUTS

 
ATD.ON

ATD.ON ( channel_id -- )

The input is any integer channel number between 0 and 15. This routine turns on the associated Analog To Digital (ATD) converter and configures the pins as analog inputs by clearing all 8 bits in either PORTAD0.MODE (if the input parameter is between 0 and 7) or PORTAD1.MODE (if the input parameter is between 8 and 15).  If the input channel_id is between 0 and 7, the ATD0-7.RESULTS converter is turned on and channels 0 through 7 are configured as analog inputs.  If the input channel_id is between 8 and 15, the ATD8-15.RESULTS converter is turned on and channels 8 through 15 are configured as analog inputs.  To turn on both converters (all 16 ATD channels) on the HCS12 processor, execute:

0 ATD.ON
8 ATD.ON

To configure some pins as analog inputs and some as digital inputs, first call ATD.ON for the specified set of 8 inputs, then call ATD.DIGITAL.INPUTS with the appropriate bitmask.  After a power up or hardware reset, the ATD converters are off by default, and PortAD0 and PortAD1 are not configured for digital inputs.  ATD.ON configures the converter to return 10-bit data left justified in a 16-bit field, with the 6 least significant bits equal to 0. ATD.ON puts the converter in fast clear mode so that the driver routines do not have to explicitly clear the conversion complete flag.  The other ATD software driver routines rely on these initializations by ATD.ON.

See also ATD.OFF and ATD.DIGITAL.INPUTS

 
ATD.SAMPLE

ATD.SAMPLE ( starting_channel_id\N -- addr | N = numchannels )

This routine converts a single sequence of up to 8 Analog To Digital (ATD) channels, waits for the conversions to complete, and returns the 16-bit base address of the result register frame in common RAM.  The starting_channel_id (an integer in the range 0 to 15) and numchannels (an integer in the range 1 to 8) parameters specify a sequence of up to 8 channels converted in order with rollover modulus 8. Note that channels 0 to 7 are on the ATD0-7.RESULTS converter, and channels 8 to 15 are on the ATD8-15.RESULTS converter, so the channel after 7 in a sequence is 0, not 8. Similarly, the channel after 15 is 8. Once started, the ATD automatically converts each of the channels in the sequence (up to the specified numchannels in the range 1 to 8) one time at 7 microseconds (us) per conversion.  In other words, the conversion time between channels within a sequence is always 7 us.  The total execution time of this routine is approximately:

(7us * numsamples) + 3.5 us

Before starting a new conversion, results should be fetched out of the returned result register frame which starts at either the 16-bit address ATD0-7.RESULTS or ATD8-15.RESULTS; the relevant 16-bit address is returned by this routine.  This result register frame contains eight 16-bit result registers, with the first result in the sequence (corresponding to starting_channel) at byte offset 0, the next at offset 2, then offset 4, etc., for the specified numchannels.  For example, if the starting channel is 4 and numchannels equals 8, then samples are stored in the result registers in the following order:

4 5 6 7 0 1 2 3

Before calling this routine, make sure that you have called ATD.ON for the specified ATD port.  If you are using channels in the range 0 to 7, execute:

0 ATD.ON

If you are using channels in the range 8 to 15, execute:

8 ATD.ON

If you are using channels from both converters, execute:

0 ATD.ON
8 ATD.ON

Note that the conversion uses the current data format, which is set by ATDOn() as 10-bit resolution, with the 10-bit data left justified in a 16-bit unsigned result; the least significant 6 bits of each result equal zero.  For mathematical simplicity each result can be interpreted as a 16-bit unsigned number spanning the range 0x0000 to 0xFFFF (decimal 0 to 65,535).  For example, converting a 2.5 Volt signal (representing half the 0 to 5V ATD input span) yields a result of 0x8000 (decimal 32768).  Calling this routine aborts any prior unfinished ATD conversions on the specified ATD subsystem (channels 0-7 or 8-15).  This routine assumes that the AFFC (fast flag clear) bit in ATDCTL2 is set as configured by ATD.ON.  Clearing this register bit or modifying other ATD control bits can result in unpredictable operation.

 
ATD.SINGLE

ATD.SINGLE ( channel_id -- u | u = conversion result )

This routine converts a single specified Analog To Digital (ATD) channel (0 ≤ channel_id ≤ 15), waits for the conversion to complete, and returns the result.  Note that the conversion uses the current data format, which is set by ATDOn() as 10-bit resolution, with the 10-bit data left justified in a 16-bit unsigned result; the least significant 6 bits of each result equal zero.  For mathematical simplicity each result can be interpreted as a 16-bit unsigned number spanning the range 0x0000 to 0xFFFF (decimal 0 to 65,535).  For example, converting a 2.5 Volt signal (representing half the 0 to 5V ATD input span) yields a result of 0x8000 (decimal 32768).  Before calling this routine, make sure that you have called ATD.ON for the specified ATD port.  If you are using channels in the range 0 to 7, execute:

0 ATD.ON

If you are using channels in the range 8 to 15, execute:

8 ATD.ON

Calling this routine aborts any prior unfinished ATD conversions on the specified ATD subsystem (channels 0-7 or 8-15).  This routine assumes that the AFFC (fast flag clear) bit in ATDCTL2 is set as configured by ATD.ON.  Clearing this register bit or modifying other ATD control bits can result in unpredictable operation.

 
ATD.START.SAMPLE

ATD.START.SAMPLE ( starting_channel_id\N -- | N = numchannels )

This routine starts the conversion of a single sequence of up to 8 Analog To Digital (ATD) channels and exits without waiting for the conversion(s) to complete.  This is useful in customer-coded interrupt service routines: you can read the prior conversion results from the result registers, then start the next conversion without waiting for results.  This makes for fast operation, as the conversions take place between the interrupt services at the rate of 7 microseconds (us) per channel.  Prior results should be fetched out of the appropriate result register set, starting at either ATD0-7.RESULTS or ATD8-15.RESULTS; See their glossary entries.  Each of these constants is the base address of eight 16-bit result registers, with the first result in the sequence (corresponding to starting_channel) at offset 0, the next at offset 2, then offset 4, etc., for the specified numchannels.  The starting_channel_id (an integer in the range 0 to 15) and numchannels (an integer in the range 1 to 8) parameters specify a sequence of up to 8 channels converted in order with rollover modulus 8. Note that channels 0 to 7 are on the ATD0-7.RESULTS converter, and channels 8 to 15 are on the ATD8-15.RESULTS converter, so the channel after 7 in a sequence is 0, not 8. Similarly, the channel after 15 is 8. This routine takes under 3.5 us to start the conversions and exit.  Once started, the ATD automatically converts each of the channels in the sequence (up to the specified numchannels in the range 1 to 8) one time at 7 us per conversion.  For example, if the starting channel is 4 and numchannels equals 8, then samples are stored in the result registers in the following order:

4 5 6 7 0 1 2 3

Before calling this routine, make sure that you have called ATD.ON for the specified ATD port.  If you are using channels in the range 0 to 7, execute:

0 ATD.ON

If you are using channels in the range 8 to 15, execute:

8 ATD.ON

If you are using channels from both converters, execute:

0 ATD.ON
8 ATD.ON

Note that the conversion uses the current data format, which is set by ATDOn() as 10-bit resolution, with the 10-bit data left justified in a 16-bit unsigned result; the least significant 6 bits of each result equal zero.  For mathematical simplicity each result can be interpreted as a 16-bit unsigned number spanning the range 0x0000 to 0xFFFF (decimal 0 to 65,535).  For example, converting a 2.5 Volt signal (representing half the 0 to 5V ATD input span) yields a result of 0x8000 (decimal 32768).  Calling this routine aborts any prior unfinished ATD conversions on the specified ATD subsystem (channels 0-7 or 8-15).  This routine assumes that the AFFC (fast flag clear) bit in ATDCTL2 is set as configured by ATD.ON.  Clearing this register bit or modifying other ATD control bits can result in unpredictable operation.

 
ATD0-7.RESULTS

ATD0-7.RESULTS ( -- addr )

A constant that returns a 16-bit address in common memory.  This address is the base of a result register frame that contains up to eight 16-bit Analog-to-Digital (ATD) registers holding the results of a conversion sequence intitiated by ATD.START.SAMPLE or ATD.SAMPLE (See their glossary entries).  A sequence is a set of up to 8 channels converted in order with rollover modulus 8, specified by starting_channel_id (an integer in the range 0 to 7) and numchannels (an integer in the range 1 to 8) parameters passed to one of the initiating routines.  As its name suggests, ATD0-7.RESULTS contains results only from analog channels 0 through 7. The channel after 7 in a sequence is 0, not 8. The ATD8-15.RESULTS register frame holds results acquired from channels 8 through 15. Once started, the ATD automatically converts each of the channels in the sequence (up to the specified numchannels in the range 1 to 8).  For example, if the starting channel is 4 and numchannels equals 8, then samples are stored in the result registers in the following order:

4 5 6 7 0 1 2 3

In this case, the 2-byte channel 4 result is stored at ATD0-7.RESULTS, the channel 5 result is stored at ATD0-7.RESULTS + 2, the channel 6 result is stored at ATD0-7.RESULTS + 4, and the final conversion in the sequence (channel 3) result is stored at ATD0-7.RESULTS + 14. Note that the conversion uses the current data format, which is set by ATDOn() as 10-bit resolution, with the 10-bit data left justified in a 16-bit unsigned result; the least significant 6 bits of each result equal zero.  For mathematical simplicity each result can be interpreted as a 16-bit unsigned number spanning the range 0x0000 to 0xFFFF (decimal 0 to 65,535).  For example, converting a 2.5 Volt signal (representing half the 0 to 5V ATD input span) yields a result of 0x8000 (decimal 32768).

 
ATD0.ID

ATD0.ID ( -- n )

Returns the interrupt identity code for the Analog-to-Digital converter #0 subsystem on the HCS12 chip.  Used as an argument for ATTACH.
Pronunciation: a-t-d-zero-i-d

 
ATD1.ID

ATD1.ID ( -- n )

Returns the interrupt identity code for the Analog-to-Digital converter #1 subsystem on the HCS12 chip.  Used as an argument for ATTACH.
Pronunciation: a-t-d-one-i-d

 
ATD8-15.RESULTS

ATD8-15.RESULTS ( -- addr )

A constant that returns a 16-bit address in common memory.  This address is the base of a result register frame that contains up to eight 16-bit Analog-to-Digital (ATD) registers holding the results of a conversion sequence intitiated by ATD.START.SAMPLE or ATD.SAMPLE (See their glossary entries).  A sequence is a set of up to 8 channels converted in order with rollover modulus 8, specified by starting_channel_id (an integer in the range 8 to 15) and numchannels (an integer in the range 1 to 8) parameters passed to one of the initiating routines.  As its name suggests, ATD8-15.RESULTS contains results only from analog channels 8 through 15. The channel after 15 in a sequence is 8. The ATD0-7.RESULTS register frame holds results acquired from channels 0 through 7. Once started, the ATD automatically converts each of the channels in the sequence (up to the specified numchannels in the range 1 to 8).  For example, if the starting channel is 12 and numchannels equals 8, then samples are stored in the result registers in the following order:

12 13 14 15 8 9 10 11

In this case, the 2-byte channel 12 result is stored at ATD8-15.RESULTS, the channel 13 result is stored at ATD8-15.RESULTS + 2, the channel 14 result is stored at ATD8-15.RESULTS + 4, and the final conversion in the sequence (channel 11) result is stored at ATD8-15.RESULTS + 14. Note that the conversion uses the current data format, which is set by ATDOn() as 10-bit resolution, with the 10-bit data left justified in a 16-bit unsigned result; the least significant 6 bits of each result equal zero.  For mathematical simplicity each result can be interpreted as a 16-bit unsigned number spanning the range 0x0000 to 0xFFFF (decimal 0 to 65,535).  For example, converting a 2.5 Volt signal (representing half the 0 to 5V ATD input span) yields a result of 0x8000 (decimal 32768).

 
ATTACH

ATTACH ( xcfa\n -- | n = interrupt identity number )

Posts an interrupt handler routine specified by xcfa for the interrupt with identity number n (e.g., ATD0.ID, ATD1.ID, etc.) Compiles an 8-byte code sequence at the EEPROM location associated with the specified interrupt.  When the interrupt is serviced, the code at xcfa will be executed.  The xcfa can be on any page.  If coded in high level, the interrupt handler routine should end with a ; and if coded in assembly should end with an RTS (as opposed to an RTI).

Implementation details: The runtime code compiled by this word saves the registers and the contents of the headerless system variable c/forth.dstack.ptr, and then writes the contents of the headerless system variable irq.dstack.save (default contents = 0x2000) into Y and into c/forth.dstack.ptr.  This ensures that forth functions invoked from C via PUSH.FORTH.PARAMS (see its glossary entry) will work properly.  The runtime code also initializes S0 in the current user area so DEPTH works.  Then the runtime code calls the specified interrupt service routine.  When the service routine returns, the runtime code restores Y, S0, c/forth.dstack.ptr, and the page register, then returns from interrupt.  This runtime code allows any foreground routine to temporarily corrupt the Y register (which is the forth data stack pointer) and/or use extended math operands that change Y without fear that an interrupt routine will rely on the contents of Y for its data stack.  Interrupt latency is 3.75 microseconds until the service routine is entered.  Exit latency after the service routine returns is 2.8 microseconds, resulting in a total latency of 6.55 microseconds.

 
AUTOSTART:

AUTOSTART: ( <name> -- )

Removes <name> from the input stream and compiles a 6-byte sequence at 0xBFFA on page 0x37 in the HCS12 on-chip flash so that upon subsequent restarts and ABORTs, <name> will be automatically executed.  This allows a finished application to be automatically entered upon power up and resets.  The autostart routine is invoked by ABORT which is called by the error handler and upon every reset or restart.  The autostart is executed after the processing of any valid boot vectors that have been posted by Mosaic’s kernel extensions, and after the PRIORITY.AUTOSTART vector is checked.  If no priority autostart or autostart routine is posted or if the specified autostart routine terminates, ABORT then invokes QUIT which is the QED-Forth interpreter.  To undo the effects of this command and return to the default startup action, call NO.AUTOSTART.  To recover from the installation of a buggy autostart routine, invoke the special cleanup mode by following the directions in the hardware manual.  NOTE: For production systems, consider using the PRIORITY.AUTOSTART: or IS.PRIORITY.AUTOSTART routines which place the startup vector near the top of page 0x0F in external RAM and shadow flash, making it easier to include the vector as part of the downloaded code.  Consult the examples in the glossary entries for DUMP.S2 and DUMP.MANY.S2.

Implementation detail: At location 0xBFFA on page 0x37, AUTOSTART: writes the pattern 0x1357 followed by the 4-byte xcfa of <name>.

See also IS.AUTOSTART, PRIORITY.AUTOSTART: and IS.PRIORITY.AUTOSTART

Attributes: I

 
AWAKE

AWAKE ( -- n )

A constant that places the value 0 on the stack.  When stored into a task's STATUS user variable, indicates to the multitasking executive that the task is awake and may be entered.

 
BACKTRACK

BACKTRACK ( -- )

Resets >IN to point to the first character of the word in the input stream that was most recently parsed by WORD.

 
BASE

BASE ( -- xaddr )

User variable that contains the current number base (number conversion radix) used for number I/O and numeric conversion.  Unchecked error if the contents of BASE are less than 2 or greater than 72.

Attributes: U

 
BAUD

BAUD ( n1\n2 -- | n1 = baud/100, n2 = 1 for Serial 1 or 2 for Serial 2 )

Configures the specified serial port (Serial1 or Serial2) to have a baud rate equal to n1*100 now and after all future resets and restarts.  Serial1 (called SCI0 in the HCS12 processor documentation) and Serial2 (called SCI1 in the HCS12 processor documentation) are implemented by on-chip hardware UARTs on the HCS12. These UARTs can implement standard baud rates of 1200, 2400, 4800, 9600, 19200, 38400, 57600, and 115200 baud.  The default rate at startup and after a factory clean is 115200 baud.  Baud rates up to 19200 baud have bit rate errors under 0.16%, and baud rates 38400, 57600, and 115200 have a bit-rate timing error of under 1.4%, which leads to excellent performance.

Implementation detail: This routine calculates the baud divisor parameter and writes it to the SCIBDH and SCIBDL register pair for the specified port to immediately cange the baud rate, and writes the same value to a reserved cell in EEPROM so that the specified baud rate is set for the specified serial port upon subsequent restarts.  To undo the effects of this command, execute BAUD with a new value or invoke the special cleanup mode.  CAUTION: frequent run-time changes to the baud rate under program control are not recommended, as this can wear out the EEPROM cell that configures the baud rate at startup.  If your application requires this, it is better to directly write to the hardware registers to modify the baud rate.

 
BEEP

BEEP ( -- )

Emits the bell character, ascii 07, if QUIET is OFF .

 
BEGIN

BEGIN ( -- )

BEGIN is used within a colon definition to mark the start of a loop structure as:

BEGIN ... UNTIL
BEGIN ... WHILE ... REPEAT
BEGIN ... AGAIN

The words after UNTIL or REPEAT are executed after the loop structure terminates.  BEGINAGAIN is an infinite loop.  An error is issued if BEGIN is not properly paired in a loop structure.

Attributes: C, I

 
BENCHMARK:

BENCHMARK: ( <name> -- )

Measures and displays the execution time for the word <name>. The timeslice clock must be running to benchmark a word.  This can be accomplished by executing START.TIMESLICER before invoking BENCHMARK:. <name> may be any executable word.  Data stack parameters required by <name> should be placed on the stack before calling BENCHMARK:. Typical use:

START.TIMESLICER \ if timeslicer wasn't already running ...
\ push necessary stack parameters for <name>
BENCHMARK: <name>

See also (BENCHMARK:)
Pronunciation: benchmark
Attributes: M, S

 
BL

BL ( -- char )

Puts the ascii value for a blank (a space, ascii value 32) on the data stack.
Pronunciation: b-l

 
BLANK

BLANK ( xaddr\u -- | u = byte count )

The ascii character value for space (32) is stored in each of u consecutive bytes beginning at xaddr.  The specified region may cross page boundaries.  Does nothing if u = 0.

 
BLANK.ARRAY

BLANK.ARRAY ( array.xpfa -- )

Stores an ascii blank (the space character, 0x20 or 32 decimal) into each byte of the specified array.

 
BOOLEAN

BOOLEAN ( w -- flag )

Converts a 16-bit integer into a boolean flag.  Flag is FALSE (0) if w is 0, otherwise flag is TRUE (-1).

 
BREAK

BREAK ( -- )

Sets a software breakpoint when compiled into any function (including assembly language functions).  At execution time, BREAK suspends the program flow, saves the machine state and invokes a FORTH-style text interpreter that can be distinguished from the standard interpreter by the BREAK> prompt displayed at the start of each line.  Any valid commands may be executed from within the BREAK interpreter.

From within the BREAK interpreter, typing a carriage return alone on a line exits the BREAK mode, restores the machine registers to the values they held just before BREAK was entered, and resumes execution of the program that was running when BREAK was entered.  The BREAK routine's preservation of the register state and its ability to execute any valid command make it a very powerful debugging tool.  BREAK may be compiled into any definition to stop program flow in order to debug or analyze a word at the point where BREAK was called.  Once inside BREAK, the stack contents may be displayed (using .S) or altered (as long as the total number of stack items is not changed).  Variables and memory locations may be displayed or altered.  New words can even be defined and executed.

BREAK is called by the trace routine if the variable SINGLE.STEP is set.  To single step through some code, compile the code with TRACE ON, then execute the code with DEBUG and SINGLE.STEP ON.  After each call, the name of the traced word and the stack picture will be printed, and then the BREAK word will execute, letting you execute FORTH commands.  To go to the next step in the word being debugged, enter a CR alone on a line.  To display the register state after each traced line, execute DUMP.REGISTERS ON.  To stop single-stepping but continue tracing, execute the forth command SINGLE.STEP OFF.  The trace will continue, but BREAK will not be called again, unless you hit a key.  The trace routine enters the BREAK mode when a keystroke is detected at the serial I/O port: if you hit a key, BREAK is called by TRACE, and again, a CR resumes execution.  To exit the traced definition completely, execute ABORT (or any illegal command) from within the BREAK interpreter.

Any error encountered while in the BREAK routine executes ABORT which places the programmer back into the standard QED-Forth interpreter (unless ABORT has been revectored to perform some other action; see CUSTOM.ABORT).  See DEBUG, TRACE, SINGLE.STEP, DUMP.REGISTERS, IS.TRACE.ACTION, and BREAK.ALL.

Attributes: M, S

 
BREAK.ALL

BREAK.ALL ( -- )

Sets a multitasking-aware software breakpoint that is useful for debugging multitasking applications.  At execution time, BREAK.ALL suspends the program flow, saves the machine state and invokes a FORTH-style text interpreter that can be distinguished from the standard interpreter by the BREAK> prompt displayed at the start of each line.  This routine suspends all tasks in the round-robin task list, disables interrupts, and calls BREAK (see its glossary entry for a complete description).  After BREAK exits, BREAK.ALL restores the interrupt state and the task loop and continues with program execution.

Attributes: M, S

 
BUILD.APPLICATION

BUILD.APPLICATION ( n <application.name> <"filename.seg"> -- )

Prints (exports) an S-record code dump and directives that summarize all of the information contained in the segment called <application.name> and, using the #saveto command, directs the printed contents to the specified filename. When later downloaded to the controller board, these statements reconstitute the application at a code location specified by the input parameter n in conjunction with the DP (dictionary pointer).

In other words, BUILD.APPLICATION is a means of storing an application segment as a text file that can be loaded at a later time, preserving all of the information needed to regenerate (compose) all of the files assoicated with the application segment.  Consult the glossary entry for APPLICATION. <application.name> and <"filename"> must be on the same line as BUILD.APPLICATION, and filename must be enclosed in quotes; all characters between the quotes are part of the filename.  The filename typically has the *.seg file extension to indicate that it is a segment build file.  If the null filename "" is specified, then the #saveto and #endsaveto statements are suppressed.

The input parameter n is a place-specifier that may have one of these three constant values: IN.PLACE, TO.HERE or USER.SPECIFIED.

  • The TO.HERE mode allows the application to be loaded at a later time along with other libraries and applications; the library code will be placed at the load-time dictionary pointer DP contents, and the dictionary pointer will be automatically advanced at load time.
  • If you want the application to remain in a fixed location such as a specified page in on-chip flash, use the IN.PLACE specifier.
  • The USER.SPECIFIED parameter provides flexibility in locating the library, but requires that you explicity place a starting code xaddress on the stack before the loading process begins; for this reason, the USER.SPECIFIED parameter is not recommended except in special circumstances.

The BUILD.APPLICATION command is a synonym for BUILD.LIBRARY.

Notes: Before reloading the application, it is a good idea to call COLD to wipe out the names of the original segment headers.  Also note that you can relocate the application’s code before calling this routine using RELOCATE: or RELOCATE.ONLY:.  Headers associated with the application segment can be relocated using MOVE.HEADERS.  If you want to relocate to flash, you can relocate to the exact flash location first, then use BUILD.APPLICATION to export the segment IN.PLACE.  If there is a problem during loading of the segment, you'll get at load time a Memory write failed during segment loading! Try reloading all libraries ABORT message.  This error message can occur if flash memory could not be correctly written, or if the segment.index of a required segment has changed since the now-loading segment was dumped; the solution is to type COLD and reload and all of the required segments in the proper order.  This routine requires at least 15.6 Kbytes available in the current heap for temporary storage of an array.

Example: This example shows the form of the output generated by this function.

IN.PLACE BUILD.APPLICATION MYAPP "myapp.4th"    \ export MYAPP application
#saveto "myapp.4th"

\ Dumping 0xE9 byte application MYAPP from xaddr 0x4811A
HERE DIN 0x12E 0x811A 0x0 SEGMENT.BUMP XDUP DP X!
2 NEEDED XDUP RECEIVE.HEX
S00900004845414445524D
S22404801A410000E000200000000004000000801A00000000000000000000000005E
S9030000FC

DIN 0x4811A DIN 0xE9 0x0 0x0  ( xaddr\d_seg_size\varsize\eesize -- )
LOAD.APPLICATION MYAPP
REQUIRES.RELATIVE MYLIB

\ MAKE.HEADER statement stack picture:
( width\seg.index\fn{ms}hdr{ls}type\cfa.os\cfa.pg.os\#inputs\input.sizes--)

0x3F 0x2 0x8 0x20 0x0 0x0 0x0 MAKE.HEADER MY.C1

PROTOTYPE: MY.C1  ${  void my_c1_function ( );}$
C.HEADERS: MY.CSTRUCT  ${
   struct MyStruct
      { int status;        // asleep/awake
        xaddr rpsave;
      };
}$

0x3F 0x2 0x8 0x3B 0x0 0x83 0x2000 MAKE.HEADER MY.CSECOND
PROTOTYPE: MY.CSECOND ${ float my_c_second ( char c1, int i1, float f1 );}$

0x3F 0x2 0x8 0xC4 0x0 0x80 0x0 MAKE.HEADER MY.C3
PROTOTYPE: MY.C3 ${ long my_c3_function ( );}$

FORTH.HEADERS: 4TH.HEADS  ${  ( these comments go into the forth file)
( second comment line)  }$

END.LOAD.SEGMENT

DATE/TIME: MYAPP ${Mon 11/23/05 12:05:32 PST}$
#endsaveto

Attributes: M, S

 
BUILD.HASH.TABLE

BUILD.HASH.TABLE ( -- )

Builds the hash table and then marks it valid by writing 0x1357 to the VALID.HASH system variable.  The hash table speeds the lookup of words in the linked list of dictionary names in the FORTH vocabulary.  Instead of searching the standard reverse-chronological list which contains all of the FORTH names, the interpreter/compiler can use the hash-linked lists which sort the names into hundreds of short lists based on the count and first character of the name.  The hash table is an array in RAM whose contents point to the last-defined name in the FORTH vocabulary corresponding to each count/first-character set.  This function is automatically called at (cold) startup and is invoked by FORGET and LINK.  The hash table is located in reserved system RAM in the upper half of page 0x1D.

See also VALID.HASH, HASH.INDEX, and HASH.INDEX>XADDR

 
BUILD.LIBRARY

BUILD.LIBRARY ( n <library.name> <"filename.seg"> -- )

Prints (exports) an S-record code dump and directives that summarize all of the information contained in the segment called <library.name> and, using the #saveto command, directs the printed contents to the specified filename. When later downloaded to the controller board, these statements reconstitute the library at a code location specified by the input parameter n in conjunction with the DP (dictionary pointer).

In other words, BUILD.LIBRARY is a means of storing an application segment as a text file that can be loaded at a later time, preserving all of the information needed to regenerate (compose) all of the files assoicated with the library segment.  Consult the glossary entry for LIBRARY and for the COMPOSE routines. <library.name> and <"filename"> must be on the same line as BUILD.LIBRARY, and filename must be enclosed in quotes; all characters between the quotes are part of the filename.  The filename typically has the *.seg file extension to indicate that it is a segment build file.  If the null filename "" is specified, then the #saveto and #endsaveto statements are suppressed.  The input parameter n is a place-specifier that may have one of these three constant values: IN.PLACE, TO.HERE or USER.SPECIFIED.  When building (exporting) a relocatable library, the recommended place-specifier is TO.HERE.  The TO.HERE mode allows the application to be loaded at a later time along with other libraries and applications; the library code will be placed at the load-time dictionary pointer DP contents, and the dictionary pointer will be automatically advanced at load time.  If you want the library to remain in a fixed location such as a specified page in on-chip flash, use the IN.PLACE specifier.  The USER.SPECIFIED parameter provides flexibility in locating the library, but requires that you explicity place a starting code xaddress on the stack before the loading process begins; for this reason, the USER.SPECIFIED parameter is not recommended except in special circumstances.

Notes: Before reloading the library, it is a good idea to call COLD to wipe out the names of the original segment headers.  Also note that you can relocate the library’s code before calling this routine using RELOCATE: or RELOCATE.ONLY:.  Headers associated with the library segment can be relocated using MOVE.HEADERS.  If you want to relocate to flash, you can relocate to the exact flash location first, then use BUILD.LIBRARY to export the segment IN.PLACE.  If there is a problem during loading of the segment, you'll get at load time a Memory write failed during segment loading! Try reloading all libraries ABORT message.  This error message can occur if flash memory could not be correctly written, or if the segment.index of a required segment has changed since the now-loading segment was dumped; the solution is to type COLD and reload and all of the required segments in the proper order.  This routine requires at least 15.6 Kbytes available in the current heap for temporary storage of an array. BUILD.LIBRARY and BUILD.APPLICATION are synonyms.

For example, the following code shows the form of the output generated by this function.

TO.HERE BUILD.LIBRARY MYLIB "mylib.4th"    \ export the MYLIB library
#saveto "mylib.4th"

\ Dumping 0xE0 byte library MYLIB from xaddr 0x4801A
HERE DIN 0x108 0x801A 0xFFFF SEGMENT.BUMP XDUP DP X!
2 NEEDED XDUP RECEIVE.HEX   S00900004845414445524D
S22404801A410000E000200000000004000000801A00000000000000000000000005E
S9030000FC
( xbase.addr-- )  DIN 0xE0 0x0 0x0  ( xaddr\d_seg_size\varsize\eesize -- )

LOAD.LIBRARY MYLIB

\ MAKE.HEADER statement stack picture:

( width\seg.index\fn{ms}hdr{ls}type\cfa.os\cfa.pg.os\#inputs\input.sizes--)

0x3F 0x41 0x8 0x2F 0x0 0x83 0x2000 MAKE.HEADER MULTIPLY.THEM

PROTOTYPE: MULTIPLY.THEM  ${  float MultiplyThem ( char c1, int i1, float f1 );}$
C.HEADERS: USER.STRUCT  ${
  struct UserStruct
   {  int next_task;  // round robin tasking
      xaddr sp_save;
   };
}$

FORTH.HEADERS: MORE.HEADS  ${  ( we usually don't need text in the forth file)
( but this is the exception that proves the rule!)  }$
END.LOAD.SEGMENT
DATE/TIME: MYAPP ${Mon 11/23/05 12:05:32 PST}$
#endsaveto

Attributes: M, S

 
BUILD.SEGMENTS

BUILD.SEGMENTS ( place.specifier "filename.seg" -- )

Steps through all the defined segments (libraries and applications) and for each performs the actions as described in the glossary entry for BUILD.APPLICATION (for application segments), or BUILD.LIBRARY using the specified input parameter.  The input parameter n is a place-specifier that may have one of these three constant values: IN.PLACE, TO.HERE or USER.SPECIFIED.  This routine requires that all segments have been completed by use of the END.SEGMENT command.  For each defined segment, prints (exports) an S-record code dump and directives that summarize all of the information contained in the segment and, using the #saveto command, directs the printed contents for all segments to the specified filename. When later downloaded to the controller board, these statements reconstitute the segments.  If TO.HERE was specified, the segments are placed at the load-time dictionary pointer HERE, and the dictionary pointer is automatically advanced.  If IN.PLACE was specified, the segments are placed at the same code location from which they were built/exported.  In other words, BUILD.SEGMENTS is a means of storing one or more library and/or application segments as a text file that can be loaded at a later time, preserving all of the information needed to regenerate (compose) all of the files assoicated with the segments.  Consult the glossary entries for the COMPOSE routines. <"filename"> must be on the same line as BUILD.SEGMENTS, and must be enclosed in quotes; all characters between the quotes are part of the filename.  The filename typically has the *.seg file extension to indicate that it is a segment build file.  If the null filename "" is specified, then the #saveto and #endsaveto statements are suppressed.

Notes: Before reloading the library, it is a good idea to call COLD to wipe out the names of the original segment headers.  Also note that you can relocate the segment code before calling this routine using RELOCATE:.  Headers associated with the segments can be relocated using MOVE.HEADERS.  If you want to relocate to flash, you can relocate to the exact flash location first, then use this routine to export the segment IN.PLACE.  If there is a problem during loading of the segment, you'll get at load time a Memory write failed during segment loading! Try reloading all libraries ABORT message.  This error message can occur if flash memory could not be correctly written, or if the segment.index of a required segment has changed since the now-loading segment was dumped; the solution is to type COLD and reload and all of the required segments in the proper order.  This routine requires at least 15.6 Kbytes available in the current heap for temporary storage of an array.

Attributes: M, S

 
BUILD.STANDARD.TASK

BUILD.STANDARD.TASK ( xaddr1\xaddr2\xaddr3\xtask.id -- |

xaddr1=xheap.start, xaddr2=xheap.end, xaddr3=VP )

Builds a task with a specified heap and variable area and no compilation privileges.  The task's stacks, user area, PAD, POCKET, and TIB are assigned to a 1Kbyte block of common RAM starting at xtask.id (the base of the task's user area, which is left on the stack by stating the task’s name).  The task is appended to the round-robin task list and left ASLEEP running the default action word HALT.  xaddr1 is the extended heap starting address, and xaddr2 is the extended heap end address. BUILD.STANDARD.TASK passes these to IS.HEAP which initializes the heap accordingly.  xaddr3 specifies the start of the variable area for the task, and xtask.id is the task identifier xaddress (also called the task's STATUS address or the base of its user area.) DP and NP are set to invalid xaddress 0\0 so that the task cannot compile new words (it can, however, interpret and execute previously defined words).  The 256-byte user area of the parent task (i.e., the task that is active when this command executes) is copied to create the new task's user area, so the parent's configuration is initially inherited by the new task.  This implies that the new task has access to all the words in the parent's dictionary.  The variables that control the memory map of the new task are set so that R0 = xtask.id + 0x400, S0 = xtask.id + 0x300, (both stacks have 1/4K space and grow downward in memory), TIB extends upward for 94 bytes starting at xtask.id + 0x180, POCKET extends upward for 64 bytes starting at xtask.id + 0x1E0, and PAD extends upward for 82 bytes and downward for 36 bytes starting at xtask.id + 0x124. To initialize CURRENT.HEAP without modifying the heap control variables, pass BUILD.STANDARD.TASK a heap start xaddress that is equal to the heap end xaddress (see IS.HEAP).

 
BUILD.TASK

BUILD.TASK ( xheap.start\xheap.end\xvp\xeep\xdp\xnp\xtib\xpad\xpocket\xr0\xs0\xtask\n -- )

Builds a task with a specified memory map.  Appends the task to the round-robin task list and leaves it ASLEEP running the default action word HALT.  The stack picture above uses non-standard symbols that are more descriptive than a long list of xaddr items.  All but the last item on the stack are extended addresses (xaddr).  The last item n is the integer size of the user area.  The first n bytes of the user area of the parent task (i.e., the task that is active when this command executes) are copied to create the new task's user area, so the parent's configuration is initially inherited by the new task.  This implies that the new task has access to all the words in the parent's dictionary because the values in the new task's CONTEXT and CURRENT user variables have been copied from the parent.  The variables that control the memory map of the new task are set according to the parameters passed to BUILD.TASK.  xheap.start\xheap.end are passed to IS.HEAP which initializes the heap accordingly. (To initialize CURRENT.HEAP without modifying the heap control variables, pass BUILD.STANDARD.TASK a heap start xaddress that is equal to the heap end xaddress; see IS.HEAP).  xvp specifies the contents of VP in the new task's user area, xeep specifies EEP, xdp specifies DP, xnp specifies NP, xtib specifies the contents of UTIB, xpad specifies the contents of UPAD, xpocket specifies the contents of UPOCKET, xr0 specifies R0 which positions the return stack, and xs0 specifies S0 which positions the data stack.  xtask.id is the base address of the user area; it is the xaddress placed on the stack when the task's name is invoked.  xr0, xs0, and xtask.id must be in common ram.  The user area grows upward in memory, and stacks grow downward.  If the new task ever calls WORD or interprets input, a POCKET buffer must be allocated and must be in the common RAM. BUILD.TASK gives the programmer complete flexibility in allocating memory resources to a task.  Some tasks might not need all of these memory areas; in this case, default invalid xaddresses such as 0\0 can be used to initialize the unneeded memory pointers.  The minimum required resources for a task are the first 6 bytes of the user area (STATUS, NEXT.TASK, and RP.SAVE) and a return stack.  At the other end of the complexity scale, tasks that can compile new definitions and perform math, I/O and heap operations need to allocate all of the memory areas.  Passing values for xvp and xdp in RAM allows compilation of new definitions and the task could subsequently have a private dictionary segment that is not accessible to other tasks. (However, note that concurrent compilation by multiple tasks is discouraged, as some compilation variables are not in task-private memory; additionally, task-private words should be in a non-FORTH vocabulary to avoid corrupting the hash table).  An error is issued if xtask.id, xr0 or xs0 is not in the common RAM.

See also BUILD.STANDARD.TASK

 
BYTE->

BYTE-> ( u1 <name> -- u2 )

Adds a named member to the structure being defined and reserves room for a single byte field in the structure.  Removes <name> from the input stream and creates a structure field called <name>. u1 is the structure offset initialized by STRUCTURE.BEGIN:. u2 is the updated offset to be used by the next member defining word or by STRUCTURE.END.  When <name> is later executed, it adds its offset u1 to the extended address found on the data stack which is typically the start xaddress of an instance of the data structure; the result is the xaddress of the desired member in the structure.
Pronunciation: byte
Attributes: D

 
BYTE.SIZE

BYTE.SIZE ( -- n )

Returns the constant value 1 which is the number of bytes in a parameter of type byte that is passed to or returned by a C-callable function.  This size specifier is used in the PARAMS( statement that describes the input and output parameters of a C-callable function.  Because all 1-byte parameters are promoted to 2 bytes by the C compiler, a byte-size parameter may be declared using either BYTE.SIZE or INT.SIZE.  Consult the glossary entry for PARAMS(

 
BYTES->

BYTES-> ( u1\u2 <name> -- u3 )

Adds a named member to the structure being defined and reserves room for u2 bytes in the structure.  Removes <name> from the input stream and creates a structure field called <name>. u1 is the structure offset initialized by STRUCTURE.BEGIN:. u3 is the updated offset to be used by the next member defining word or by STRUCTURE.END.  When <name> is later executed, it adds its offset u1 to the extended address found on the data stack which is typically the start xaddress of an instance of the data structure; the result is the xaddress of the desired member in the structure.
Pronunciation: bytes
Attributes: D

 
C!

C! ( byte\xaddr -- )

Stores byte at xaddr.
Pronunciation: c-store

 
C,

C, ( byte -- )

Stores byte at the next available location in the definitions area and increments the definitions pointer DP by 1. An error occurs if byte is not correctly store (for example, if DP does not point to RAM).  An error occurs if the C, operation causes DP to be incremented across the boundary between 0xBFFF (the last valid address in a given page) and 0xC000 (the start of the common kernel area).
Pronunciation: c-comma

 
C.CALLABLE

C.CALLABLE ( -- xaddr )

A 16-bit system variable that controls whether a c-callable extended header is created by any defining word.  This is typically used when defining a library or application segment that will be invoked from the C programming environment.  The default contents of C.CALLABLE after a COLD restart is zero.  To create a C-callable function, variable or EEPROM variable, C.CALLABLE must be non-zero while the word is being defined.  The low level defining words (CREATE) and CREATE examine the state of C.CALLABLE and, if nonzero, set the size of the newly created name header to the extended size and set the C-callable bit in the header.type field of the name header.  The defining words XCREATE, X:, and XCODE set the system variable C.CALLABLE true before calling (CREATE) to ensure that a C-callable eXtended header is formed, and restore C.CALLABLE to its prior value after the new header is created.  To create C-callable variables or EEvariables, set C.CALLABLE true, declare the variables and their prototypes (see VPROTOTYPE: and EEPROTOTYPE☺, and then return C.CALLABLE to its default value of zero, as:

C.CALLABLE ON
VARIABLE     MYVAR
VPROTOTYPE:  MYVAR ${ xaddr myvar }$   \ no ; (semicolon) in var prototype!
EEVARIABLE   MYEEVAR
EEPROTOTYPE: MYEEVAR ${ xaddr myeevar }$
C.CALLABLE OFF

When COMPOSE.C.HEADERS is executed, the C macro definitions for these variables will be created.
Pronunciation: c-callable

 
C.HEADERS:

C.HEADERS: ( <header.name> <${ long.string}$> -- )

Defines one or more lines of text (between the ${ and }$ delimiters of the <long.string>) that will be printed into the C header (*.h) file of the currently compiling library or application segment when the segment is composed using COMPOSE.C.HEADERS or COMPOSE.C.HEADERS.FOR. <header.name> is a placeholder, and it must be unique.  The long.string starts with ${ followed by a space or cr, and ends with the }$ delimiter.  The <header.name> and ${ must be on the same line as C.HEADERS: and the beginning ${ and the terminating }$ need not be space-delimited.

For example:

C.HEADERS: MY.CSTRUCT ${
   struct MyStruct {
      int status;  // asleep/awake
      xaddr rpsave;
   };
}$

Note that you need not put the terminating }$ on a separate line; putting it on the line above would simply delete the a carriage return from the text dump.

IMPLEMENTATION DETAILS: The text string is stored in the forth names area during the compilation of the segment, but does not take up space in the final loaded library.  If the names page boundary is crossed during the definition of header.name, this routine aborts with an error.  The long.string can cross the name-page boundary without error.  The <header.name> has a bit set in its function.type field identifying it as a C header text name, and this causes the text string to be printed during the segment export.  The xaddress of the text string can be obtained as:

NFA.FOR <header.name> NFA>L$ DROP


Pronunciation: c-headers

 
C@

C@ ( xaddr -- byte )

Fetches the byte stored at xaddr.
Pronunciation: c-fetch

 
CALC.CHECKSUM

CALC.CHECKSUM ( xaddr\u -- checksum | u must be even )

Calculates a 16-bit checksum for the buffer specified by xaddr and u, where xaddr is the starting address, and u is the number of bytes.  The buffer may cross page boundaries.  The checksum is calculated by initializing a 16-bit accumulator to zero, then adding in turn each 2-byte number in the buffer to the accumulator; the checksum is the final value of the accumulator.  Using this routine provides a method of checking whether the contents of an area of memory have changed since a prior checksum was calculated.  This routine is optimized for speed, and executes at 0.7 microseconds per byte.  The number of bytes u must be even; otherwise, an additional byte is included in the checksum.  The result is undefined if u = 0 or 1.

 
CALC.CHECKSUM.MANY

CALC.CHECKSUM.MANY ( xaddr\d -- checksum | d must be even )

Calculates a 16-bit checksum for the buffer specified by xaddr and d, where xaddr is the starting address, and d is the number of bytes.  The buffer may cross page boundaries.  The checksum is calculated by initializing a 16-bit accumulator to zero, then adding in turn each 2-byte number in the buffer to the accumulator; the checksum is the final value of the accumulator.  Using this routine provides a method of checking whether the contents of an area of memory have changed since a prior checksum was calculated.  This routine is optimized for speed, and executes at 0.7 microseconds per byte.  The number of bytes d must be even; otherwise, an additional byte is included in the checksum.  The result is undefined if d = 0 or 1.

 
CALL

CALL ( <function.name> -- )

Removes <name> from the input stream and compiles a call to <function.name> into the current definition, where <function.name> is the name of an executable FORTH or assembly coded routine.  Typically used in an assembly coded definition.

 
CASE

CASE ( n -- n )

Used inside a colon definition to mark the beginning of a CASE statement which implements a multi-decision control structure.  Use as:

n1 CASE
   n2 OF words to be executed if n1 = n2  ENDOF
   n3 OF words to be executed if n1 = n3  ENDOF
   n4 OF words to be executed if n1 = n4  ENDOF
   words to be executed if n1 does not equal n2 or n3 or n4
ENDCASE

An error is issued if CASE and ENDCASE are not properly paired in a definition.

See also ENDCASE, OF, ENDOF, RANGE.OF, and URANGE.OF

Attributes: C, I

 
CAT

CAT ( xaddr.of.lstring\umax.count\xstring.to.add\+count.to.add\eol -- )

Important: The specifed umax.count must be four bytes less than the available space at xaddr.of.lstring, to account for:

  • Two-byte count at the beginning of the buffer;
  • Null byte written beyond the end of the resulting string; and
  • A known bug involving two-byte eol values; see below.

A QED-Forth “long string” contains a 2-byte count followed by the string contents.  CAT concatenates onto the “long string” at xaddr.of.lstring the +count.to.add bytes in the string specified by xstring.to.add, plus the specified eol (end of line) sequence and a terminating null byte (not included in any count), and updates the 16-bit count located in the first 2 bytes at xaddr.of.lstring.  The available long string buffer starting at xaddr.of.lstring must be 4 bytes larger than the specified umax.count to allow for the 2-byte count, the terminating null byte, and an extra byte that may be written due to a known bug (see below).  The string to be added must have a positive count ≤ 32767 bytes. 

The 16-bit eol parameter can specify 1 or 2 characters.  If eol = -1, no eol data is stored in the string.  If the most significant (ms) byte of eol is non-zero, two bytes are stored: first the ms byte, then the least significant byte.  Typical eol parameters include 'crlf' = 0x0D0A, 'cr' = 0x0D, or the null character 0x00 (unnecessary with CAT since a null character is always added anyway).

If the long string resulting from concatenating xstring.to.add to the existing contents of xaddr.of.lstring would be longer than umax.count, the result is truncated to umax.count bytes plus the terminating null character.

Known Bug: If the length of the resulting string after appending xstring.to.add is equal to umax.count, no eol bytes are written. However, if the resulting string is at least one byte shorter than umax.count, the eol sequence is written, regardless of whether it is one or two bytes. In the case where one byte is available and eol is two bytes, both bytes will be written, and the stored count at the beginning of xaddr.of.lstring will be incremented to one more than umax.count.

The terminating null byte is appended to the resulting long string regardless of whether or not there is room for it according to umax.count, and is not included in the count at the beginning of xaddr.of.lstring.

NOTE: If assembling a long string from scratch, remember to zero the first 2 bytes (16-bit count) of xaddr.of.lstring before the first call to this routine.

See also LPARSE

 
CFA.FOR

CFA.FOR ( -- xcfa )

Compile Time: ( <name> – )

Removes <name> from the input stream and returns <name>'s extended code field address xcfa.  xcfa is the first byte of executable code associated with <name>'s definition.  If in execution mode, leaves the xcfa on the stack.  If in compilation mode, compiles the xcfa as a 2-cell literal in the current definition; the xcfa is pushed to the stack when the definition later executes.  An error occurs if no <name> is given or if <name> cannot be found in the dictionary. In compilation mode, an error occurs if <name> is in a different library or application segment than the segment that CFA.FOR is located in; the error message is Can't compile deferred lib-to-lib call. To resolve this condition, simply define a colon definition synonym for <name> in the current library or application segment, and use the synonym as the argument of CFA.FOR.
Pronunciation: c-f-a-for
Attributes: I

 
CFA>NAME

CFA>NAME ( xcfa -- )

Prints the name of the word associated with the specified extended code field address xcfa.  Useful for error diagnostics to print the name of the word in which an error occurs.  The name is printed as ?NAME? if no name corresponding to xcfa is found in the dictionary.
Pronunciation: c-f-a-to-name

 
CFA>NFA

CFA>NFA ( xcfa -- [xnfa] or [0\0] )

Given the extended code field address xcfa of a word in the dictionary, searches the dictionary and returns the extended name field address xnfa of the word.  If the name associated with xcfa cannot be found in the dictionary, returns 0\0. xcfa is the first byte of executable machine code associated with the definition, and xnfa is the count byte of the word's header.

See also CFA.FOR, ID. and NFA.FOR
Pronunciation: c-f-a-to-n-f-a

 
CFA>PFA

CFA>PFA ( xcfa -- [xpfa] or [0\0] )

Given the extended code field address xcfa of a word in the dictionary, searches the dictionary and returns the extended parameter field address xpfa of the word.  If the name associated with xcfa cannot be found in the dictionary or if it does not have a parameter field, returns 0\0.

See also CFA.FOR and '
Pronunciation: c-f-a-to-p-f-a

 
CHANGE.BITS

CHANGE.BITS ( byte1\byte2\xaddr -- | byte1 = data; byte2 = mask )

At the byte specified by xaddr, modifies the bits specified by 1's in byte2 to have the values indicated by the corresponding bits in byte1. In other words, byte2 serves as a mask which specifies the bits at xaddr that are to be modified, and byte1 provides the data which is written to the modified bits.  Disables interrupts for 0.65 microseconds to ensure an uninterrupted read/modify/write operation.

 
CHANGE.NFA.TYPE

CHANGE.NFA.TYPE ( n1\n2\xnfa -- | n1=data, n2 = mask )

The 16-bit input parameters n1 and n2 are the data and mask, respectively, used to modify the contents of the function.type (msbyte) and header.type (lsbyte) of the header specified by xnfa.  Bits corresponding to 1’s in n2 are modified to have the corresponding bit values of n1. Bits corresponding to 0’s in n2 are unchanged.  This low-level utility is typically not used by the programmer.

 
CHAR.SIZE

CHAR.SIZE ( -- n )

Returns the constant value 1 which is the number of bytes in a parameter of type char that is passed to or returned by a C-callable function.  This size specifier is used in the PARAMS( statement that describes the input and output parameters of a C-callable function.  Because all 1-byte parameters are promoted to 2 bytes by the C compiler, a char-size parameter may be declared using either CHAR.SIZE or INT.SIZE.  Consult the glossary entry for PARAMS(

 
CHARS/LINE

CHARS/LINE ( -- xaddr )

A 16-bit user variable that contains the maximum number of characters that can be received by EXPECT.  Also used by matrix print words M. M.. and M.PARTIAL to format their output. CHARS/LINE is initialized to a default value of 96 upon each COLD restart, and its value should not be increased above 96 unless the TIB is moved from its default location.
Pronunciation: chars-per-line
Attributes: U

 
CHECKSTART.DISABLE

CHECKSTART.DISABLE ( -- )

Undoes the effect of CHECKSTART.ENABLE.  Implementation detail: Erases 8 bytes starting at 0xBFF0 on page 0x37 in on-chip flash.

See also CHECKSTART.ENABLE

 
CHECKSTART.ENABLE

CHECKSTART.ENABLE ( xcfa\u -- )

Configures a checksum calculation that protects the boot vectors.  When this function is executed, CALC.CHECKSUM is invoked to calculate a 16-bit checksum starting at xcfa over a range of u bytes, where u must be even.  The checksum region may cross one or more page boundaries.  The calculated checksum is stored along with xcfa and u in a structure in flash memory that is checked by ABORT at runtime upon every subsequent power-up and restart.  The checksum is recalculated at runtime and compared with the stored checksum.  If the checksums match, any boot vectors that were set up using SET.BOOT.VECTOR are executed.  If the checksums do not match, no boot vectors are executed.  This function is typically not used by the end customer; rather, it is typically invoked as part of a kernel extension package that sets up boot vectors and invokes this routine to provide checksum protection at runtime.  This prevents the operating system from trying to execute boot vectors that have been erased or otherwise altered.

See also CHECKSTART.DISABLE

Implementation detail: Starting at address 0xBFF0 on page 0x37 in on-chip flash, stores the 2-byte pre-calculated checksum, the 2-byte number of bytes u, followed by the 4-byte xcfa with the most significant byte set to 0x13.

 
CLEAR.BITS

CLEAR.BITS ( byte1\xaddr -- )

For each bit of byte1 that is set, clears the corresponding bit of the 8 bit value at xaddr.  Disables interrupts for 0.5 microseconds to ensure an uninterrupted read/modify/write operation.

See also SET.BITS

 
CLEAR.BOOT.VECTORS

CLEAR.BOOT.VECTORS ( -- )

Erases all boot vectors so that none will be executed at reset or restart.  This function is called during a factory cleanup, but it is not called by NO.AUTOSTART.  To temporarily disable boot vectors without erasing them, use DISABLE.BOOT.VECTORS, which can be reversed using ENABLE.BOOT.VECTORS.  These functions are typically invoked interactively from the QED-Forth prompt.

Implementation detail: Writes 0 to the most significant byte in each location in the vector table to disable all 16 boot vectors at 0xBFB0 to 0xBFFF in page 0x37 on-chip flash memory.

See also SET.BOOT.VECTOR

 
CLOCK.MONITOR.ID

CLOCK.MONITOR.ID ( -- n )

Returns the interrupt identity code for the clock monitor interrupt.  Used as an argument for ATTACH.
Pronunciation: clock-monitor-i-d

 
CMOVE

CMOVE ( xaddr1\xaddr2\u -- | xaddr1=src, xaddr2=dest, u = byte count )

If u is greater than 0, u consecutive bytes are copied from addresses starting at xaddr1 to addresses starting at xaddr2. The source and destination extended addresses may be located on different pages and the move may cross page boundaries.  If the source and destination regions overlap and xaddr1 < xaddr2, CMOVE starts at high memory and moves toward low memory to avoid propagation of the moved contents.  CMOVE always moves the contents in such a way as to avoid memory propagation, except that attempts to perform an overlapping-region copy to or from the kernel flash starting at the precise address 0xC000 may result in propagation.  Speed is approximately 2.3 microseconds per byte.

See also CMOVE.MANY
Pronunciation: c-move

 
CMOVE.IN.PAGE

CMOVE.IN.PAGE ( addr1\addr2\u\page -- | addr1=src, addr2=dest, u = byte count )

If u is greater than 0, u consecutive bytes starting at addr1 are copied to the destination addresses starting at addr2 on the specified page.  If the source and destination regions overlap and addr1 < addr2, CMOVE.IN.PAGE starts at high memory and moves toward low memory to avoid propagation of the moved contents.  CMOVE.IN.PAGE always moves the contents in such a way as to avoid memory propagation.  Speed is approximately 0.2 microseconds per byte.
Pronunciation: c-move-in-page

 
CMOVE.MANY

CMOVE.MANY ( xaddr1\xaddr2\d -- | xaddr1=src, xaddr2=dest, d = byte count )

If the 32-bit byte count d is greater than 0, d consecutive bytes are copied from addresses starting at xaddr1 to addresses starting at xaddr2. The source and destination extended addresses may be located on different pages and the move may cross page boundaries.  If the source and destination regions overlap and xaddr1 < xaddr2, CMOVE.MANY starts at high memory and moves toward low memory to avoid propagation of the moved contents.  CMOVE.MANY always moves the contents in such a way as to avoid memory propagation, except that attempts to perform an overlapping-region copy to or from the kernel flash starting at the precise address 0xC000 may result in propagation.  Speed is approximately 2.3 microseconds per byte.
Pronunciation: c-move-many

 
CMOVE.MANY.CHECK

CMOVE.MANY.CHECK ( xaddr1\xaddr2\d -- flag | xaddr1=src, xaddr2=dest, d = byte count )

Performs the action of CMOVE.MANY (see its glossary entry), and then calculates the source and destination checksums, returning a true flag if they are equal, or a false flag if they are not equal.  The source checksum is calculated by calling CALC.CHECKSUM.MANY with parameters xaddr1 and d, and the destination checksum is calculated by calling CALC.CHECKSUM.MANY with parameters xaddr2 and d.  Note that the full CMOVE.MANY operation is performed whether d is even or odd, but the checksum count is forced via truncation to be even, which means that the last byte of an odd-count move is not checksum-verified.

 
CODE

CODE ( <name> -- )

Begins an assembly coded definition.  Removes <name> from the input stream and creates a header for <name> that cannot be found in the dictionary until END.CODE executes.  Executes ASSEMBLER so that the assembler mnemonics can be found by the interpreter.  The assembly mnemonics between CODE and END.CODE form the body of the definition.

See also XCODE, RCODE and END.CODE

Attributes: D

 
COLD

COLD ( -- )

Disables interrupts and restarts the QED-Forth system and initializes all of the user variables to their default values.  Initializes the following machine registers:

SYNR    REFDV   RTICTL  SPI0CR1  PPSS   PERS   PTS     DDRS   PLLCTL  CLKSEL
INITRM  INITRG  INITEE  MISC     PEAR   MODE   EBICTL  PPAGE  RDRIV   TSCR1
TSCR2   PACTL   RDRS    WOMS     DDRJ   PERJ   PPSJ    MODRR  SCI0BDH SCI0BDL
SCI0CR1 SCI1BDH SCI1BDL SCI1CR1

Initializes the vectors of the vital interrupts if INIT.VITAL.IRQS.ON.COLD has been executed (see its glossary entry).  Initializes the user pointer UP and writes initial values to each system user variable in the default forth task.  Sets the memory map as follows:

DP: 0x1D8000 NP: 0x1D9000 VP: 0x2000 EEP: 0x680

HEAP: 0x188000 to 0x1CBFFF

Initializes the timeslice increment to 1.024 msec, and initializes the system resource variables.  Calls FP.DEFAULTS, BUILD.HASH.TABLE, and copies from xflash to RAM by invoking LOAD.PAGES to copy the memory pages designated by the LOAD.PAGES.AT.STARTUP command(s).  Unless an autostart is present, this routine prints the coldstart message.  Unless an autostart is present or NO.STATUS.AT.STARTUP has been executed, this routine executes REPORT.PAGES.LOADED to summarize the flash-to-ram pages loaded, and executes .MAP to summarize the memory map.  Calls ABORT which clears the stacks and calls either the QED-Forth interpreter or an autostart routine that has been installed using PRIORITY.AUTOSTART:, IS.PRIORITY.AUTOSTART, AUTOSTART:, or IS.AUTOSTART.  If COLD.ON.RESET has been executed, every reset or power-up will invoke a COLD (as opposed to a WARM) initialization sequence.  Consult the documentation for more information about cold restarts.

See also QUIET.COLD

 
COLD.ON.RESET

COLD.ON.RESET ( -- )

Initializes a flag in EEPROM that causes subsequent resets to execute a cold restart (as opposed to the standard warm-or-cold restart).  This option is useful to help bullet-proof turnkeyed systems that have an autostart word installed; any error or reset causes a full COLD restart which initializes all user variables, after which the autostart routine completes the system initialization and enters the application routine.

See also STANDARD.RESET

 
COMMON.PAGE

COMMON.PAGE ( -- page | page = 0 )

Places a zero onto the data stack; this represents the default page assigned to the common memory (i.e., addresses below 0x8000 or at/above 0xC000).

 
COMPILE

COMPILE ( <name> -- )

Removes the next <name> from the input stream.  Use as:

: <namex>
   ... COMPILE <name> ...
;

where <namex> is typically immediate and <name> is typically not immediate.  Compiles into the current definition code that will cause <name> to be compiled when <namex> is executed.  That is, COMPILE defers the compilation of <name> until <namex> executes.

Attributes: C, I

 
COMPILE.CALL

COMPILE.CALL ( xcfa -- )

Compiles a call to the assembly language subroutine whose first byte of executable machine code is stored at xcfa.  This low-level utility is used by the compiler and is typically not invoked by the programmer.  This routine is smart with respect to compiling calls to routines in common or paged memory, and compiling calls with relative or absolute paging depending on the circumstances.  This routine must not be called if the required invocation is a library-to-library call (i.e., if bit6 of the msbyte of xcfa is set and if LIBRARY.IS.COMPILING is true); use COMPILE.LIB2LIB.CALL for these cases.  If the target xcfa is to be accessed via a page-relative call, the msbit of xcfa is set by FIND, and this routine compiles a page-relative call referenced to DP.PAGE.  Otherwise a page-absolute call is compiled.  If the target xcfa is in a non-local library segment and the page-relative bit (the msbit of the xcfa) is 0, a page-absolute call is compiled even if the current DP.PAGE equals target xcfa page, because our segment might later move with respect to the library declared with a REQUIRES.FIXED statement.  All intra-page calls use relative addressing unless the target is in a non-local library.  All inter-page calls use absolute 16-bit addressing and either relative or absolute page specification, depending on the state of the page-relative bit.

 
COMPILE.LIB2LIB.CALL

COMPILE.LIB2LIB.CALL ( segment.xhandle\addr.offset\page.offset -- )

Compiles a call to the assembly language subroutine specified by addr.offset and page.offset in a remote library.  The input parameters are typically returned by LIB2LIB.CFA.FOR, and the address and page offsets are relative to the segment base xaddress of the segment that contains the target function.  This low-level routine is used only if LIBRARY.IS.COMPILING is true, and if the target xcfa is in a library (indicated by bit6 of the msbyte of the page.offset = 1).  The segment.xhandle parameter is the xaddress in the segment structure of the currently compiling segment that contains the index of the target function that is specified by addr.offset and page.offset.  The segment.xhandle is initialized by either the REQUIRES.FIXED or the REQUIRES.RELATIVE statement when the library is being declared or loaded.
Pronunciation: compile-lib-to-lib-call

 
COMPLEMENT

COMPLEMENT ( w1 -- w2 )

Returns the ones complement of w1. That is, inverts each bit of w1 to produce w2.

 
COMPOSE.C.ASM.CODE

COMPOSE.C.ASM.CODE ( <"filename.s"> -- )

Prints (exports) the C assembly code definitions for the C-callable functions from all of the defined non-kernel segments, and, using the #saveto command, directs the printed contents to the specified "filename.s", where .s is the standard extension of the GNU tools for an assembly file.  The resulting file is used in conjuction with the *.h C header file (created by COMPOSE.C.HEADERS) to enable access from C of functions defined using Forth.  This routine prints the C-assembly code for all the C-callable functions from the segment.header for segment number 1 until the LATEST defined function.  Aborts if no segments have been defined.  This routine does not print the S-records that contain the executable segment code; to accomplish this, see COMPOSE.C.INSTALLER.  This routine requires at least 15.6 Kbytes available in the current heap for temporary storage of an array. <"filename.s"> must be on the same line as COMPOSE.C.ASM.CODE, and "filename.s" must be enclosed in quotes; all characters between the quotes are part of the filename.  If the null filename "" is specified, then the #saveto and #endsaveto statements are suppressed.  To compose the C assembler code for a single library or application segment, see COMPOSE.C.ASM.CODE.FOR.  See also the glossary entries for the other COMPOSE routines.

Example: This example shows the form of the output generated by this function.

COMPOSE.C.ASM.CODE     "allc.s"      \ export C assembly code
#saveto "allc.s"
.include "mosaic_asm_macros.s"
 mosaic_driver_name "ALLC"
 mosaic_new_segment
 mosaic_driver_codespace 0x30
 mosaic_driver_varspace  0x23
 mosaic_driver_eespace   0x1f
 mosaic_driver_namespace 0xc4
 mosaic_driver_checksum  0xC959
 .sect .text
 .globl MultiplyThem
 .type MultiplyThem,@function
 .far MultiplyThem
MultiplyThem:
 jsr 0xC000
 .2byte 0x2000
 .byte 0x83
 .2byte MYLIB_ARRAY_ADDR
 .byte 0x0
 .2byte 0x2F
 rtc
 .size MultiplyThem, .-MultiplyThem
#endsaveto

Pronuncation: compose-c-assembly-code
Attributes: M, S

 
COMPOSE.C.ASM.CODE.FOR

COMPOSE.C.ASM.CODE.FOR ( <segment.name> <"filename.s"> -- )

Prints (exports) the C assembly code definitions for the C-callable functions from the specified segment, and, using the #saveto command, directs the printed contents to the specified "filename.s", where .s is the standard extension of the GNU C programming environment for an assembly file.  The resulting file is used in conjuction with the *.h C header file (created by COMPOSE.C.HEADERS.FOR) to enable access from C of functions defined using Forth.  Aborts if the specified segment was not properly terminated with an END.SEGMENT statement, unless <segment.name> is the currently compiling segment, in which case all C-callable headers in the segment up until the LATEST defined function are included.  This routine does not print the S-records that contain the executable segment code; to accomplish this, see COMPOSE.C.INSTALLER.FOR.  This routine requires at least 15.6 Kbytes available in the current heap for temporary storage of an array. <segment.name> and <"filename.s"> must be on the same line as COMPOSE.C.ASM.CODE.FOR, and "filename.s" must be enclosed in quotes; all characters between the quotes are part of the filename.  If the null filename "" is specified, then the #saveto and #endsaveto statements are suppressed.  See also the glossary entries for the other COMPOSE routines, and see COMPOSE.C.ASM.CODE for an example of use.

Pronuncation: compose-c-assembly-code-for
Attributes: M, S

 
COMPOSE.C.HEADERS

COMPOSE.C.HEADERS ( <"filename.h"> -- )

Prints (exports) the C headers for the C-callable functions from all of the defined non-kernel segments, and, using the #saveto command, directs the printed contents to the specified "filename.h", where .h is the standard extension of the C programming environment for a header file.  The exported text comprises function prototypes, variable macros, EEPROM variable macros, and header text declared using the PROTOTYPE: VPROTOTYPE: EEPROTOTYPE: and C.HEADERS: commands, respectively.  The resulting file is used in conjuction with the *.s assembly file to enable access from C of functions defined using Forth.  This routine prints the headers for all the C-callable functions from the segment.header for segment number 1 until the LATEST defined function.  Aborts if no segments have been defined.  To print the C headers for a single specified application or library segment, see COMPOSE.C.HEADRS.FOR.  This routine does not print the S-records that contain the executable segment code; to accomplish this, see COMPOSE.C.INSTALLER.  This routine requires at least 15.6 Kbytes available in the current heap for temporary storage of an array. <"filename.h"> must be on the same line as COMPOSE.C.HEADERS, and "filename.h" must be enclosed in quotes; all characters between the quotes are part of the filename.  If the null filename "" is specified, then the #saveto and #endsaveto statements are suppressed.  See COMPOSE.C.HEADERS.FOR for an example of use, and See the glossary entries for the other COMPOSE routines.

Attributes: M, S

 
COMPOSE.C.HEADERS.FOR

COMPOSE.C.HEADERS.FOR ( <segment.name> <"filename.h"> -- )

Prints (exports) the C headers for the C-callable functions from the specified segment, and, using the #saveto command, directs the printed contents to the specified filename.h, where .h is the standard extension of the C programming environment for a header file.  The exported text comprises function prototypes, variable macros, EEPROM variable macros, and header text declared using the PROTOTYPE: VPROTOTYPE: EEPROTOTYPE: and C.HEADERS: commands, respectively.  The resulting file is used in conjuction with the *.s assembly file to enable access from C of functions defined using Forth.  Aborts if the specified segment was not properly terminated with an END.SEGMENT statement, unless <segment.name> is the currently compiling segment, in which case all C-callable headers in the segment up until the LATEST defined function are included.  This routine does not print the S-records that contain the executable segment code; to accomplish this, see COMPOSE.C.INSTALLER.FOR.  This routine requires at least 15.6 Kbytes available in the current heap for temporary storage of an array. <segment.name> and <"filename.h"> must be on the same line as COMPOSE.C.HEADERS, and "filename.h" must be enclosed in quotes; all characters between the quotes are part of the filename.  If the null filename "" is specified, then the #saveto and #endsaveto statements are suppressed.  See also the glossary entries for the other COMPOSE routines.

Example: This example shows the form of the output generated by this function.

COMPOSE.C.HEADERS.FOR MYLIB      "mylib.h"     \ export C headers for mylib
#saveto "mylib.h"
#ifndef MYLIB_ARRAY_ADDR
#define MYLIB_ARRAY_ADDR (SEG_ARRAY_ADDR(MYLIB_ID))
SET_GLOBAL_SYMBOL("MYLIB_ARRAY_ADDR",MYLIB_ARRAY_ADDR);
MOSAIC_DRIVER_NAME("MYLIB");
#define MYLIB_CODE_SIZE 0x108
#define MYLIB_VAR_SIZE 0xA
#define MYLIB_EEVAR_SIZE 0x6
#define MYLIB_NAME_SIZE 0x230
#define MYLIB_COMPILATION_START_ADDR 0x801A
#define MYLIB_CODE_CHECKSUM 0xA885
extern void __attribute__((far))  MagicNumber ( );
struct UserStruct
   { int next_task;  // round robin tasking
     xaddr sp_save;
   };
extern float __attribute__((far))  MultiplyThem ( char c1, int i1, float f1 );
extern long __attribute__((far))  SayLong ( );
#define  libvar1   (* (xaddr*) (SEG_VARSTART(MYLIB_ID) + 0x0 ))
#define  libeevar1 (* (float*) (SEG_EEVARSTART(MYLIB_ID) + 0x0 ))
#endif

Attributes: M, S

 
COMPOSE.C.INSTALLER

COMPOSE.C.INSTALLER ( n\flag <”filename.cin”> -- )

Prints (exports) the C installer file for all of the defined non-kernel segments starting with segment #1, and, using the #saveto command, directs the printed contents to the specified "filename.cin" or "filename.qcin" file as explained below.  The input parameter n is a place specifier that should equal one of the constants TO.HERE, IN.PLACE, or USER.SPECIFIED.  The input flag parameter specifies whether the quick output format should be used; if the flag is true, the code S-records are not included in the file, and this speeds the downloading of segments that have previously been loaded into memory on the controller board.  The exported text comprises the code preamble, the optional S-record code dump (present only if the input flag is false), segment declarations (created by LIBRARY or APPLICATION statements in the source code), END.LOAD.SEGMENT declarations (created by END.SEGMENT statements in the source code), requires declarations (created by REQUIRES.FIXED and REQUIRES.RELATIVE statements), and an optional DATE/TIME: directive.  The resulting file is downloaded to the board (typically via the terminal’s #include directive) to enable a C program to access previously compiled library and/or application segments.  Aborts if no segments have been defined, or if any of the segments has not been properly terminated with an END.SEGMENT statement.  This routine requires at least 15.6 Kbytes available in the current heap for temporary storage of an array. <"filename"> must be on the same line as COMPOSE.C.INSTALLER, and "filename" must be enclosed in quotes; all characters between the quotes are part of the filename.  The default file extension for a C install file is *.cin; if the quick flag input parameter is true, then the *.qcin (“quick C installer”) extension should be used.  If the null filename "" is specified, then the #saveto and #endsaveto statements are suppressed.  When building (exporting) relocatable library segments, the recommended place-specifier is TO.HERE.  The TO.HERE mode allows the segments to be loaded at a later time along with other libraries and applications; the code will be placed at the load-time dictionary pointer DP contents, and the dictionary pointer will be automatically advanced at load time.  If you want the exported segments to remain in a fixed location such as a specified page in on-chip flash, use the IN.PLACE specifier.  The USER.SPECIFIED parameter provides flexibility in locating the segments, but requires that you explicity place a starting code xaddress on the stack before the loading process begins; for this reason, the USER.SPECIFIED parameter is not recommended except in special circumstances.

Notes: Before sending the file created by this routine to the board, it is a good idea to call COLD to wipe out the names of the original segment headers.  Make sure that the DP (dictionary pointer) is set to the desired starting address and page; it can be in RAM or in onchip flash.  The NP (names pointer) must point to valid paged or common RAM, and the VP (variable pointer) and EEP (EEPROM Pointer) must point to valid common RAM.  Consult the glossary entry for COMPOSE.C.INSTALLER.FOR for an example of use.

 
COMPOSE.C.INSTALLER.FOR

COMPOSE.C.INSTALLER.FOR ( n\flag <segment.name> <”filename.cin”> -- )

Prints (exports) the C installer file for the specified segment and, using the #saveto command, directs the printed contents to the specified "filename.cin" or "filename.qcin" as explained below.  The input parameter n is a place specifier that should equal one of the constants TO.HERE, IN.PLACE, or USER.SPECIFIED.  The input flag parameter specifies whether the quick output format should be used; if the flag is true, the code S-records are not included in the file, and this speeds the downloading of segments that have previously been loaded into memory on the controller board.  The exported text comprises the code preamble, the optional S-record code dump (present only if the input flag is false), segment declaration (created by LIBRARY or APPLICATION statements in the source code), END.LOAD.SEGMENT declaration (created by END.SEGMENT statements in the source code), requires declarations (created by REQUIRES.FIXED and REQUIRES.RELATIVE statements), and an optional DATE/TIME: directive.  The resulting file is downloaded to the board (typically via the termiinal’s #include directive) to enable a C program to access a previously compiled library or application segment.  Aborts if <segment.name> is not a valid segment, or if it has not been properly terminated with an END.SEGMENT statement.  This routine requires at least 15.6 Kbytes available in the current heap for temporary storage of an array. <segment.name> and <"filename"> must be on the same line as COMPOSE.C.INSTALLER, and "filename" must be enclosed in quotes; all characters between the quotes are part of the filename.  The default file extension for a C install file is *.cin; if the quick flag input parameter is true, then the *.qcin (“quick C installer”) extension should be used.  If the null filename "" is specified, then the #saveto and #endsaveto statements are suppressed.  When building (exporting) a relocatable segment, the recommended place-specifier is TO.HERE.  The TO.HERE mode allows the segments to be loaded at a later time along with other libraries and applications; the code will be placed at the load-time dictionary pointer DP contents, and the dictionary pointer will be automatically advanced at load time.  If you want the exported segment to remain in a fixed location such as a specified page in on-chip flash, use the IN.PLACE specifier.  The USER.SPECIFIED parameter provides flexibility in locating the segment, but requires that you explicity place a starting code xaddress on the stack before the loading process begins; for this reason, the USER.SPECIFIED parameter is not recommended except in special circumstances.

Notes: Before sending the file created by this routine to the board, it is a good idea to call COLD to wipe out the names of the original segment headers.  Make sure that the DP (dictionary pointer) is set to the desired starting address and page; it can be in RAM or in onchip flash.  The NP (names pointer) must point to valid paged or common RAM, and the VP (variable pointer) and EEP (EEPROM Pointer) must point to valid common RAM.  See also the glossary entry for COMPOSE.C.INSTALLER.

Example: This example shows the form of the output generated by this function.

COMPOSE.C.HEADER.FOR "mylib.cin" \ export C install file for mylib

#saveto "mylib.cin"
\ Dumping 0x108 byte library MYLIB from xaddr 0x4801A
HERE DIN 0x108 0x801A 0xFFFF SEGMENT.BUMP XDUP DP X!
2 NEEDED XDUP RECEIVE.HE
xS00900004845414445524D
S9030000FC
( xbase.addr-- )   DIN 0x108 0xA 0x6  ( xaddr\d_seg_size\varsize\eesize -- )
LOAD.LIBRARY MYLIB
END.LOAD.SEGMENT
DATE/TIME: MYAPP ${Mon 11/23/05 12:05:32 PST}$

Attributes: M, S

 
COMPOSE.FLASH.INSTALLER

COMPOSE.FLASH.INSTALLER ( flag "filename" -- )

A low-level utility used to capture as a reloadable file one or more segments that have been relocated to the processor’s onchip flash.  Typically used to move a library to be flash resident, or to compile a slave application on the master on a dual processor platform such as the PDQScreen, relocate it to master flash, then dump out a file and send it to the slave to run as the slave application.  Prints (exports) an installer file for all of the defined non-kernel segments starting with segment #1, and, using the #saveto command, directs the printed contents to the specified "filename.fin" or "filename.qfin" file as explained below.  The input flag parameter specifies whether the quick output format should be used; if the flag is true, the code and header S-records are not included in the file, and this speeds the downloading of segments that have previously been loaded into memory on the controller board.  For each segment, the exported text comprises an instruction to set the DP and NP, optional S-record header and code dumps (present only if the input flag is false), segment declarations (LOAD.LIBRARY or LOAD.APPLICATION statements), requires declarations (REQUIRES.FIXED and REQUIRES.RELATIVE statements), and an END.LOAD.SEGMENT declaration.  This routine requires at least 15.6 Kbytes available in the current heap for temporary storage of an array. <"filename"> must be on the same line as COMPOSE.FLASH.INSTALLER, and "filename" must be enclosed in quotes; all characters between the quotes are part of the filename.  The default file extension for a Forth install file is *.fin; if the quick flag input parameter is true, then the *.qfin (“quick Forth installer”) extension should be used.  If the null filename "" is specified, then the #saveto and #endsaveto statements are suppressed.  Before sending the file created by this routine to the board, it is a good idea to call COLD to wipe out the names of the original segment headers.

Example of use: Load the segment(s) as usual in RAM.  In this example, the segment is called myapp, and its code is originally compiled on page 0. Then, to relocate myapp to pages 30 (code) and 31 (heads), do the following:

0x30 RELOCATE: myapp      ( -- success? )
0x31 MOVE.HEADERS myapp      \ only moves heads for 1 segment; repeat as needed
1 RESTORE.SEGMENT.NAMES      \ install relocated names
0 COMPOSE.FLASH.INSTALLER "myapp_flash.fin"

Note that the top level word in the segment should typically call

( last.segment.index -- ) RESTORE.SEGMENT.NAMES

to restore the runtime access to headers; see its glossary entry for details.

 
COMPOSE.FORTH.INSTALLER

COMPOSE.FORTH.INSTALLER ( n\flag <”filename.fin”> -- )

Prints (exports) the Forth installer file for all of the defined non-kernel segments starting with segment #1, and, using the #saveto command, directs the printed contents to the specified "filename.fin" or "filename.qfin" file as explained below.

The input parameter n is a place specifier that should equal one of the constants TO.HERE, IN.PLACE, or USER.SPECIFIED.  The input flag parameter specifies whether the quick output format should be used; if the flag is true, the code S-records are not included in the file, and this speeds the downloading of segments that have previously been loaded into memory on the controller board.

The exported text comprises:

  • the code preamble,
  • the optional S-record code dump (present only if the input flag is false),
  • segment declarations (created by LIBRARY or APPLICATION statements in the source code),
  • END.LOAD.SEGMENT declarations (created by END.SEGMENT statements in the source code),
  • requires declarations (created by REQUIRES.FIXED and REQUIRES.RELATIVE statements),
  • a MAKE.HEADER statement for each function that was declared while the system variable PRIVATE was OFF,
  • header text declared using the FORTH.HEADERS: command, and,
  • an optional DATE/TIME: directive.

The resulting file is downloaded to the board (typically via the terminal’s #include directive) to enable a Forth program to access previously compiled library and/or application segments.  Aborts if no segments have been defined, or if any of the segments has not been properly terminated with an END.SEGMENT statement.

This routine requires at least 15.6 Kbytes available in the current heap for temporary storage of an array. <"filename"> must be on the same line as COMPOSE.FORTH.INSTALLER, and "filename" must be enclosed in quotes; all characters between the quotes are part of the filename.  The default file extension for a Forth install file is *.fin; if the quick flag input parameter is true, then the *.qfin (“quick Forth installer”) extension should be used.  If the null filename "" is specified, then the #saveto and #endsaveto statements are suppressed.

When building (exporting) relocatable library segments, the recommended place-specifier is TO.HERE.  The TO.HERE mode allows the segments to be loaded at a later time along with other libraries and applications; the code will be placed at the load-time dictionary pointer DP contents, and the dictionary pointer will be automatically advanced at load time.  If you want the exported segments to remain in a fixed location such as a specified page in on-chip flash, use the IN.PLACE specifier.  The USER.SPECIFIED parameter provides flexibility in locating the segments, but requires that you explicitly place a starting code xaddress on the stack before the loading process begins; for this reason, the USER.SPECIFIED parameter is not recommended except in special circumstances.

Notes: Before sending the file created by this routine to the board, it is a good idea to call COLD to wipe out the names of the original segment headers.  Make sure that the DP (dictionary pointer) is set to the desired starting address and page; it can be in RAM or in onchip flash.  The NP (names pointer) must point to valid paged or common RAM, and the VP (variable pointer) and EEP (EEPROM Pointer) must point to valid common RAM.

Consult the glossary entry for COMPOSE.FORTH.INSTALLER.FOR for an example of use.  The file created by COMPOSE.C.INSTALLER is similar to the file created by COMPOSE.FORTH.INSTALLER, with the exception that the C version omits the Forth MAKE.HEADER and header text declarations to save memory.

 
COMPOSE.FORTH.INSTALLER.FOR

COMPOSE.FORTH.INSTALLER.FOR ( n\flag <segment.name> <”filename.fin”> -- )

Prints (exports) the Forth installer file for the specified segment and, using the #saveto command, directs the printed contents to the specified "filename.fin" or "filename.qfin" as explained below.

The input parameter n is a place specifier that should equal one of the constants TO.HERE, IN.PLACE, or USER.SPECIFIED.  The input flag parameter specifies whether the quick output format should be used; if the flag is true, the code S-records are not included in the file, and this speeds the downloading of segments that have previously been loaded into memory on the controller board.  The exported text comprises the following:

  • a code preamble,
  • the optional S-record code dump (present only if the input flag is false),
  • segment declaration (created by LIBRARY or APPLICATION statements in the source code),
  • END.LOAD.SEGMENT declaration (created by END.SEGMENT statements in the source code),
  • requires declarations (created by REQUIRES.FIXED and REQUIRES.RELATIVE statements),
  • a MAKE.HEADER statement for each function that was declared while the system variable PRIVATE was OFF,
  • header text declared using the FORTH.HEADERS: command, and,
  • an optional DATE/TIME: directive.

The resulting file is downloaded to the board (typically via the termiinal’s #include directive) to enable a forth program to access a previously compiled library or application segment.  Aborts if <segment.name> is not a valid segment, or if it has not been properly terminated with an END.SEGMENT statement.

This routine requires at least 15.6 Kbytes available in the current heap for temporary storage of an array. <segment.name> and <"filename"> must be on the same line as COMPOSE.FORTH.INSTALLER, and "filename" must be enclosed in quotes; all characters between the quotes are part of the filename.  The default file extension for a Forth install file is *.fin; if the quick flag input parameter is true, then the *.qfin (“quick Forth installer”) extension should be used.  If the null filename "" is specified, then the #saveto and #endsaveto statements are suppressed.

When building (exporting) a relocatable segment, the recommended place-specifier is TO.HERE.  The TO.HERE mode allows the segments to be loaded at a later time along with other libraries and applications; the code will be placed at the load-time dictionary pointer DP contents, and the dictionary pointer will be automatically advanced at load time.  If you want the exported segment to remain in a fixed location such as a specified page in on-chip flash, use the IN.PLACE specifier.

The USER.SPECIFIED parameter provides flexibility in locating the segment, but requires that you explicity place a starting code xaddress on the stack before the loading process begins; for this reason, the USER.SPECIFIED parameter is not recommended except in special circumstances.

Notes: Before sending the file created by this routine to the board, it is a good idea to call COLD to wipe out the names of the original segment headers.  Make sure that the DP (dictionary pointer) is set to the desired starting address and page; it can be in RAM or in onchip flash.  The NP (names pointer) must point to valid paged or common RAM, and the VP (variable pointer) and EEP (EEPROM Pointer) must point to valid common RAM.  See also the glossary entry for COMPOSE.FORTH.INSTALLER.  The file created by COMPOSE.C.INSTALLER.FOR is similar to the file created by COMPOSE.FORTH.INSTALLER.FOR, with the exception that the C version omits the Forth MAKE.HEADER and header text declarations to save memory.

Example: This example shows the form of the output generated by this function.

COMPOSE.FORTH.HEADER.FOR  "mylib.fin"   \ export forth install file for mylib
#saveto "mylib.fin"
\ Dumping 0x108 byte library MYLIB from xaddr 0x4801A
HERE DIN 0x108 0x801A 0xFFFF SEGMENT.BUMP XDUP DP X!
2 NEEDED XDUP RECEIVE.HE
xS00900004845414445524D
S9030000FC
( xbase.addr-- )   DIN 0x108 0xA 0x6  ( xaddr\d_seg_size\varsize\eesize -- )

LOAD.LIBRARY MYLIB

\ MAKE.HEADER statement stack picture:
( width\seg.index\fn{ms}hdr{ls}type\cfa.os\cfa.pg.os\#inputs\input.sizes--)
0x3F 0x41 0x8 0x20 0x0 0x0 0x0     MAKE.HEADER MAGIC.NUM
0x3F 0x41 0x8 0x2F 0x0 0x83 0x2000 MAKE.HEADER MULTIPLY.THEM
0x3F 0x41 0x10A 0xE0 0x0 0x0 0x0   MAKE.HEADER LIBVAR1
0x3F 0x41 0x20A 0xF8 0x0 0x0 0x0   MAKE.HEADER LIBEEVAR1
END.LOAD.SEGMENT
DATE/TIME: MYAPP ${Mon 11/23/05 12:05:32 PST}$

Attributes: M, S

 
CONSTANT

CONSTANT ( w <name> -- )

Removes the next <name> from the input stream and defines a child word called <name> which when executed leaves the value w on the data stack.  w is stored in the definitions area of the dictionary. <name> is referred to as a constant. Use as:

w CONSTANT <name>

CAUTION: When defining a relocatable library, do not store a fixed address in a constant if the address refers to a location that is subject to relocation (such as a pointer to a variable, eeprom variable, or a function address).  Instead, in these situations use segment-relocation-smart defining words such as VARIABLE and EEVARIABLE (and their variants such as XVARIABLE and EEXVARIABLE), V.INSTANCE:, D.INSTANCE:, and XCONSTANT.REL

Attributes: D

 
CONTEXT

CONTEXT ( -- xaddr )

A user variable that contains a 32-bit xhandle which in turn contains the xnfa of the top word in the vocabulary to be searched first.  Thus CONTEXT X@ returns the xhandle of the search vocabulary, and CONTEXT X@ X@ returns the xnfa of the top word in the search vocabulary.  In short, the contents of CONTEXT determine the search vocabulary.

See also FIND and CURRENT

Attributes: U

 
CONVERT

CONVERT ( ud1\xaddr1 -- ud2\xaddr2 )

Converts the numeric string starting at xaddr1+1 into the 32-bit number ud2. Conversion is accomplished by multiplying the double accumulator ud1 by the value in BASE and then adding the next digit from the string at xaddr1. Conversion ends when a non-convertible ASCII character is encountered in the string.  Isolated embedded commas are ignored and are not treated as a non-convertible character.  xaddr2 is the address of the first non-convertible character encountered in the string.  For example, executing

0\0  " 123 " CONVERT

leaves a 32-bit representation of the number 123 on the data stack under the xaddr of the terminating space in the string " 123 ".

 
COP.ID

COP.ID ( -- n )

Returns the interrupt identity code for the computer operating properly (COP) interrupt.  Used as an argument for ATTACH.
Pronunciation: cop-i-d

 
COPY.ARRAY

COPY.ARRAY ( array.xpfa1\array.xpfa2 -- )

Dimensions the destination array specified by array.xpfa2 and copies the contents of the source array specified by array.xpfa1 into the destination.  The source and destination can be in different heaps.

 
COPY.MATRIX

COPY.MATRIX ( matrix.xpfa1\matrix.xpfa2 -- )

Dimensions the destination matrix specified by matrix.xpfa2 and copies the contents of the source matrix specified by matrix.xpfa1 into the destination.  The source and destination can be in different heaps.

 
COUNT

COUNT ( x$addr -- xaddr\cnt | xaddr = x$addr+1 )

Unpacks the counted string whose count is stored at x$addr and whose first character is stored at x$addr+1. Returns the extended address of the first character under the count.  The string may cross a page boundary.

See also LCOUNT

 
COUNT.TO.MSEC

COUNT.TO.MSEC ( ud1 -- ud2 | ud1 = elapsed timeslice count, ud2 = #msec )

Returns the number of milliseconds ud2 corresponding to the elapsed number of timeslice counts ud1. The input parameter ud1 can be a difference (elapsed count, calculated using D-) between a prior time and a more recent timeslice count, or it can be the current value of the timeslice clock since it was initialized to 0\0 by INIT.ELAPSED.TIME.  The resolution equals the period of the timeslice clock (the default is approximately 1 msec).  Even though the timeslice clock has a period that is a multiple of 1.024 msec, this routine mathematically compensates for the non-integer period, reducing the reported error to 1 part in 5000, equivalent to reporting 17 too few seconds per day.  The maximum time that the return value can represent is about 49.7 days.

See also READ.ELAPSED.TIME, READ.ELAPSED.SECONDS, TIMESLICE.COUNT, START.TIMESLICER, and MSEC.TIMESLICE.PERIOD

 
COUNT.TYPE

COUNT.TYPE ( x$addr -- )

Unpacks count from x$addr on page and types the string.  COUNT.TYPE is equivalent to COUNT TYPE

Attributes: M

 
COUNTER.UNDERFLOW.ID

COUNTER.UNDERFLOW.ID ( -- n )

Returns the interrupt identity code for the modulus down-counter underflow interrupt.  Used as an argument for ATTACH.
Pronunciation: counter-underflow-i-d

 
CR

CR ( -- )

Causes subsequent output to appear at the beginning of the next line by emitting a carriage return (ascii 13) followed by a line feed (ascii 10).
Pronunciation: c-r
Attributes: M

 
CR.BEFORE.MSG

CR.BEFORE.MSG ( -- xaddr )

A user variable that contains a 16-bit flag.  If the flag is false (the default condition), system warnings and error messages are printed without first emitting carriage return/linefeed characters.  This ensures smooth downloads if the host terminal is using the suggested technique of waiting for a linefeed character (ascii 10) before sending each new line of source code to the PDQ controller.  If the CR.BEFORE.MSG flag is true, the error and warning messages are printed on a separate line, but the leading carriage return/linefeed that is emitted may cause the host terminal to send the next line of source code before the PDQ controller is capable of responding to it.  Thus it is recommended that CR.BEFORE.MSG be kept in its default OFF state while downloading.
Pronunciation: carriage-return-before-message
Attributes: U

 
CREATE

CREATE ( <name> -- )

Adds a new header for <name> to the names area.  Executes BL WORD to parse the next space-delimited word <name> from the input stream.  Converts the parsed string to upper case letters and searches the dictionary via (FIND) to check for uniqueness, issuing a warning if <name> is not unique.

If the system variable NP.NOBUMP is in its default false state, checks to see if the names pointer NP is within 88 bytes of top of the names page, and if so bumps NP to the start of the next page, and aborts if the allotted names page region as indicated by the system variable LAST.NP.PAGE has been exceeded.  If the system variable DP.NOBUMP is in its default false state, checks to see if the dictionary pointer DP is within 256 bytes of top of the dictionary page, and if so bumps DP to the start of the next page, and aborts if the allotted dictionary page region as indicated by the system variable LAST.DP.PAGE has been exceeded.

Creates a new header for <name> starting at the address pointed to by NP, updates NP to point to the byte after <name>'s header, and initializes the fields in the header.  This routine links the header to LATEST in the CURRENT vocabulary via a standard (chronological) link and, if <name> is in the VFORTH vocabulary, the hash link is set and the relevant hash table entry is updated.  The number of characters saved in the header is the lesser of the value in WIDTH or the actual number of characters in <name>.

If locals.are.compiling or C.CALLABLE is true, or if a library is compiling and PRIVATE is false, then all characters are saved in the header.  This ensures the uniqueness of local variables, C-callable functions, and published library functions.  This routine sets the size of the header to the standard size if C.CALLABLE is false, or to the extended size if C.CALLABLE is true.  Certain defining words such as XCREATE, X:, and XCODE set the system variable C.CALLABLE true before creating the header to ensure that a C-callable extended header is formed.

Uses the contents of the system variable THIS.SEGMENT and the user variable WIDTH to initialize the corresponding header fields.  Copies the contents of the system variable FUNCTION.TYPE to the function.type field in the header, then zeros the FUNCTION.TYPE system variable.  Sets the bitmasks in the header.type field subject to the following conditions: if THIS.SEGMENT = 0, sets bit 2 (in.kernel.mask); if C.CALLABLE is true, sets bit 3 (c.callable.mask); if PRIVATE is true, sets bit 4 (private.mask).  Other bits in the header field encode whether the header is immediate, has a pfa, or is a segment header; these bits are set by other functions.  The cfa.offset and cfa.page.offset fields are set according to the equation

[cfa(page) - segment.base(page)]

where segment.base(page) is calculated by looking in the EEPROM segment table entry pointed to by the system variable THIS.SEGMENT.  Finally, the contents of the vocabulary pointed to by CURRENT is set equal to the newly created nfa, where the nfa (name field address) is the address of the name count in the header.  An abort error occurs if the header cannot be stored (e.g.  if NP does not point to RAM).  If WIDTH is less than or equal to 1, (CREATE) resets WIDTH to 2.

Attributes: D

 
CURRENT

CURRENT ( -- xaddr )

A user variable that contains a 32-bit xhandle which in turn contains the xnfa of the top word in the vocabulary to which new definitions are added by CREATE.  Thus CURRENT X@ returns the xhandle of the definitions vocabulary, and CURRENT X@ X@ is equivalent to LATEST, returning the xnfa of the latest word defined.  In short, the contents of CURRENT determine the vocabulary to which new words are added.

See also CREATE and CONTEXT

Attributes: U

 
CURRENT.HEAP

CURRENT.HEAP ( -- xaddr )

A user variable that holds the 32-bit extended address that specifies the end of the current heap.  Executing CURRENT.HEAP X@ places the xaddress of the last+1 byte in the current heap on the data stack; the other heap control variables are stored just below this address in the heap.

See also IS.HEAP
Attributes: U

 
CUSTOM.ABORT

CUSTOM.ABORT ( -- xaddr )

A user variable that contains a 16-bit flag.  If the flag is TRUE, the abort routine whose xcfa is in UABORT is executed each time that ABORT is called.  If the flag is FALSE, ABORT executes the default (ABORT) routine.

See also ABORT, (ABORT), and UABORT

Attributes: U

 
CUSTOM.ERROR

CUSTOM.ERROR ( -- xaddr )

A user variable that contains a 16-bit flag.  If the flag is TRUE, the error routine whose xcfa is in UERROR is executed in response to every system error.  If CUSTOM.ERROR is FALSE, all system errors call the default (ERROR routine.

See also (ERROR) and UERROR

Attributes: U

 
D+

D+ ( d1\d2 -- d3 )

Adds two signed double numbers d1 and d2 giving the signed double number result d3.
Pronunciation: d-plus

 
D-

D- ( d1\d2 -- d3 | d3 = d1 - d2 )

Subtracts two signed double numbers d1 and d2 giving the signed double number result d3.
Pronunciation: d-minus

 
D.

D. ( wd -- )

Prints wd with no leading spaces and 1 trailing space.  If the number base is decimal, wd is printed as a signed number in the range -2,147,483,648 to +2,147,483,647. In other bases wd is printed as an unsigned positive number.
Pronunciation: d-dot
Attributes: M, S

 
D.INSTANCE:

D.INSTANCE: ( u <name> -- | u is the size of the structure )

Removes <name> from the input stream and creates a structure instance called <name>, and allocates u bytes in the definitions area starting at HERE for the structure instance (the D in D.INSTANCE: refers to the Definitions area where the instance is allocated).  Compare with V.INSTANCE:.  When <name> is executed, the extended base address of the allocated structure instance is placed on the data stack.  Typical use:

<structure.name> D.INSTANCE: <name>

where <structure.name> was defined using

STRUCTURE.BEGIN: <structure.name>
   ...
STRUCTURE.END

Executing <structure.name> leaves the structure size u on the stack, and D.INSTANCE: <name> allocates and names the instance.  Executing

SIZE.OF <name>

places the allocated size of the instance on the stack.  The instance may not cross a page boundary.  D.INSTANCE: is "segment-relocation-smart", and returns the correct result even when defined inside a library or application segment that is relocated to a location that is different from its initial compilation address.
Pronunciation: d-instance
Attributes: D

 
D.OVER.N

D.OVER.N ( d\n -- d\n\d )

Copies the double number located under the top data stack cell to the top of the data stack.
Pronunciation: d-over-n

 
D.R

D.R ( wd\+byte -- | +byte is field width )

Prints wd right-justified in a field of +byte characters.  If +byte is less than or equal to the number of characters to be printed, the number is printed with no extra spaces.  If the number base is decimal, wd is printed as a signed number in the range -2,147,483,648 to +2,147,483,647. In other bases w is printed as an unsigned positive number.  To print wd as a positive unsigned number in decimal base, use UD.R
Pronunciation: d-dot-r
Attributes: M, S

 
D0<>

D0<> ( wd -- flag )

Flag is TRUE if double number wd is not equal to zero, and FALSE otherwise.
Pronunciation: d-zero-not-equal

 
D0=

D0= ( wd -- flag )

Flag is TRUE if double number wd is equal to zero and FALSE otherwise.
Pronunciation: d-zero-equal

 
D2*

D2* ( d1 -- d2 | d2 = d1 * 2 )

Multiplies signed double number d1 by 2 giving d2. Overflow errors are not checked.
Pronunciation: d-two-star

 
D2/

D2/ ( d1 -- d2 | d2 = d1 / 2 )

Divides signed double number d1 by 2 giving d2.
Pronunciation: d-two-slash

 
D<

D< ( d1\d2 -- flag )

Flag is TRUE if the signed double number d1 is less than the signed double number d2 and FALSE otherwise.
Pronunciation: d-less-than

 
D<>

D<> ( wd1\wd2 -- flag )

Flag is TRUE if the two double numbers are not equal and FALSE otherwise.
Pronunciation: d-not-equal

 
D=

D= ( wd1\wd2 -- flag )

Flag is TRUE if the two double numbers are equal and FALSE otherwise.
Pronunciation: d-equal

 
D>

D> ( d1\d2 -- flag )

Flag is TRUE if the signed double number d1 is greater than the signed double number d2 and FALSE otherwise.
Pronunciation: d-greater-than

 
D>R

D>R ( d -- )
Return stack: ( R: -- d )

Transfers the top double number on the data stack to the return stack.
Pronunciation: d-to-r
Attributes: C

 
D>R$

D>R$ ( d\+b -- xaddr\cnt | +b = width )

Converts d to a counted string right justified in a field of minimum width +b.  The string is built below PAD, and the count is stored at xaddr-1.

See also UD>R$

Attributes: S

 
D>S

D>S ( d -- n )

Converts the double number d to the single number n by dropping the most significant cell of d.  There is an unchecked error if d cannot be represented by a 16-bit signed integer.
Pronunciation: d-to-s

 
D>S?

D>S? ( d -- [d\2] or [n\1] )

If possible, converts double number d to a single number n and leaves n on the stack under a 1 flag.  Otherwise leaves double number d on the stack under a 2 flag.
Pronunciation: d-to-s-question

 
DABS

DABS ( d1 -- +d2 )

Replaces double precision signed number d1 with its absolute value +d2. If d1 is positive, +d2 = d1. If d1 is negative, +d2 is the negative of d1.
Pronunciation: d-abs

 
DATE/TIME:

DATE/TIME: ( <segment.name> <${date/time.string}$> -- )

For the specified <segment.name>, stores the specified date/time string which is delimited by a starting ${ and an ending }$ delimiter.  The string is exported by COMPOSE.FORTH.INSTALLER, COMPOSE.FORTH.INSTALLER.FOR, COMPOSE.C.INSTALLER, COMPOSE.C.INSTALLER.FOR, and the routines that BUILD library and application segments.

The SEGMENT.PRESENT function compares the saved string to a string sent by the IDE (Integrated Development Environment, which includes the terminal).  This comparison result is used by the IDE to decide whether the standard or quick version of the install file should be downloaded to the board.  If the date/time string and code checksum match, then the segment has already been loaded, and the quick version that does not include S-records can be sent to speed the download.  DATE/TIME: parses from the input stream a single- or multi-line long-string that starts with ${ and ends with the }$ delimiter.  At least one space is required before the ${ delimiter, and a space or carriage return is required after the }$ delimiter.  The string is saved in the forth names area pointed to by NP in RAM, and the offset from the xnfa to the x$addr is stored in the 3-byte +PROTOTYPE$ field of the forth header. <segment.name> must be a segment header defined with the LIBRARY or APPLICATION directive.  The comparison is case sensitive, and any extra characters (including spaces) will cause a mis-match when SEGMENT.PRESENT executes.

Example of use:

DATE/TIME: MYAPP ${Mon 11/23/05 12:05:32 PST}$
 
DEALLOCATED

DEALLOCATED ( xpfa -- )

De-allocates the heap memory associated with the data structure having the specified parameter field address xpfa.  The xpfa is typically associated with a word defined by H.INSTANCE:. Typical use:

size.of.heap.item  H.INSTANCE:  <name>
SIZE.OF <name>   ' <name>  ALLOCATED
   ...
 '  <name>  DEALLOCATED
 
DEBUG

DEBUG ( -- xaddr )

A user variable that holds a 16-bit flag.  If true, this flag enables error checking by the word NEEDED, and enables a stack contents display via the .S routine after each line is interpreted while in the execution mode.  DEBUG also enables the trace printout of words that are compiled while TRACE is ON.

Attributes: U

 
DECIMAL

DECIMAL ( -- )

Set the numeric conversion base to ten by storing decimal 10 into the user variable BASE.

 
DEFAULT.MAP

DEFAULT.MAP ( -- )

Establishes a default memory map that is convenient for programming.  Sets DP = 0x8000 on page 0x00, sets NP = 0x8000 on page 0x10, sets VP = 0x2000 in common RAM, and sets the 80 Kbyte default heap at 0x8000 on page 0x18 through 0xBFFF on page 0x1C.  The only difference between the DEFAULT.MAP and to the memory map established after a COLD restart is that this routine sets DP at 0x8000 on page 0x00 and NP at 0x8000 on page 0x10, compared to DP and NP on page 0x1D after COLD.  This routine leaves the user area, stacks, TIB, POCKET and PAD as they were.  It is recommended that the programmer execute ANEW <name> (or equivalently, declare a new segment using LIBRARY or APPLICATION) immediately after using this command; this will properly reset the memory pointers when reloading the compiled words during program development.

 
DEFAULT.TRACE.ACTION

DEFAULT.TRACE.ACTION ( -- )

Installs NO.OP, a do-nothing word, as the trace action.  Equivalent to

CFA.FOR  NO.OP  IS.TRACE.ACTION

See IS.TRACE.ACTION.

 
DEFINITIONS

DEFINITIONS ( -- )

Stores the contents of CONTEXT into CURRENT so that the search vocabulary is also the vocabulary to which new definitions are appended.

Attributes: I

 
DELETED

DELETED ( array.xpfa -- | used for arrays and matrices )

De-allocates the heap space assigned to the specified array or matrix, and clears the parameter field to indicate that the data structure is no longer dimensioned.  Use as:

'  <name> DELETED

See DIMENSIONED, DIMMED.

 
DEPTH

DEPTH ( -- +n | +n = stack depth )

+n is the number of cells on the data stack before +n was placed on the stack.

 
DFIXX

DFIXX ( r -- d )

d is the 32 bit integer closest to the floating point number r.

See also FIXX
Pronunciation: d-fix
Attributes: S

 
DFLOT

DFLOT ( d -- r )

Converts the double number d to the nearest floating point number r.  Note that there is a potential loss of resolution in this conversion, since d is represented by 32 significant bits, while r has a 23-bit mantissa.

See also FLOT
Pronunciation: d-f-lot
Attributes: S

 
DIGIT

DIGIT ( char -- [ n\-1 ] or [ 0 ] )

Converts ascii char to binary digit n in the current number base and leaves n on the stack under a true flag.  If char cannot be converted to a valid digit, returns a false flag.

 
DIM.CONSTANT.ARRAY:

DIM.CONSTANT.ARRAY: ( u1\...\uN\N\n <name> -- | N=#dim, n=bytes/element )

Removes <name> from the input stream and creates and dimensions an array in the definitions area.  This is useful for building lookup tables that will reside in the non-volatile code area after the application is finished.  u1, u2, …uN specify the number of elements in each dimension, N specifies the number of dimensions, and n specifies the number of bytes per element. <name> behaves exactly as an array does; its stack picture is

( indices -- xaddr )

and an element xaddress is also returned upon execution of the command

indices  ' <name> []

DIM.CONSTANT.ARRAY: creates a header for <name> in the names area of the dictionary.  It creates and initializes a parameter field and a handle (to mimic a heap handle) in the definitions area, and allots the required number of bytes for the array in the definitions area.  ABORTs if #dim is invalid (not equal to 1 or 2).  The array may cross page boundaries, and may increment the dictionary pointer DP so that it points to a new page.

Example of use:

To define and dimension a constant array to have 2 dimensions (3 rows and 4 columns) with 6 bytes per element, execute:

3 4 2 6 DIM.CONSTANT.ARRAY: <name>

To access the starting element in the array (row=0, col=0), execute

0 0 <name>    ( -- xaddr)

which leaves the xaddress of the element on the stack, ready for a fetch or store function.

Restrictions: In general, constant arrays should be dimensioned only once at the time of creation; redimensioning to a larger size could write over other routines in the dictionary and cause a crash.

Notes on relocation of constant arrays: DIM.CONSTANT.ARRAY: is application-segment-relocation-smart, and returns the correct result even when defined inside an application segment that is relocated to a new parallel page.  The relocation cannot change the base address of the application segment or the constant array.  Do not use DIM.CONSTANT.ARRAY: when defining a library segment, as libraries typically undergo both address and page relocation.  When using a relocated constant array, the access syntax must use the <name> of the array as in the example of use above; the tick syntax ' <array_name> [] or ' <array_name> [0] is not allowed.

Attributes: D

 
DIM.CONSTANT.MATRIX:

DIM.CONSTANT.MATRIX: ( #rows\#cols <name> -- )

Removes <name> from the input stream and creates and dimensions a matrix in the definitions area.  This is useful for building lookup tables that will reside in ROM after the application is finished and write-protected. <name> behaves exactly as a matrix does; its stack picture is:

( row#\col# -- xaddr )

and an element xaddress is also returned upon execution of the command

 row# col#  ' <name> M[]

DIM.CONSTANT.MATRIX: creates a header for <name> in the names area of the dictionary.  It creates and initializes a parameter field and a handle (to mimic a heap handle) in the definitions area, and allots the required number of bytes for the matrix in the definitions area.  The matrix is assigned #rows rows and #cols columns, 2 dimensions, and 4 bytes/element.  The matrix may cross page boundaries, and may increment the dictionary pointer DP so that it points to a new page.  DIM.CONSTANT.MATRIX: is segment-relocation-smart, and returns the correct result even when defined inside a library or application segment that is relocated to a location that is different from its initial compilation address.

Example of use:

To define and dimension a constant matrix to have 3 rows and 4 columns, execute:

3 4 DIM.CONSTANT.MATRIX: <name>

To access the starting element in the matrix (row=0, col=0), execute

0 0 <name>    ( -- xaddr)

which leaves the xaddress of the element on the stack, ready for a fetch or store function.

Restrictions: Care must be used when using matrix operators that assume that the matrix resides in the current heap.  In general, constant matrices should be dimensioned only once at the time of creation; redimensioning to a larger size could write over other routines in the dictionary and cause a crash.

To access the starting element in the array, execute

0 0 <name>    ( -- xaddr)

which leaves the xaddress of the element on the stack, ready for a fetch or store function.

Restrictions: In general, constant matrices should be dimensioned only once at the time of creation; redimensioning to a larger size could write over other routines in the dictionary and cause a crash.

Notes on relocation of constant matrices: DIM.CONSTANT.MATRIX: is application-segment-relocation-smart, and returns the correct result even when defined inside an application segment that is relocated to a new parallel page.  The relocation cannot change the base address of the application segment or the constant matrix.  Do not use DIM.CONSTANT.MATRIX: when defining a library segment, as libraries typically undergo both address and page relocation.  When using a relocated constant matrix, the access syntax must use the <name> of the matrix as in the example of use above; the tick syntax ' <matrix_name> [] or ' <matrix_name> [0] is not allowed.

Attributes: D

 
DIMENSIONED

DIMENSIONED ( u1\...\uN\N\n\array.xpfa -- )

Dimensions the array specified by array.xpfa.  u1…uN specify the number of elements in each dimension, N specifies the number of dimensions, and n specifies the number of bytes per element.  DIMENSIONED executes DELETED to de-allocate any heap space previously allocated to the array, and then writes the dimensioning information into the array's parameter field and allocates the required number of bytes in the heap.  ABORTs if there is not enough heap space or if N is invalid (N must be either 1 or 2).

Example of use:

To define and dimension an array to have 2 dimensions (3 rows and 4 columns) with 6 bytes per element, execute:

ARRAY:   <name>
3 4 2 6   ' <name>  DIMENSIONED
 
DIMMED

DIMMED ( #rows\#cols\matrix.xpfa -- )

Dimensions the matrix specified by matrix.xpfa to have #rows rows and #cols columns.  The number of dimensions is 2, and there are 4 bytes per element (i.e., the size of a floating point number).  DIMMED executes DELETED to de-allocate any heap space previously allocated to the matrix, and then writes the dimensioning information into the parameter field and allocates the required number of bytes in the heap.  ABORTs if there is not enough heap space.  For example, to define and dimension a matrix to have 3 rows and 4 columns, execute:

MATRIX: <name>
3 4 ' <name>  DIMMED
 
DIN

DIN ( -- wd )

Compile Time: ( <name> – )

DIN removes the next word from the input stream, converts it to a 32-bit double number wd in the current number base (or in hexadecimal if the number is preceeded by 0x or 0X), and executes 2LITERAL which leaves the number on the stack if QED-Forth is in execution mode, or compiles it as a literal in the current definition if QED-Forth is in compilation mode.  If DIN is not used, 32-bit numbers in the input stream are truncated to 16 bits.  An error is issued if <name> cannot be converted to a valid number.  Typical use:

HEX DIN 12345678   ( -- 5678 \ 1234 )
D.      12345678 ok


Pronunciation: d-in

 
DINT

DINT ( r -- d )

d is the double number representation of the integer part of floating point number r.

See also INT.PART
Pronunciation: d-int

 
DINT.FLOOR

DINT.FLOOR ( r -- d )

d is the greatest double number less than or equal to r.

See also INT.FLOOR
Pronunciation: d-int-floor

 
DISABLE.BOOT.VECTORS

DISABLE.BOOT.VECTORS ( -- )

Prevents any boot vectors installed by SET.BOOT.VECTOR from being executed.  The effect of this command can be reversed by ENABLE.BOOT.VECTORS.

See also CLEAR.BOOT.VECTORS

Implementation detail: Sets a configuration bit in reserved system EEPROM to suppress the execution of all installed boot vectors.

 
DISABLE.INTERRUPTS

DISABLE.INTERRUPTS ( -- )

Sets the interrupt mask bit (the I bit) in the condition code register to globally disable interrupts.

 
DMAX

DMAX ( d1\d2 -- [d1] or [d2] | retains the greater of d1 and d2 )

Retains the greater of two signed double numbers and drops the other.
Pronunciation: d-max

 
DMIN

DMIN ( d1\d2 -- [d1] or [d2] | retains the lesser of d1 and d2 )

Retains the lesser of the two signed double numbers and drops the other.
Pronunciation: d-min

 
DNEGATE

DNEGATE ( d1 -- d2 | d2 = two's complement of d1 )

Negates signed double number d1 to yield d2. The negative (two's complement) is computed by inverting all of the bits in d1 and adding a 32-bit 1 to the result.
Pronunciation: d-negate

 
DO

DO ( w1\w2 -- | w1 = limit, w2 = starting index )

Return Stack: ( R: – w1\w2 )

Used inside a colon definition to mark the beginning of a counted loop structure that is terminated by LOOP or +LOOP. DO sets up the loop control parameters (index and limit) on the return stack with w1 as the limit and w2 as the starting index. Because the loop parameters are maintained on the return stack, caution must be exercised when using the operators >R and R> inside a loop. DO…LOOPs may be nested as long as each DO is matched with a corresponding LOOP or +LOOP in the same definition as DO. w1 and w2 may either be a pair of signed integers or a pair of unsigned integers.

DO may only be used within a definition. Use as:

w1 w2 DO ... LOOP

or

w1 w2 DO ...  n +LOOP

The loop terminates when index crosses the boundary between limit-1 and limit in either direction. An error is issued if DO is not properly paired with LOOP or +LOOP inside a definition.

Before the first iteration, DO tests to see if index = limit (that is, w2 = w1); if so the loop is skipped and control is immediately passed to the word after LOOP or +LOOP. For all iterations the test for termination is done by LOOP or +LOOP at the end of the DO…LOOP or DO…+LOOP control structure. This behavior is taken from the ANSI X3.215-1994 definition of ?DO; that is, our DO behaves identically to the ANSI FORTH ?DO. The ANSI standard DO always caused the loop to execute at least once; our DO and the ANSI ?DO do not.

Examples of DO…LOOP and DO…+LOOP
Code Output
4 4 DO I . LOOP (no execution)
4 0 DO I . LOOP 0 1 2 3
4 5 DO I . LOOP 5 6 7 8 … -2 -1 0 1 2 3
4 0 DO I . 1 +LOOP 0 1 2 3
4 0 DO I . 2 +LOOP 0 2
0 4 DO I . -1 +LOOP 4 3 2 1 0
0 4 DO I . -2 +LOOP 4 2 0

See also LOOP  +LOOP  I  J  K  I'  LEAVE

Attributes: C, I

 
DOES>

DOES> ( -- )

Used in a high level defining word to mark the beginning of the specification of the run-time action of the child words.  Use as:

: <namex>
   <DBUILDS  compile time action
   DOES>     run time action
;

or as

: <namex>
   <VBUILDS   compile time action
   DOES>      run time action
;

where <namex> is referred to as a defining word. Executing the statement

<namex> <child's.name>

defines the child word.  The code after <DBUILDS or <VBUILDS specifies the action to be taken while defining the child word, and the code after DOES> specifies the action to be taken when the child word executes.

The default run-time action of DOES> is to leave the extended parameter field address of the child word on the data stack.  Thus, the code between DOES> and ; should expect the xpfa on the stack when the child executes.  DOES> is segment-relocation-smart, and performs the correct actions even when invoked inside a library or application segment that is relocated to a location that is different from its initial compilation address.  Consult the definitions of <DBUILDS and <VBUILDS for examples of use.

See also <DBUILDS and <VBUILDS
Pronunciation: does

 
DOUBLE->

DOUBLE-> ( u1 <name> -- u2 )

Adds a named member to the structure being defined and reserves room for a double number field in the structure.  Removes <name> from the input stream and creates a structure field called <name>. u1 is the structure offset initialized by STRUCTURE.BEGIN:. u2 is the updated offset to be used by the next member defining word or by STRUCTURE.END.  When <name> is later executed, it adds its offset u1 to the extended address found on the data stack which is typically the start xaddress of an instance of the data structure; the result is the xaddress of the desired member in the structure.
Pronunciation: double
Attributes: D

 
DOUBLE:

DOUBLE: ( <name> -- )

Defines a 32-bit self-fetching variable.  Removes <name> from the input stream and creates a child word (a self-fetching variable) called <name> and allots 4 bytes in the variable area as the parameter field where the self-fetching variable's value is stored.  When <name> is executed it leaves its value (a 32-bit number) on the stack.  Thus <name> behaves like a 2constant when executed.  Unlike a 2constant, its parameter field is in the variable area and so can always be modified.  The TO command is used to store a value into the self-fetching variable.  In general, code using self-fetching variables runs faster than does similar code that uses standard variables because the fetch and store operations are integrated into the action of the variable.  Use as:

DOUBLE: <name>


Pronunciation: double-colon
Attributes: D

 
DOUBLES->

DOUBLES-> ( u1\u2 <name> -- u3 )

Adds a named member to the structure being defined and reserves room for u2 double numbers in the structure.  Removes <name> from the input stream and creates a structure field called <name>. u1 is the structure offset initialized by STRUCTURE.BEGIN:. u3 is the updated offset to be used by the next member defining word or by STRUCTURE.END.  When <name> is later executed, it adds its offset u1 to the extended address found on the data stack which is typically the start xaddress of an instance of the data structure; the result is the xaddress of the desired member in the structure.
Pronunciation: doubles
Attributes: D

 
DP

DP ( -- xaddr )

User variable that contains the 32-bit definitions pointer.  The contents of DP are placed on the stack by HERE and are modified by ALLOT.  The command DP X@ is equivalent to HERE; it yields the xaddr of the next available dictionary location.  The command DP @ is equivalent to DPAGE; it yields the page of the definitions area.
Pronunciation: d-p
Attributes: U

 
DP.NOBUMP

DP.NOBUMP ( -- xaddr )

A 16-bit system variable that is zeroed by COLD.  If the system variable DP.NOBUMP is in its default false state, CREATE (which is called by defining words such as : and CODE) checks to see if the dictionary pointer DP is within 256 bytes of top of the dictionary page, and if so, it bumps DP to the start of the next page.  This feature helps automatically manage the dictionary pointer, typically avoiding an abort error due to a definition crossing a page boundary.

See also LAST.DP.PAGE and NP.NOBUMP

 
DPAGE

DPAGE ( -- page )

Returns the page of the definitions area of the dictionary.  Equivalent to DP @
Pronunciation: d-page
Attributes: U

 
DPICK

DPICK ( d\wn-1\...w1\w0\+n -- d\wn-1\...\w1\w0\d | 0 ≤ +n ≤ 255 )

Copies the double number whose most significant cell is the nth item on the stack (0-based, not including n) to the top of the stack.  An unchecked error occurs if there are fewer than +n+2 cells on the data stack. 0 DPICK is equivalent to 2DUP, 1 DPICK is equivalent to D.OVER.N, 2 DPICK is equivalent to 2OVER.
Pronunciation: d-pick

 
DR>

DR> ( -- d )
Return stack: ( R: d -- )

Transfers the top double number on the return stack to the data stack.
Pronunciation: d-r-from
Attributes: C

 
DR>DROP

DR>DROP ( -- )
Return stack: ( R: d -- )

Removes the top double number on the return stack.
Pronunciation: d-r-from-drop
Attributes: C

 
DR@

DR@ ( -- d )
Return stack: ( R: d -- d )

Copies the top double number on the return stack to the data stack.
Pronunciation: d-r-fetch
Attributes: C

 
DRANGE

DRANGE ( d1\d2\d3 -- d1\flag )

Flag is TRUE if d1 is greater than or equal to d2 and less than or equal to d3. Otherwise flag is FALSE.
Pronunciation: d-range

 
DROP

DROP ( w -- )

Drops the top cell from the stack.

 
DSCALE

DSCALE ( d1\n -- d2 )

Arithmetically (i.e., preserving sign) shifts double number d1 by n bit places to yield signed double number result d2. If n is positive, d1 is shifted left; if n is negative, d1 is shifted right.  The absolute value of n determines the number of bits of shifting.  For example, 1 DSCALE is equivalent to D2* and -1 DSCALE is equivalent to D2/ . There is an unchecked error if the absolute value of n is greater than 31.
Pronunciation: d-scale

 
DU<

DU< ( ud1\ud2 -- flag )

Flag is TRUE if the unsigned double number ud1 is less than the unsigned double number ud2.
Pronunciation: d-u-less-than

 
DU>

DU> ( ud1\ud2 -- flag )

Flag is TRUE if the unsigned double number ud1 is greater than the unsigned double number d2.
Pronunciation: d-u-greater-than

 
DUMP

DUMP ( xaddr\u -- | xaddr = start address, u = number of bytes )

Displays the contents of u bytes starting at the specified xaddr.  The contents are dumped as hexadecimal bytes regardless of the current number base, and the ascii equivalent contents are also displayed.  For example, to display 0x40 bytes starting at address 0x9000\1, execute:

HEX  9000  1  40  DUMP

and to display the last 0x10 bytes on page 1 and the first 0x20 bytes on page 2, type: BFF0 1 30 DUMP

DUMP calls the word PAUSE.ON.KEY, so the dump responds to XON/XOFF handshaking and can be aborted by typing a carriage return; see PAUSE.ON.KEY.

Attributes: M, S

 
DUMP.AUTOSTARTS

DUMP.AUTOSTARTS ( -- )

Dumps to the active serial port the contents of addresses 0xBFFA through BFFF on pages 0x0F and 0x37 with in-place reported xaddresses in Motorola S2 hex format.  The resulting dump includes the autostart code vectors compiled by PRIORITY.AUTOSTART (on page 0x0F) and AUTOSTART (on page 0x37); See their glossary entries.  Using this routine facilitates transferring the autostart vectors to production units; to load a dumped set of autostart vectors into a board, simply execute:

-1 –1 RECEIVE.HEX

and use the Mosaic Terminal program to send the result created by DUMP.AUTOSTARTS to the production board.

Attributes: M, S

 
DUMP.BINARY

DUMP.BINARY ( xaddr\u -- | xaddr = start address, u = number of bytes )

Emits u bytes of memory starting at the specified xaddr as a binary (not ascii!) stream.  For example, to perform a binary dump of the last 0x10 bytes on page 1 and the first 0x20 bytes on page 2, type:

HEX  BFF0  1  30  DUMP.BINARY

DUMP.BINARY calls the word PAUSE.ON.KEY intermittently, so the dump responds to XON/XOFF handshaking and can be aborted by typing a carriage return; see PAUSE.ON.KEY.  Note that this routine does not GET the serial resource if SERIAL.ACCESS equals RELEASE.AFTER.LINE.

Attributes: M, S

 
DUMP.INTEL

DUMP.INTEL ( xaddr1\addr2\u -- )

xaddr1 is the location of the first byte to be dumped, addr2 specifies the starting address reported in the dump, and u is the number of bytes to be dumped.  Dumps the contents of u bytes starting at xaddr using the standard ascii Intel hex format which is useful for transferring data between devices.  The line format is:

:{#bytes}{reported.addr}{00}{byte}{byte} ...{byte}{checksum}

All numbers are in hexadecimal base.  Each line starts with a : character, followed by a 2-digit number of bytes (a maximum of 0x20 bytes per line), followed by a 4-digit starting address for the line, followed by the recrord type 00, followed by the contents of the memory locations (2 hex digits per byte), and concluding with a checksum followed by a carriage return/linefeed.  The checksum is calculated by summing each of the bytes on the line into an 8-bit accumulator and negating (two's complementing) the result.  The hex dump ends with the line

:00000001FF

For example, to dump 0x40 bytes starting at PDQ controller address 0x9000\1 so that the bytes reside at the beginning of a target memory device, execute:

HEX  9000  01  0000   40  DUMP.INTEL

which specifies 0x9000\1 as the starting address, 0000 as the reported base address in the memory device, and 0x40 as the number of bytes to be dumped.  To dump the last 0x20 bytes on page 1 and the first 0x40 bytes on page 2 so that they reside at locations 0xBFE0 through 0xC03F in the target memory device, execute

BFE0  1  BFE0   60    DUMP.INTEL

The complementary word RECEIVE.HEX loads the controller’s memory starting at any location based on a received Intel or Motorola hex file.  DUMP.INTEL calls the word PAUSE.ON.KEY, so the dump responds to XON/XOFF handshaking and can be aborted by typing a carriage return.

See also DUMP.S1, DUMP.S2, RECEIVE.HEX and PAUSE.ON.KEY

Attributes: M, S

 
DUMP.KERNEL.S

DUMP.KERNEL.S ( -- )

This low-level utility routine prints information used by the GCC compiler to access C-callable functions in the kernel (operating system).  This function is useable only at the factory and should be executed after a COLD restart.  For each C-callable function (LATEST through FORTH), it prints a wrapper for use by C compiler in the following form:

#saveto "Activate.s"
  .sect .text
  .globl Activate
  .type Activate,@function
  .far Activate
Activate:
  jsr 0xC000
  .2byte 0xC000
  .byte 0x2
  .2byte KERNEL_ARRAY_ADDR
  .byte 0x3C
  .2byte 0x997A
  rtc
  .size Activate, .-Activate
#endsaveto

This routine requires at least 15.6 Kbytes available in the current heap for a temporary array.

Attributes: M, S

 
DUMP.MANY.S2

DUMP.MANY.S2 ( xaddr1\d1\d2 -- | d1 = reported address, d2 = #bytes )

xaddr1 is the location of the first byte to be dumped, double number d1 specifies the 24 bit starting address reported in the dump, and d2 is the number of bytes to be dumped.  Dumps the contents of d2 bytes starting at xaddr1 using the standard ascii Motorola S2 hex format which is useful for burning flash memory chips and transferring data between devices.  Motorola S2 records report 24 bit addresses which are useful in capturing and transferring complete application programs to/from flash memory. (To report 16 bit addresses, see DUMP.S1.) Dumps an S0 header record which is

S00900004845414445524D

then as many S2 data records as required, followed by an S9 termination record which is

S9030000FC

The Motorola S2 hex line format is:

S2{#bytes}{24bit.reported.addr}{byte}...{byte}{chksum}

All numbers are in hexadecimal base.  A maximum of 0x20 data bytes are dumped per line.  Each line starts with the record type (S2 in this case), followed by a 2-digit number of bytes (typically 24, which equals 0x20 byte per line plus 4 bytes for the reported address and checksum), followed by a 6-digit starting address for the line, followed by the contents of the memory locations (2 hex digits per byte), and concluding with a checksum.  The checksum is calculated by summing each of the bytes on the line (excluding the record type) into an 8-bit accumulator and (one's) complementing the result.  DUMP.S2 calls the word PAUSE.ON.KEY, so the dump responds to XON/XOFF handshaking and can be aborted by typing a carriage return.

See also DUMP.S2, RECEIVE.HEX and PAUSE.ON.KEY

Example of use: Assume that you have created an application program using the memory map established by DEFAULT.MAP.  Let’s say that this is a program with code in pages 0 through 0x0F, names in pages 0x10 through 0x13, heap on pages 0x18-0x1C, and that you used PRIORITY.AUTOSTART: to configure a startup vector so that the application runs automatically upon each power-up and restart.  Referring to the glossary entry for PRIORITY.AUTOSTART: we see that it installs the vector at locations 0xBFFA-0xBFFF on page 0x0F.  We assume that no additional libraries or boot vectors need to be written into other memory areas such as on-chip flash.  To dump this program including the 6 byte priority autostart vector at the top of page 0x0F, configure the terminal to save the incoming text to a file (via the “save file” menu item), and execute:

DIN 0x008000  DIN 0x008000  DIN 0x50000  DUMP.S2   \ pages 00-0x13

Note that the reported xaddresses equal the actual dumped xaddresses; this allows us to use the simple –1 –1 RECEIVE.HEX command to reload the image in place.  Now open and edit the resulting file, removing any extraneous text, then re-save the file.  To transfer the application to each new production controller board such that it reloads to the same addresses contained in the dump, follow these steps.  First execute at the terminal

-1 -1 RECEIVE.HEX   <send the captured file>

This loads the image into RAM.  Next, save the image in the shadow flash using the command:

0x00  0x14  STORE.PAGES .

which writes from pages 00 through 0x13 to the back-up flash; this page range contains the code area, priority autostart vector, and names area.  The . (dot) command prints the success flag; it should equal –1 (FFFF in hex base).  Finally, we instruct the controller to load RAM from the back-up flash upon each COLD restart, and we write-protect RAM pages 0 through 0x0F (write protect region 1) and pages 0x10 through 0x13 (write protect region 2) to prevent corruption using these commands:

00 0x14  1  LOAD.PAGES.AT.STARTUP   \ load/restore pages 0x00 to 0x13
1 WRITE.PROTECT            \ protect pages 0x00-0x0F
2 WRITE.PROTECT            \ protect pages 0x10-0x13

This is an effective method of mass producing controller-based products running a turnkeyed autostart program.  Consult the glossary entry for DUMP.S2 for an example illustrating how to handle a smaller program, and consult the documentation for further discussion of these issues.

See also DUMP.AUTOSTARTS

Attributes: M, S

 
DUMP.REGISTERS

DUMP.REGISTERS ( -- xaddr )

A user variable that holds a flag.  If the flag is true, a definition that has been compiled with TRACE ON prints the contents of the registers before each instruction during a trace.  If the flag is false, the register contents are not printed during a trace.

 
DUMP.S1

DUMP.S1 ( xaddr1\addr2\u -- )

xaddr1 is the location of the first byte to be dumped, addr2 specifies the starting address reported in the dump, and u is the number of bytes to be dumped.  Dumps the contents of u bytes starting at xaddr using the standard ascii Motorola S1 hex format which is useful for transferring data between devices.  Motorola S1 records report 16 bit addresses. (To report full 24 bit addresses, see DUMP.S2.) Outputs an S0 header record which is

S00900004845414445524D

then as many S1 data records as required, followed by an S9 termination record which is

S9030000FC

The Motorola S1 hex line format is:

S1{#bytes}{16bit.reported.addr}{byte}...{byte}{chksum}

All numbers are in hexadecimal base.  A maximum of 0x20 data bytes are dumped per line.  Each line starts with the record type (S1 in this case), followed by a 2-digit number of bytes (typically 23, which equals 0x20 bytes per line plus 3 bytes for the reported address and checksum), followed by a 4-digit starting address for the line, followed by the contents of the memory locations (2 hex digits per byte), and concluding with a checksum.  The checksum is calculated by summing each of the bytes on the line (excluding the record type) into an 8-bit accumulator and (one's) complementing the result.  The complementary word RECEIVE.HEX loads memory starting at any location based on a received Motorola or Intel hex file.  DUMP.S1 calls the word PAUSE.ON.KEY, so the dump responds to XON/XOFF handshaking and can be aborted by typing a carriage return.

See also DUMP.S2, DUMP.INTEL, RECEIVE.HEX and PAUSE.ON.KEY

Attributes: M, S

 
DUMP.S2

DUMP.S2 ( xaddr1\d\u -- )

xaddr1 is the location of the first byte to be dumped, double number d specifies the 24 bit starting address reported in the dump, and u is the number of bytes to be dumped.  Dumps the contents of u bytes starting at xaddr1 using the standard ascii Motorola S2 hex format which is useful for burning flash memory chips and transferring data between devices.  Motorola S2 records report 24 bit addresses which are useful in capturing and transferring complete application programs to/from flash memory. (To report 16 bit addresses, see DUMP.S1.) Dumps an S0 header record which is

S00900004845414445524D

then as many S2 data records as required, followed by an S9 termination record which is

S9030000FC

The Motorola S2 hex line format is:

S2{#bytes}{24bit.reported.addr}{byte}...{byte}{chksum}

All numbers are in hexadecimal base.  A maximum of 0x20 data bytes are dumped per line.  Each line starts with the record type (S2 in this case), followed by a 2-digit number of bytes (typically 24, which equals 0x20 byte per line plus 4 bytes for the reported address and checksum), followed by a 6-digit starting address for the line, followed by the contents of the memory locations (2 hex digits per byte), and concluding with a checksum.  The checksum is calculated by summing each of the bytes on the line (excluding the record type) into an 8-bit accumulator and (one's) complementing the result.  DUMP.S2 calls the word PAUSE.ON.KEY, so the dump responds to XON/XOFF handshaking and can be aborted by typing a carriage return.

See also DUMP.S1, DUMP.INTEL, RECEIVE.HEX and PAUSE.ON.KEY

Example of use: Assume that you have created an application program using the memory map established by DEFAULT.MAP.  Let’s say that this is a simple program with code in pages 0 and 1, names in pages 0x10 and 0x11, heap on pages 0x18-0x1C, and that you used PRIORITY.AUTOSTART: to configure a startup vector so that the application runs automatically upon each power-up and restart.  Referring to the glossary entry for PRIORITY.AUTOSTART: we see that it installs the vector at locations 0xBFFA-0xBFFF on page 0x0F.  We assume that no additional libraries or boot vectors need to be written into other memory areas such as on-chip flash.  To dump this program including the 6 byte priority autostart vector at the top of page 0x0F, configure the terminal to save the incoming text to a file (via the “save file” menu item), and execute:

DIN 0x008000  DIN  0x008000  0x8000  DUMP.S2  \ pages 1 and 2
DIN 0x108000  DIN  0x108000  0x8000  DUMP.S2  \ pages 0x10 and 0x11
DIN 0x0FBFFA  DIN  0x0FBFFA  0x06    DUMP.S2  \ startup vector, page 0xF

Note that the reported xaddresses equal the actual dumped xaddresses; this allows us to use the simple –1 –1 RECEIVE.HEX command to reload the image in place.  Now open and edit the resulting file, removing any extraneous text and concatenating the 3 dumps into 1 S-record by removing all but the first and last S0 (header) and S9 (termination) records, then re-save the file.  To transfer the application to each new production controller board such that it reloads to the same addresses contained in the dump, follow these steps.  First execute at the terminal

-1 -1 RECEIVE.HEX   <send the captured file>

This loads the image into RAM.  Next, save the image in the shadow flash using the command:

0x00  0x12 STORE.PAGES .

which writes from pages 00 through 0x11 to the back-up flash; this page range contains the code area, priority autostart vector, and names area.  The . (dot) command prints the success flag; it should equal –1 (FFFF in hex base).  Finally, we instruct the controller to load RAM from the back-up flash upon each COLD restart, and we write-protect RAM pages 0 through 0x0F (write protect region 1) and pages 0x10 through 0x13 (write protect region 2) to prevent corruption using these commands:

00 0x12 1  LOAD.PAGES.AT.STARTUP  \ load/restore pages 0x00 to 0x11
1 WRITE.PROTECT    \ protect pages 0x00-0x0F
2 WRITE.PROTECT    \ protect pages 0x10-0x13

This is an effective method of mass producing controller-based products running a turnkeyed autostart program.  Consult the glossary entry for DUMP.MANY.S2 for an example illustrating how to handle a longer program, and consult the documentation for further discussion of these issues.

See also DUMP.AUTOSTARTS

Attributes: M, S

 
DUMP.SEGMENT

DUMP.SEGMENT ( n\flag1\flag2\flag3\xnfa -- )

This routine prints/exports information associated with the segment having the specified segment header xnfa.

The place input parameter n is IN.PLACE, TO.HERE or USER.SPECIFIED; See their glossary entries.  The three input flags are designated as follows: flag1 = c?; flag2 = full.build?; flag3 = suppress.S-record?. This low-level primitive is called by BUILD.LIBRARY, BUILD.APPLICATION, BUILD.SEGMENTS, COMPOSE.FORTH.INSTALLER, COMPOSE.FORTH.INSTALLER.FOR, COMPOSE.C.INSTALLER, and COMPOSE.C.INSTALLER.FOR; See their glossary entries.  This function is not recommended for the end user.  If the c? flag is true, Forth headers are not included in the dump.  If the full.build? flag is true, all of the information needed to fully reconstitute the segment as demanded by BUILD.LIBRARY, BUILD.APPLICATIONS, or BUILD.SEGMENTS is included in the dump, including the PROTOTYPE:, VPROTOTYPE:, EEPROTOTYPE:, C.HEADERS: and FORTH.HEADERS: declarations.  If the full.build? flag is false, only the statements needed by the COMPOSE installer commands are included, and the prototype and header declarations are not dumped.  If the suppress.S.record? input flag is true, the s-record code dump is suppressed as required by the quick compose installer routines.  This routine requires at least 15.6 Kbytes available in the current heap for a temporary array.

Attributes: M, S

 
DUMP.SEGMENT.FILE

DUMP.SEGMENT.FILE ( xnfa1\xnfa2\flag1\flag2\flag3\flag4 "<file>" -- )

This low-level primitive performs the action of COMPOSE.C.HEADERS and COMPOSE.C.ASM.CODE; See their glossary entries.  This function is not recommended for the end user.  The four input flags are designated as follows: flag1 = c.headers?; flag2 = c.code?; flag3 = 4th.include.headers?; flag4 = segment.build.headers? Only one of these flags should be true at a time.  This routine scans the headers between xnfa1 and xnfa2, inclusive, and prints the specified text associated with the headers as required by the calling function, printing #saveto and #endsaveto statements to direct the output to the specified "file". This routine requires at least 15.6 Kbytes available in the current heap for a temporary array.

Attributes: M, S

 
DUMP.SEGMENT.FILE.FOR

DUMP.SEGMENT.FILE.FOR ( flag1\flag2\flag3\flag4 <segment.name> "<file>" -- )

This low-level primitive performs the action of COMPOSE.C.HEADERS.FOR and COMPOSE.C.ASM.CODE.FOR; See their glossary entries.  This function is not recommended for the end user.  The four input flags are designated as follows: flag1 = c.headers?; flag2 = c.code?; flag3 = 4th.include.headers?; flag4 = segment.build.headers? Only one of these flags should be true at a time.  This routine prints the specified text associated with the specified <segment.name> as required by the calling function, printing #saveto and #endsaveto statements to direct the output to the specified "file". This routine requires at least 15.6 Kbytes available in the current heap for a temporary array.

Attributes: M, S

 
DUMP.SEGMENT.STREAM

DUMP.SEGMENT.STREAM ( xnfa1\xnfa2\flag1\flag2\flag3\flag4 -- )

This low-level primitive is called by all of the segment BUILD and COMPOSE routines; See their glossary entries.  This function is not recommended for the end user.  The four input flags are designated as follows: flag1 = c.headers?; flag2 = c.code?; flag3 = 4th.include.headers?; flag4 = segment.build.headers? Only one of these flags should be true at a time.  This routine scans the headers between xnfa1 and xnfa2, inclusive, and prints the specified text associated with the headers as required by the calling COMPOSE or BUILD function.  This routine requires at least 15.6 Kbytes available in the current heap for a temporary array.

Attributes: M, S

 
DUMP.SEGMENTS

DUMP.SEGMENTS ( n\flag1\flag2\flag3 <"filename"> -- )

This low-level primitive performs the action of BUILD.SEGMENTS, COMPOSE.FORTH.INSTALLER and COMPOSE.C.INSTALLER for all completed segments; See their glossary entries.

This function is not recommended for the end user.  The place input parameter n is IN.PLACE, TO.HERE or USER.SPECIFIED; See their glossary entries.  The three input flags are designated as follows: flag1 = c?; flag2 = full.build?; flag3 = suppress.S-record?. If the c? flag is true, Forth headers are not included in the dump.  If the full.build? flag is true, all of the information needed to fully reconstitute the segment as demanded by BUILD.LIBRARY, BUILD.APPLICATIONS, or BUILD.SEGMENTS is included in the dump, including the PROTOTYPE:, VPROTOTYPE:, EEPROTOTYPE:, C.HEADERS: and FORTH.HEADERS: declarations.  If the full.build? flag is false, only the statements needed by the COMPOSE installer commands are included, and the prototype and header declarations are not dumped.  If the suppress.S.record? input flag is true, the s-record code dump is suppressed as required by the quick compose installer routines.  This routine prints the specified text to a file, printing #saveto and #endsaveto statements to direct the output to the specified "file". This routine requires at least 15.6 Kbytes available in the current heap for a temporary array.

Attributes: M, S

 
DUP

DUP ( w -- w\w )

Duplicates the top cell of the data stack.
Pronunciation: dupe

 
DUP.HEAP.ITEM

DUP.HEAP.ITEM ( xhandle1 -- [xhandle2] or [0\0] )

Given the 32-bit handle xhandle1 of a source heap item, creates a duplicate heap item with identical contents in the same heap and returns its handle xhandle2. Returns 0\0 if xhandle1 is not a valid handle or if there is insufficient memory in the heap.  To copy a heap item into a different heap, use TRANSFER.HEAP.ITEM.
Pronunciation: dupe-heap-item

 
DUP>R

DUP>R ( w -- w )
Return stack: ( R: -- w )

Copies the top cell on the data stack to the return stack.
Pronunciation: dupe-to-r
Attributes: C

 
This page is about: Embedded Forth Language Library Functions and Forth Word Definitions, Forth Compiler and Interpreter, Forth RTOS Kernel Functions – Glossary definitions for v6 Forth language kernel functions (Forth library words) starting with the characters: ! " # $ ' ( * + , - . / 0 1 2 3 4 8 : ; < = > ? @ A B C or D. Forth programming language built-in functions, embedded real time operating system RTOS, Forth firmware programs, embedded Forth language, Forth compiler, Forth interpreter, interpretive computer languages Embedded real time operating system RTOS, Forth firmware programs, embedded Forth language, Forth compiler, Forth interpreter, interpretive computer languages
 
 
Navigation