GLOSSARY OF GENERIC FIGFORTH 2.148


GLOSSARY INDEX

Here you can select the glossary entry of a word. All words in the basic set are documented.

!CSP __ ! __ #> __ #BUFF __ #S __ # __ <# __ <BUILDS __ < __ ' __ (+LOOP) __ (.") __ (;CODE) __ (ABORT) __ (DO) __ (FIND) __ (LINE) __ (LOOP) __ (NUMBER) __ ( __ */MOD __ */ __ * __ +! __ +- __ +BUF __ +LOOP __ +ORIGIN __ + __ , __ --> __ -DUP __ -FIND __ -TRAILING __ - __ ." __ .CPU __ .LINE __ .R __ . __ /MOD __ / __ 0< __ 0= __ 0BRANCH __ 0 __ 1+ __ 1 __ 2! __ 2+ __ 2@ __ 2DUP __ 2 __ 3 __ : __ ;CODE __ ;S __ ; __ = __ >R __ > __ ?COMP __ ?CSP __ ?ERROR __ ?EXEC __ ?LINUX-ERROR __ ?LOADING __ ?PAIRS __ ?STACK __ ?TERMINAL __ ? __ @ __ ABORT __ ABS __ AGAIN __ ALLOT __ AND __ B/BUF __ B/SCR __ BACK __ BASE __ BEGIN __ BLANKS __ BLK __ BLOCK-EXIT __ BLOCK-FILE __ BLOCK-HANDLE __ BLOCK-INIT __ BLOCK __ BL __ BRANCH __ BUFFER __ BYE __ C! __ C, __ C/L __ C@ __ CELL+ __ CFA __ CMOVE __ COLD __ COMPILE __ CONSTANT __ CONTEXT __ COUNT __ CREATE __ CR __ CSP __ CURRENT __ D+- __ D+ __ D.R __ D. __ DABS __ DECIMAL __ DEFINITIONS __ DIGIT __ DISK-ERROR __ DLITERAL __ DMINUS __ DOES> __ DO __ DPL __ DP __ DROP __ DUP __ ELSE __ EMIT __ EMPTY-BUFFERS __ EM __ ENCLOSE __ ENDIF __ END __ ERASE __ ERROR __ EXECUTE __ EXPECT __ FENCE __ FILL __ FIRST __ FLD __ FLUSH __ FOR-VOCS __ FOR-WORDS __ FORGET-VOC __ FORGET __ FORTH __ HERE __ HEX __ HLD __ HOLD __ ID. __ IF __ IMMEDIATE __ INDEX __ INTERPRET __ IN __ I __ KEY __ L! __ L@ __ LATEST __ LEAVE __ LFA __ LIMIT __ LINOS __ LIST __ LITERAL __ LIT __ LOAD __ LOOP __ M* __ M/MOD __ M/ __ MATCH __ MAX __ MESSAGE __ MINUS __ MIN __ MOD __ NFA __ NOOP __ NUMBER __ OFFSET __ OR __ OUT __ OVER __ P! __ P@ __ PAD __ PC! __ PC@ __ PFA __ PREV __ QUERY __ QUIT __ R# __ R/W __ R0 __ R> __ REPEAT __ ROT __ RP! __ RP@ __ RUBOUT __ R __ S->D __ S0 __ SCR __ SET-TERM __ SIGN __ SMUDGE __ SP! __ SP@ __ SPACES __ SPACE __ STATE __ SWAP __ TASK __ TERMIO __ THEN __ TIB __ TOGGLE __ TRAVERSE __ TRIAD __ TYPE __ U< __ U* __ U. __ U/ __ U0 __ UNTIL __ UPDATE __ USER __ USE __ VARIABLE __ VLIST __ VOC-LINK __ VOCABULARY __ WARM __ WARNING __ WHILE __ WIDTH __ WORD __ XOR __ X __ [COMPILE] __ [ __ ] __


GLOSSARY INDEX BY WORDSET

Here you can select the description of a Wordsets: small sets of words that work together. These are intended to give more insight in how to use the words in cooperation.

Note: the first reference under `see also' of a word is the wordset to which it belongs.

COMPILING CONTROL DEFINING DICTIONARY DOUBLE ERRORS FORMATTING INIT INPUT JUGGLING LOGIC MEMORY MISC MULTIPLYING OPERATOR OUTPUT PARSING SCREEN SECURITY STACKS STORAGE STRING SUPERFLUOUS SYSTEM VOCABULARIES Fig-Forth 3.0 Manual




Choose the word you want to know about:

WORDSET COMPILING

  • OVERVIEW OF COMPILING
  • COMPILE
  • DLITERAL
  • LITERAL
  • LIT
  • [COMPILE]
  • WORDSET CONTROL

  • OVERVIEW OF CONTROL
  • (+LOOP)
  • (DO)
  • (LOOP)
  • +LOOP
  • 0BRANCH
  • AGAIN
  • BACK
  • BEGIN
  • BRANCH
  • DO
  • ELSE
  • ENDIF
  • END
  • IF
  • I
  • LEAVE
  • LOOP
  • REPEAT
  • THEN
  • UNTIL
  • WHILE
  • WORDSET DEFINING

  • OVERVIEW OF DEFINING
  • (;CODE)
  • :
  • ;CODE
  • ;
  • <BUILDS
  • CONSTANT
  • CREATE
  • DOES>
  • USER
  • VARIABLE
  • VOCABULARY
  • WORDSET DICTIONARY

  • OVERVIEW OF DICTIONARY
  • '
  • (FIND)
  • ,
  • -FIND
  • ALLOT
  • C,
  • CFA
  • DP
  • FENCE
  • FOR-VOCS
  • FOR-WORDS
  • FORGET-VOC
  • FORGET
  • HERE
  • ID.
  • IMMEDIATE
  • LFA
  • NFA
  • PAD
  • PFA
  • SMUDGE
  • TRAVERSE
  • VLIST
  • WIDTH
  • WORDSET DOUBLE

  • OVERVIEW OF DOUBLE
  • D+
  • DABS
  • DMINUS
  • S->D
  • WORDSET ERRORS

  • OVERVIEW OF ERRORS
  • ?ERROR
  • ERROR
  • MESSAGE
  • WARNING
  • WORDSET FORMATTING

  • OVERVIEW OF FORMATTING
  • #>
  • #S
  • #
  • (NUMBER)
  • +-
  • <#
  • BASE
  • D+-
  • DECIMAL
  • DIGIT
  • DPL
  • FLD
  • HEX
  • HLD
  • HOLD
  • NUMBER
  • SIGN
  • WORDSET INIT

  • OVERVIEW OF INIT
  • (ABORT)
  • +ORIGIN
  • ABORT
  • COLD
  • QUIT
  • WARM
  • WORDSET INPUT

  • OVERVIEW OF INPUT
  • ?TERMINAL
  • EXPECT
  • IN
  • KEY
  • RUBOUT
  • SET-TERM
  • TERMIO
  • TIB
  • WORDSET JUGGLING

  • OVERVIEW OF JUGGLING
  • -DUP
  • 2DUP
  • DROP
  • DUP
  • OVER
  • ROT
  • SWAP
  • WORDSET LOGIC

  • OVERVIEW OF LOGIC
  • 0<
  • 0=
  • <
  • =
  • >
  • AND
  • OR
  • U<
  • XOR
  • WORDSET MEMORY

  • OVERVIEW OF MEMORY
  • !
  • +!
  • 2!
  • 2@
  • @
  • BLANKS
  • C!
  • C@
  • CELL+
  • CMOVE
  • EM
  • ERASE
  • FILL
  • L!
  • L@
  • P!
  • P@
  • PC!
  • PC@
  • TOGGLE
  • WORDSET MISC

  • OVERVIEW OF MISC
  • .CPU
  • EXECUTE
  • NOOP
  • TASK
  • U0
  • X
  • WORDSET MULTIPLYING

  • OVERVIEW OF MULTIPLYING
  • */MOD
  • */
  • M*
  • M/MOD
  • M/
  • U*
  • U/
  • WORDSET OPERATOR

  • OVERVIEW OF OPERATOR
  • *
  • +
  • -
  • /MOD
  • /
  • ABS
  • MAX
  • MINUS
  • MIN
  • MOD
  • WORDSET OUTPUT

  • OVERVIEW OF OUTPUT
  • ."
  • .R
  • .
  • ?
  • CR
  • D.R
  • D.
  • EMIT
  • OUT
  • SPACES
  • SPACE
  • TYPE
  • U.
  • WORDSET PARSING

  • OVERVIEW OF PARSING
  • (.")
  • (
  • ENCLOSE
  • INTERPRET
  • QUERY
  • STATE
  • WORD
  • [
  • ]
  • WORDSET SCREEN

  • OVERVIEW OF SCREEN
  • (LINE)
  • -->
  • .LINE
  • ;S
  • B/SCR
  • C/L
  • INDEX
  • LIST
  • LOAD
  • R#
  • SCR
  • TRIAD
  • WORDSET SECURITY

  • OVERVIEW OF SECURITY
  • !CSP
  • ?COMP
  • ?CSP
  • ?EXEC
  • ?LOADING
  • ?PAIRS
  • ?STACK
  • CSP
  • WORDSET STACKS

  • OVERVIEW OF STACKS
  • >R
  • R0
  • R>
  • RP!
  • RP@
  • R
  • S0
  • SP!
  • SP@
  • WORDSET STORAGE

  • OVERVIEW OF STORAGE
  • #BUFF
  • +BUF
  • B/BUF
  • BLK
  • BLOCK-EXIT
  • BLOCK-FILE
  • BLOCK-HANDLE
  • BLOCK-INIT
  • BLOCK
  • BUFFER
  • DISK-ERROR
  • EMPTY-BUFFERS
  • FIRST
  • FLUSH
  • LIMIT
  • OFFSET
  • PREV
  • R/W
  • UPDATE
  • USE
  • WORDSET STRING

  • OVERVIEW OF STRING
  • -TRAILING
  • BL
  • COUNT
  • MATCH
  • WORDSET SUPERFLUOUS

  • OVERVIEW OF SUPERFLUOUS
  • 0
  • 1+
  • 1
  • 2+
  • 2
  • 3
  • WORDSET SYSTEM

  • OVERVIEW OF SYSTEM
  • ?LINUX-ERROR
  • BYE
  • LINOS
  • WORDSET VOCABULARIES

  • OVERVIEW OF VOCABULARIES
  • CONTEXT
  • CURRENT
  • DEFINITIONS
  • FORTH
  • LATEST
  • VOC-LINK

  • COMPILING

    OVERVIEW:

    The wordset COMPILING contains words that compile See also IMMEDIATE words and numbers. You need special precautions because these words would execute during compilation. Numbers are compiled in line , behind a word that fetches them.


    COMPILE

    STACKEFFECT:

    DESCRIPTION:

    When the word containing COMPILE executes, the execution address of the word following COMPILE is copied (compiled) into the dictionary. This allows specific compilation situations to be handled in addition to simply compiling an execution address (which the interpreter already does).

    GLOSSARY INDEX

    SEE ALSO: COMPILING [COMPILE]


    DLITERAL

    STACKEFFECT: d --- d (executing) d --- (compiling)

    DESCRIPTION:

    If compiling, compile a stack double number into a literal. Later execution of the definition containing the literal will push it to the stack. If executing, the number will remain on the stack.

    GLOSSARY INDEX

    SEE ALSO: COMPILING


    LITERAL

    STACKEFFECT: n --- (compiling)

    DESCRIPTION:

    If compiling, then compile the stack value n as a 16 bit literal. This definition is immediate so that it will execute during a colon definition. The intended use is: : xxx [ calculate ] LITERAL ; Compilation is suspended for the compile time calculation of a value. Compilation is resumed and LITERAL compiles this value.

    GLOSSARY INDEX

    SEE ALSO: COMPILING


    LIT

    STACKEFFECT: --- n

    DESCRIPTION:

    Within a colon-definition, LIT is compiled followed by a 16 bit literal number given during compilation. Later execution of LIT causes the contents of this next dictionary address to be pushed to the stack.

    GLOSSARY INDEX

    SEE ALSO: COMPILING


    [COMPILE]

    STACKEFFECT:

    DESCRIPTION:

    Used in a colon-definition in form:

    : xxx [COMPILE] FORTH ;

    [COMPILE] will force the compilation of an immediate definitions, that would otherwise execute during compilation. The above example will select the FORTH vocabulary then xxx executes, rather than at compile time.

    GLOSSARY INDEX

    SEE ALSO: COMPILING COMPILE


    CONTROL

    OVERVIEW:

    The wordset CONTROL contains words that influence the control flow of a program, i.e. the sequence in which commands are executed in compiled words. With control words you can have actions performed repeatedly, or depending on conditions.


    (+LOOP)

    STACKEFFECT: n ---

    DESCRIPTION:

    The run-time proceedure compiled by +LOOP, which increments the loop index by n and tests for loop completion.

    GLOSSARY INDEX

    SEE ALSO: CONTROL +LOOP


    (DO)

    STACKEFFECT:

    DESCRIPTION:

    The run-time proceedure compiled by DO which moves the loop control parameters to the return stack.

    GLOSSARY INDEX

    SEE ALSO: CONTROL DO


    (LOOP)

    STACKEFFECT:

    DESCRIPTION:

    The run-time proceedure compiled by LOOP which increments the loop index and tests for loop completion.

    GLOSSARY INDEX

    SEE ALSO: CONTROL LOOP


    +LOOP

    STACKEFFECT: n1 --- (run) addr n2 --- (compile)

    DESCRIPTION:

    Used in a colon-definition in the form: DO ... n1 +LOOP At run-time, +LOOP selectively controls branching back to the corresponding DO based on n1 , the loop index and the loop limit. The signed increment n1 is added to the index and the total compared to the limit. The branch back to DO occurs until the new index is equal to or greater than the limit (n1>0), or until the new index is equal to or less than the limit (n1<0). Upon exiting the loop, the parameters are discarded and execution continues ahead. At compile time, +LOOP compiles the run-time word (+LOOP) and the branch offset computed from HERE to the address left on the stack by DO . n2 is used for compile tine error checking.

    GLOSSARY INDEX

    SEE ALSO: CONTROL


    0BRANCH

    STACKEFFECT: f ---

    DESCRIPTION:

    The run-time proceedure to conditionally branch. If f is false (zero), the following in-line parameter is added to the interpretive pointer to branch ahead or back. Compiled by IF , UNTIL , and WHILE .

    GLOSSARY INDEX

    SEE ALSO: CONTROL


    AGAIN

    STACKEFFECT: addr n --- (compiling)

    DESCRIPTION:

    Used in a colon-definition in the form:

    BEGIN ... AGAIN

    At run-time, AGAIN forces execution to return to corresponding BEGIN . There is no effect on the stack. Execution cannot leave this loop (unless R> DROP is executed one level below). At compile time, AGAIN compiles BRANCH with an offset from HERE to addr. n is used for compile-time error checking.

    GLOSSARY INDEX

    SEE ALSO: CONTROL


    BACK

    STACKEFFECT: addr --

    DESCRIPTION:

    Calculate the backward branch offset from HERE to addr and compile into the next available dictionary memory address.

    GLOSSARY INDEX

    SEE ALSO: CONTROL LOOP UNTIL


    BEGIN

    STACKEFFECT: --- addr n (compiling)

    DESCRIPTION:

    Occurs in a colon-definition in form:

    BEGIN ... UNTIL

    BEGIN ... AGAIN

    BEGIN ... WHILE ... REPEAT

    At run-time, BEGIN marks the start of a sequence that may be repetitively executed. It serves as a return point from the corresponding UNTIL , AGAIN or REPEAT When executing UNTIL a return to BEGIN will occur if the top of the stack is false; for AGAIN and REPEAT a return to BEGIN always occurs. At compile time BEGIN leaves its return address and n for compiler error checking.

    GLOSSARY INDEX

    SEE ALSO: CONTROL


    BRANCH

    STACKEFFECT:

    DESCRIPTION:

    The run-time proceedure to unconditionally branch. An in-line offset is added to the interpretive pointer IP to branch ahead or back. BRANCH is compiled by ELSE , AGAIN , REPEAT .

    GLOSSARY INDEX

    SEE ALSO: CONTROL


    DO

    STACKEFFECT: n1 n2 --- (execute) addr n --- (compile)

    DESCRIPTION:

    Occurs in a colon-definition in form: DO ... LOOP At run time, DO begins a sequence with repetitive execution controlled by a loop limit n1 and an index with initial value n2 . DO removes these from the stack. Upon reaching LOOP the index is incremented by one. Until the new index equals or exceeds the limit, execution loops back to just after DO ; otherwise the loop parameters are discarded and execution continues ahead. Both n1 and n2 are determined at run-time and may be the result of other operations. Within a loop I will copy the current value of the index to the stack. When compiling within the colon definition, DO compiles (DO) , leaves the following address addr and n for later error checking.

    GLOSSARY INDEX

    SEE ALSO: CONTROL I LOOP +LOOP LEAVE


    ELSE

    STACKEFFECT: addr1 n1 --- addr2 n2 (compiling)

    DESCRIPTION:

    Occurs within a colon-definition in the form:

    IF ... ELSE ... ENDIF

    At run-time, ELSE executes after the true part following IF . ELSE forces execution to skip over the following false part and resumes execution after the ENDIF . It has no stack effect. At compile-time ELSE emplaces BRANCH reserving a branch offset, leaves the address addr2 and n2 for error testing. ELSE also resolves the pending forward branch from IF by calculating the offset from addr1 to HERE and storing at addr1 .

    GLOSSARY INDEX

    SEE ALSO: CONTROL


    ENDIF

    STACKEFFECT: addr n --- (compile)

    DESCRIPTION:

    Occurs in a colon-definition in form: IF ... ENDIF x IF ... ELSE ... ENDIF At run-time, ENDIF serves only as the destination of a forward branch from IF or ELSE . It marks the conclusion of the conditional structure. THEN is another name for ENDIF . Both names are supported in fig-FORTH. At compile-time, ENDIF computes the forward branch offset from addr to HERE and stores it at addr . n is used for error tests.

    GLOSSARY INDEX

    SEE ALSO: CONTROL IF ELSE


    END

    STACKEFFECT:

    DESCRIPTION:

    This is an 'alias' or duplicate definition for UNTIL .

    GLOSSARY INDEX

    SEE ALSO: CONTROL BEGIN


    IF

    STACKEFFECT: f --- (run-time) / --- addr n (compile)

    DESCRIPTION:

    Occurs is a colon-definition in form: IF (tp) ... ENDIF or IF (tp) ... ELSE (fp) ... ENDIF At run-time, IF selects execution based on a boolean flag. If f is true (non-zero), execution continues ahead thru the true part. If f is false (zero), execution skips till just after ELSE to execute the false part. After either part, execution resumes after ENDIF . ELSE and its false part are optional.; if missing, false execution skips to just after ENDIF . At compile-time IF compiles 0BRANCH and reserves space for an offset at addr . addr and n are used later for resolution of the offset and error testing.

    GLOSSARY INDEX

    SEE ALSO: CONTROL


    I

    STACKEFFECT: --- n

    DESCRIPTION:

    Used within a do-loop to copy the loop index to the stack. Other use is implementation dependent.

    GLOSSARY INDEX

    SEE ALSO: CONTROL R


    LEAVE

    STACKEFFECT:

    DESCRIPTION:

    Force termination of a do-loop at the next opportunity by setting the loop limit equal to the current value of the index. The index itself remains unchanged, and execution proceeds normally until LOOP or +LOOP is encountered.

    GLOSSARY INDEX

    SEE ALSO: CONTROL


    LOOP

    STACKEFFECT: addr n --- (compiling)

    DESCRIPTION:

    Occurs in a colon-definition in form: DO ... LOOP At run-time, LOOP selectively controls branching back to the corresponding DO based on the loop index and limit. The loop index is incremented by one and compared to the limit. The branch back to DO occurs until the index equals or exceeds the limit; at that time, the parameters are discarded and execution continues ahead. At compile-time, LOOP compiles (LOOP) and uses addr to calculate an offset to DO . n is used for error testing.

    GLOSSARY INDEX

    SEE ALSO: CONTROL


    REPEAT

    STACKEFFECT: addr n --- (compiling)

    DESCRIPTION:

    Used within a colon-definition in the form: BEGIN ... WHILE ... REPEAT At run-time, REPEAT forces an unconditional branch back to just after the corresponding BEGIN . At compile-time, REPEAT compiles BRANCH and the offset from HERE to addr. n is used for error testing.

    GLOSSARY INDEX

    SEE ALSO: CONTROL WHILE


    THEN

    STACKEFFECT:

    DESCRIPTION:

    An alias for ENDIF .

    GLOSSARY INDEX

    SEE ALSO: CONTROL


    UNTIL

    STACKEFFECT: f --- (run-time) addr n --- (compile)

    DESCRIPTION:

    Occurs within a colon-definition in the form: BEGIN ... UNTIL At run-time, UNTIL controls the conditional branch back to the corresponding BEGIN If f is false, execution returns to just after BEGIN . if true, execution continues ahead. At compile-time, UNTIL compiles 0BRANCH and an offset from HERE to addr. n is used for error tests.

    GLOSSARY INDEX

    SEE ALSO: CONTROL


    WHILE

    STACKEFFECT: f --- (run-time) / ad1 nl --- ad1 n1 ad2 n2

    DESCRIPTION:

    Occurs in a colon-definition in the form: BEGIN ... WHILE (tp) ... REPEAT At run-time, WHILE selects conditional execution based on boolean flag f . If f is true (non-zero), WHILE continues execution of the true part thru to REPEAT , which then branches back to BEGIN . If f is false (zero), execution skips to just after REPEAT , exiting the structure. At compile time, WHILE emplaces 0BRANCH and leaves ad2 of the reserved offset. The stack values will be resolved by REPEAT .

    GLOSSARY INDEX

    SEE ALSO: CONTROL


    DEFINING

    OVERVIEW:

    The wordset DEFINING contains words that add new entries to the dictionary. A number of such defining words are predefined, but there is also the possibility to make new defining words, using <BUILDS and DOES> .


    (;CODE)

    STACKEFFECT:

    DESCRIPTION:

    The run-time proceedure, compiled by ;CODE, that rewrites the code field of the most recently defined word to point to the following machine code sequence.

    GLOSSARY INDEX

    SEE ALSO: DEFINING ;CODE


    :

    STACKEFFECT:

    DESCRIPTION:

    Used in the form called a colon-definition:

    : cccc ... ;

    Creates a dictionary entry defining cccc as equivalent to the following sequence of Forth word definitions '...' until the next ';' or ';CODE' . The compiling process is done by the text interpreter as long as STATE is non-zero. Other details are that the CONTEXT vocabulary is set to the CURRENT vocabulary and that words with the precedence bit set (P) are executed rather than being compiled.

    GLOSSARY INDEX

    SEE ALSO: DEFINING


    ;CODE

    STACKEFFECT:

    DESCRIPTION:

    Used in the form: : cccc .... ;CODE assembly mnemonics Stop compilation and terminate a new defining word cccc by compiling (;CODE). Set the CONTEXT vocabulary to ASSEMBLER , assembling to machine code the following mnemonics. When cccc later executes in the form: cccc nnnn the word nnnn will be created with its execution proceedure given by the machine code following cccc . That is, when nnnn is executed, it does so by jumping to the code after nnnn . An existing defining word must exist in cc prior to ;CODE .

    GLOSSARY INDEX

    SEE ALSO: DEFINING (;CODE)


    ;

    STACKEFFECT:

    DESCRIPTION:

    Terminate a colon-definition and stop further compilation. Compiles the run-time ;S .

    GLOSSARY INDEX

    SEE ALSO: DEFINING


    <BUILDS

    STACKEFFECT:

    DESCRIPTION:

    Used within a colon-definition:

    : cccc <BUILDS ... DOES> ... ;

    Each time cccc is executed, <BUILDS defines a new word with a high-level execution proceedure. Executing cccc in the form: cccc nnnn uses <BUILDS to create a dictionary entry for nnnn with a call to the DOES> part for nnnn . When nnnn is later executed, it has the address of its parameter area on the stack and executes the words after DOES> in cccc . <BUILDS and DOES> allow runtime proceedures to written in high-level rather than in assembler code (as required by ;CODE ).

    GLOSSARY INDEX

    SEE ALSO: DEFINING


    CONSTANT

    STACKEFFECT: n ---

    DESCRIPTION:

    A defining word used in the form: n CONSTANT cccc to create word cccc , with its parameter field containing n . When cccc is later executed, it will push the value of n to the stack.

    GLOSSARY INDEX

    SEE ALSO: DEFINING VARIABLE


    CREATE

    STACKEFFECT:

    DESCRIPTION:

    A defining word used in the form: CREATE cccc by such words as CODE and CONSTANT to create a dictionary header for a Forth definition. The code field contains the address of the words parameter field.

    GLOSSARY INDEX

    SEE ALSO: DEFINING


    DOES>

    STACKEFFECT:

    DESCRIPTION:

    A word which defines the run-time action within a high-level defining word. DOES> alters the code field and first parameter of the new word to execute the sequence of compiled word addresses following DOES> . Used in combination with <BUILDS . When the DOES> part executes it begins with the address of the first parameter of the new word on the stack. This allows interpretation using this area or its contents. Typical uses include the Forth assembler, multidimensional arrays, and compiler generation.

    GLOSSARY INDEX

    SEE ALSO: DEFINING


    USER

    STACKEFFECT: n ---

    DESCRIPTION:

    A defining word used in the form: n USER cccc which creates a user variable cccc . The parameter field of cccc contains n as a fixed offset relative to the user pointer register UP for this user variable. When cccc is later executed, it places the sum of its offset and the user area base address on the stack as the storage address of that particular variable. In fig-Forth the UP is fixed.

    GLOSSARY INDEX

    SEE ALSO: DEFINING VARIABLE +ORIGIN


    VARIABLE

    STACKEFFECT:

    DESCRIPTION:

    A defining word used in the form: n VARIABLE cccc When VARIABLE is executed, it creates the definition cccc with its parameter field initialized to n . When cccc is later executed, the address of its parameter field (containing n ) is left on the stack, so that a fetch or store may access this location.

    GLOSSARY INDEX

    SEE ALSO: DEFINING USER CONSTANT


    VOCABULARY

    STACKEFFECT:

    DESCRIPTION:

    A defining word used in the form: VOCABULARY cccc to create a vocabulary definition cccc . Subsequent use of cccc will make it the CONTEXT vocabulary which is searched first by INTERPRET . The sequence cccc DEFINITIONS also make cccc the CURRENT vocabulary into which new definitions are placed. A vocabulary parameter field contains at first the dovoc pointer, then it contains a dummy name field (DFNA) with a name " " (blank) , a dummy link field (DLFA) and the vocabulary link field address ( VLFA ). Actually executing the vocabulary means storing its DLFA into CONTEXT . The VLFA points to the VLFA of the next vocabulary or 0 for the end. In fig-FORTH, cccc will be so chained as to include all definitions of the vocabulary in which cccc is itself defined. All vocabularys ultimately chain to Forth. By convention, vocabulary names are to be declared IMMEDIATE .

    GLOSSARY INDEX

    SEE ALSO: DEFINING VOC-LINK


    DICTIONARY

    OVERVIEW:

    The wordset DICTIONARY contains words that at a lower level than the wordset DEFINING concern the memory area that is allocated to the dictionary. They may add data to the dictionary at the expense of the free space, one cell or one byte at a time, or allocate a buffer at once. The dictionary space may also be shrunk, and the words that were there are lost. The dictionary entry of a word is represented by its lowest address. Based on that an entry may considered a record with fields. Words to access those fields also belong to this wordset.


    '

    STACKEFFECT: --- addr

    DESCRIPTION:

    Used in the form: . ' nnnn Leaves the parameter field address of dictionary word nnnn. As a compiler directive, executes in a colon-definition to compile the address as a literal. If the word is not found after a search of CONTEXT and CURRENT , an appropriate error message is given.

    GLOSSARY INDEX

    SEE ALSO: DICTIONARY CFA LFA NFA PFA


    (FIND)

    STACKEFFECT: addr1 addr2 --- pfa b tf (ok) addr1 addr2 .--- ff (bad)

    DESCRIPTION:

    Searches the dictionary starting at the name field address addr2, matching to the text at addr1. Returns parameter field address, length byte of name field and boolean true for a good match. If no match is found, only a boolean false is left.

    GLOSSARY INDEX

    SEE ALSO: DICTIONARY FIND


    ,

    STACKEFFECT: n ---

    DESCRIPTION:

    Store n into the next available dictionary memory cell, advancing the dictionary pointer.

    GLOSSARY INDEX

    SEE ALSO: DICTIONARY DP C


    -FIND

    STACKEFFECT: --- pfa b tf (found) --- ff (not found)

    DESCRIPTION:

    Accepts the next text word (delimited by blanks) in the input stream to HERE , and searches the CONTEXT and then CURRENT vocabularies for a matching entry. If found, the dictionary entry's parameter field address, its length byte, and a boolean true is left. Otherwise, only a boolean false is left.

    GLOSSARY INDEX

    SEE ALSO: DICTIONARY (FIND)


    ALLOT

    STACKEFFECT: n ---

    DESCRIPTION:

    Add the signed number to the dictionary pointer DP . May be used to reserve dictionary space or re-origin memory. As the Pentium is a byte-addressable machine n counts bytes.

    GLOSSARY INDEX

    SEE ALSO: DICTIONARY CELL+


    C,

    STACKEFFECT: b ---

    DESCRIPTION:

    Store 8 bits of b into the next available dictionary byte, advancing the dictionary pointer.

    GLOSSARY INDEX

    SEE ALSO: DICTIONARY DP


    CFA

    STACKEFFECT: pfa --- cfa

    DESCRIPTION:

    Convert the parameter field address of a definition to its code field address.

    GLOSSARY INDEX

    SEE ALSO: DICTIONARY ' PFA


    DP

    STACKEFFECT: ---- addr

    DESCRIPTION:

    A user variable, the dictionary pointer, which contains the address of the next free memory above the dictionary. The value may be read by HERE and altered by ALLOT .

    GLOSSARY INDEX

    SEE ALSO: DICTIONARY


    FENCE

    STACKEFFECT: --- addr

    DESCRIPTION:

    A user variable containing an address below which FORGET ting is trapped. To forget below this point the user must alter the contents of FENCE .

    GLOSSARY INDEX

    SEE ALSO: DICTIONARY


    FOR-VOCS

    STACKEFFECT: x1..xn xt ---

    DESCRIPTION:

    For all vocabularies execute xt with as data the VLFA of those words. xt must have the stack diagram x1..xn vlfa --- x1..xn

    GLOSSARY INDEX

    SEE ALSO: DICTIONARY FOR-WORDS EXECUTE


    FOR-WORDS

    STACKEFFECT: x1...xn xt ---

    DESCRIPTION:

    For all words in the current context execute xt with as data x1..xn plus the NFA of those words. xt must have the stack diagram x1..xn nfa --- x1..xn

    GLOSSARY INDEX

    SEE ALSO: DICTIONARY FOR-VOCS EXECUTE


    FORGET-VOC

    STACKEFFECT: n1 addr -- n1

    DESCRIPTION:

    Forget all words below n1 from the vocabulary whose VLFA is given by addr . Leave n1 as this word is intended to be used with FOR-VOCS .

    GLOSSARY INDEX

    SEE ALSO: DICTIONARY FORGET


    FORGET

    STACKEFFECT:

    DESCRIPTION:

    Executed in the form: FORGET cccc Deletes definition named cccc from the dictionary with all entries physically following it. In fig-FORTH, an error message will occur if the CURRENT and CONTEXT vocabularies are not currently the same.

    GLOSSARY INDEX

    SEE ALSO: DICTIONARY FENCE


    HERE

    STACKEFFECT: --- addr

    DESCRIPTION:

    Leave the address of the next available dictionary location.

    GLOSSARY INDEX

    SEE ALSO: DICTIONARY DP


    ID.

    STACKEFFECT: addr --

    DESCRIPTION:

    Print a definition's name from its name field address.

    GLOSSARY INDEX

    SEE ALSO: DICTIONARY ' PFA NFA


    IMMEDIATE

    STACKEFFECT:

    DESCRIPTION:

    Mark the most recently made definition so that when encountered at compile time, it will be executed rather than being compiled, i.e. the precedence bit in its header is set. This method allows definitions to handle unusual compiling situations, rather than build them into the fundamental compiler. The user may force compilation of an immediate definition by preceeding it with [COMPILE] .

    GLOSSARY INDEX

    SEE ALSO: DICTIONARY


    LFA

    STACKEFFECT: pfa --- lfa

    DESCRIPTION:

    Convert the parameter field address of a dictionary definition to its link field address.

    GLOSSARY INDEX

    SEE ALSO: DICTIONARY ' PFA


    NFA

    STACKEFFECT: pfa --- nfa

    DESCRIPTION:

    Convert the parameter field address of a definition to its name field.

    GLOSSARY INDEX

    SEE ALSO: DICTIONARY ' PFA


    PAD

    STACKEFFECT: --- addr

    DESCRIPTION:

    Leave the address of the text output buffer, which is a fixed offset above HERE .

    GLOSSARY INDEX

    SEE ALSO: DICTIONARY


    PFA

    STACKEFFECT: nfa --- pfa

    DESCRIPTION:

    Convert the name field address of a compiled definition to its parameter field address.

    GLOSSARY INDEX

    SEE ALSO: DICTIONARY ' CFA LFA NFA


    SMUDGE

    STACKEFFECT:

    DESCRIPTION:

    Used during word definition to toggle the "smudge bit" in a definitions' name field. This prevents an uncompleted definition from being found during dictionary searches, until compiling is completed without error.

    GLOSSARY INDEX

    SEE ALSO: DICTIONARY IMMEDIATE


    TRAVERSE

    STACKEFFECT: addr1 n --- addr2

    DESCRIPTION:

    Move across the name field of a fig-FORTH variable length name field. addr1 is the address of either the length byte or the last letter. If n=1, the motion is toward hi memory; if n=-l, the motion is toward low memory. The addr2 resulting is address of the other end of the name.

    GLOSSARY INDEX

    SEE ALSO: DICTIONARY NFA PFA


    VLIST

    STACKEFFECT:

    DESCRIPTION:

    List the names of the definitions in the context vocabulary.

    GLOSSARY INDEX

    SEE ALSO: DICTIONARY


    WIDTH

    STACKEFFECT: --- addr

    DESCRIPTION:

    In fig-FORTH, a user variable containing the maximum number of letters saved in the compilation of a definitions' name. ( Characters not saved need not match in a dictionary search). It must be 1 thru 31, with a default value of 31. The name character count and its natural characters are saved, up to the value in WIDTH . The value may be changed at any time within the above limits.

    GLOSSARY INDEX

    SEE ALSO: DICTIONARY


    DOUBLE

    OVERVIEW:

    The wordset DOUBLE contains words that manipulate double's. In this 32 Forth you would never need double's if it weren't for the NUMBER formatting wordset that uses them exclusively.


    D+

    STACKEFFECT: d1 d2 --- dsum

    DESCRIPTION:

    Leave the double number sum of two double numbers.

    GLOSSARY INDEX

    SEE ALSO: DOUBLE DMINUS +


    DABS

    STACKEFFECT: d --- ud

    DESCRIPTION:

    Leave the absolute value ud of a double number.

    GLOSSARY INDEX

    SEE ALSO: DOUBLE DMINUS


    DMINUS

    STACKEFFECT: d1 --- d2

    DESCRIPTION:

    Leave the double number two's complement of a double number, i.e. d2 is -d1

    GLOSSARY INDEX

    SEE ALSO: DOUBLE D+


    S->D

    STACKEFFECT: n --- d

    DESCRIPTION:

    Sign extend a single number to form a double number.

    GLOSSARY INDEX

    SEE ALSO: DOUBLE


    ERRORS

    OVERVIEW:

    The wordset ERRORS contains words to handle errors.


    ?ERROR

    STACKEFFECT: f n --

    DESCRIPTION:

    Issue an error message number n , if the boolean flag is true.

    GLOSSARY INDEX

    SEE ALSO: ERRORS ERROR


    ERROR

    STACKEFFECT: line --- in blk

    DESCRIPTION:

    Execute error notification and restart of system. WARNING is first examined. If 1, the text of line n , relative to screen 4 of drive O is printed. This line number may be positive or negative, and beyond just screen 4. If WARNING is zero, n is just printed as a message number (non disc installation). If WARNING is -l, the definition (ABORT) is executed, normally a warm start via QUIT .

    GLOSSARY INDEX

    SEE ALSO: ERRORS QERROR


    MESSAGE

    STACKEFFECT: n --

    DESCRIPTION:

    Print on the selected output device the text of line n relative to screen 4 of drive 0. n may be positive or negative. MESSAGE may be used to print incidental text such as report headers. If WARNING is zero, the message will simply be printed as a number (disc unavailable).

    GLOSSARY INDEX

    SEE ALSO: ERRORS


    WARNING

    STACKEFFECT: --- addr

    DESCRIPTION:

    A user variable containing a value controlling messages. If = 1 disc is present, and screen 4 of drive 0 is the base location for messages. If = 0, no disc is present and messages will be presented by number. If = -1, execute (ABORT) for a user specified proceedure.

    GLOSSARY INDEX

    SEE ALSO: ERRORS MESSAGE ERROR


    FORMATTING

    OVERVIEW:

    The wordset FORMATTING generates formatted output for numbers, i.e. printing the digits in a field with a certain width, possibly with sign etc. This is possible in any number base. (Normally base 10 is used, which means that digits are found as a remainder by dividing by 10). Formatting in Forth is always based on double numbers. Single numbers are handled by converting them to double first. This requires some double precision operators to be present in the Forth core. See also DOUBLE wordset. See also MULTIPLYING wordset.


    #>

    STACKEFFECT: d --- addr count

    DESCRIPTION:

    Terminates numeric output conversion by dropping d, leaving the text address and character count suitable for TYPE.

    GLOSSARY INDEX

    SEE ALSO: FORMATTING


    #S

    STACKEFFECT: d1 --- d2

    DESCRIPTION:

    Generates ascii text in the text output buffer, by the use of #, until a zero double number n2 results. Used between <# and #>.

    GLOSSARY INDEX

    SEE ALSO: FORMATTING


    #

    STACKEFFECT: d1 --- d2

    DESCRIPTION:

    Generate from a double number d1, the next ascii character which is placed in an output string. Result d2 is the quotient after division by BASE, and is maintained for further processing. Used between <# and #>.

    GLOSSARY INDEX

    SEE ALSO: FORMATTING #S


    (NUMBER)

    STACKEFFECT: d1 addr1 --- d2 addr2

    DESCRIPTION:

    Convert the ascii text beginning at addr1+l with regard to BASE . The new value is accumulated into double number d1 , being left as double number d2 . addr2 is the address of the first unconvertable digit.

    GLOSSARY INDEX

    SEE ALSO: FORMATTING NUMBER


    +-

    STACKEFFECT: n1 n2 --- n3

    DESCRIPTION:

    Apply the sign of n2 to n1 , which is left as n3 .

    GLOSSARY INDEX

    SEE ALSO: FORMATTING SIGN #S <# D+-


    <#

    STACKEFFECT:

    DESCRIPTION:

    Setup for pictured numeric output formatting using the words: <# # #S SIGN #> The conversion is done on a double number producing text at PAD .

    GLOSSARY INDEX

    SEE ALSO: FORMATTING DPL HLD HOLD FLD


    BASE

    STACKEFFECT: --- addr

    DESCRIPTION:

    A user variable containing the current number base used for input and output conversion.

    GLOSSARY INDEX

    SEE ALSO: FORMATTING DECIMAL HEX <#


    D+-

    STACKEFFECT: d1 n --- d2

    DESCRIPTION:

    Apply the sign of n to the double number d1 , leaving it as d2 .

    GLOSSARY INDEX

    SEE ALSO: FORMATTING SIGN #S <# +-


    DECIMAL

    STACKEFFECT:

    DESCRIPTION:

    Set the numeric conversion BASE for decimal input-output.

    GLOSSARY INDEX

    SEE ALSO: FORMATTING HEX


    DIGIT

    STACKEFFECT: c n1 --- n2 tf (ok) c n1 --- ff (bad)

    DESCRIPTION:

    Converts the ascii character c (using base n1 ) to its binary equivalent n2 , accompanied by a true flag. If the conversion is invalid, leaves only a false flag.

    GLOSSARY INDEX

    SEE ALSO: FORMATTING


    DPL

    STACKEFFECT: ---- addr

    DESCRIPTION:

    A user variable containing the number of digits to the right of the decimal on double integer input. It may also be used hold output column location of a decimal point, in user generated formating. The default value on single number input is -1.

    GLOSSARY INDEX

    SEE ALSO: FORMATTING <# FLD HLD


    FLD

    STACKEFFECT: --- addr

    DESCRIPTION:

    A user variable for control of number output field width. Presently unused in fig-FORTH.

    GLOSSARY INDEX

    SEE ALSO: FORMATTING


    HEX

    STACKEFFECT:

    DESCRIPTION:

    Set the numeric conversion BASE for hexadecimal (base 16) input-output.

    GLOSSARY INDEX

    SEE ALSO: FORMATTING DECIMAL


    HLD

    STACKEFFECT: --- addr

    DESCRIPTION:

    A user variable that holds the address of the latest character of text during numeric output conversion.

    GLOSSARY INDEX

    SEE ALSO: FORMATTING <# DPL FLD


    HOLD

    STACKEFFECT: c ---

    DESCRIPTION:

    Add the character c to the beginning of the output string. It must be executed for numeric formatting inside a <# and #> construct .

    GLOSSARY INDEX

    SEE ALSO: FORMATTING # DIGIT


    NUMBER

    STACKEFFECT: addr --- d

    DESCRIPTION:

    Convert a character string left at addr with a preceeding count, to a signed double number d , using the current numeric base. If a decimal point is encountered in the text, its position will be given in DPL , but no other effect occurs. If numeric conversion is not possible, an error message will be given.

    GLOSSARY INDEX

    SEE ALSO: FORMATTING BASE


    SIGN

    STACKEFFECT: n d --- d

    DESCRIPTION:

    Stores an ascii "-" sign just before a converted numeric output string in the text output buffer when n is negative. n is discarded but double number d is maintained. Must be used between <# and #> .

    GLOSSARY INDEX

    SEE ALSO: FORMATTING +- D+-


    INIT

    OVERVIEW:

    The wordset INIT contains words to initialise or reinitialise Forth.


    (ABORT)

    STACKEFFECT:

    DESCRIPTION:

    Executes after an error when WARNING is -1. This word normally executes ABORT, but may be altered (with care) to a user's alternative proceedure AP as follows: ' AP CFA ' (ABORT) !.

    GLOSSARY INDEX

    SEE ALSO: INIT


    +ORIGIN

    STACKEFFECT: n --- addr

    DESCRIPTION:

    Leave the memory address relative by n bytes to the area from which the user variables are initialised, so one can access or modify the boot-up parameters. A user variable addresses with an offset from the initialisation for U0, which is at 0 CELL+ +ORIGIN . This can be swapped to get a fresh set of user variables. One can access or modify the boot-up parameters, prior to saving a customised boot image, or to change the initialisation by COLD.

    GLOSSARY INDEX

    SEE ALSO: INIT (ABORT) USER


    ABORT

    STACKEFFECT:

    DESCRIPTION:

    Clear the stacks and enter the execution state. Set BASE to decimal.Note how this is different from COLD , where the bootup value is reinstalled(!) Return control to the operators terminal, printing a startup message with the version number.

    GLOSSARY INDEX

    SEE ALSO: INIT WARM


    COLD

    STACKEFFECT:

    DESCRIPTION:

    The cold start proceedure to adjust all user variables to their intial values, i.a. the stacks and the dictionary pointers. Restart via ABORT . May be called from the terminal to remove application programs and restart. Opens the file that contains the blocks.

    GLOSSARY INDEX

    SEE ALSO: INIT WARM BLOCK LIST


    QUIT

    STACKEFFECT:

    DESCRIPTION:

    Clear the return stack, stop compilation, and return control to the operators terminal. No message is given.

    GLOSSARY INDEX

    SEE ALSO: INIT


    WARM

    STACKEFFECT:

    DESCRIPTION:

    Discard blocks; they may not be written back to mass storage. Clear the stacks and enter the execution state. Return control to the operators terminal, printing a startup message with the version number.

    GLOSSARY INDEX

    SEE ALSO: INIT ABORT


    INPUT

    OVERVIEW:

    The wordset INPUT contains words to get input from the terminal and such. For disk I/O: See also STORAGE


    ?TERMINAL

    STACKEFFECT: --- f

    DESCRIPTION:

    Perform a test of the terminal keyboard for a break request. Any key pressed is interpreted as such and the key is consumed. A true flag indicates actuation.

    GLOSSARY INDEX

    SEE ALSO: INPUT KEY EXPECT


    EXPECT

    STACKEFFECT: addr count ---

    DESCRIPTION:

    Transfer characters from the terminal to address, until a "return" or the count of characters have been received. Rely on the operating system for input editing. One or more nulls are added at the end of the text.

    GLOSSARY INDEX

    SEE ALSO: INPUT KEY ?TERMINAL


    IN

    STACKEFFECT: --- addr

    DESCRIPTION:

    A user variable containing the byte offset within the current input text buffer (terminal or disc) from which the next text will be accepted. WORD uses and moves the value of IN .

    GLOSSARY INDEX

    SEE ALSO: INPUT


    KEY

    STACKEFFECT: --- c

    DESCRIPTION:

    Leave the ascii value of the next terminal key struck.

    GLOSSARY INDEX

    SEE ALSO: INPUT EXPECT ?TERMINAL


    RUBOUT

    STACKEFFECT: --- c

    DESCRIPTION:

    A user variable, leaving the key code that must delete the last character from the input buffer. In this fig-Forth it is not used

    GLOSSARY INDEX

    SEE ALSO: INPUT USER


    SET-TERM

    STACKEFFECT: len b ---

    DESCRIPTION:

    Set the terminal length to len and toggle the c_lflag field with b in the termio structure TERMIO . In particular toggling with 0AH makes that the terminal doesn't wait for a <return>.

    GLOSSARY INDEX

    SEE ALSO: INPUT SET-TERM


    TERMIO

    STACKEFFECT: --- addr

    DESCRIPTION:

    Leave the address of the terminal description, this has the layout of a the c-structure termio .

    GLOSSARY INDEX

    SEE ALSO: INPUT SET-TERM


    TIB

    STACKEFFECT: --- addr

    DESCRIPTION:

    A user variable containing the address of the terminal input buffer.

    GLOSSARY INDEX

    SEE ALSO: INPUT


    JUGGLING

    OVERVIEW:

    The wordset JUGGLING contains words that change the lifo-buffer. The necessity for this arise, because the data you want to feed to a program is not directly accessible, i.e. on top of the stack. It also possible that you need the same data twice, because you have to feed it to two different program's. Design your program such that you need them as little as possible, because they are confusing.


    -DUP

    STACKEFFECT: n1 --- n1 (if zero) / n1 --- n1 n1 (non-zero)

    DESCRIPTION:

    Reproduce n1 only if it is non-zero. This is usually used to copy a value just before IF , to eliminate the need for an ELSE part to drop it.

    GLOSSARY INDEX

    SEE ALSO: JUGGLING DUP


    2DUP

    STACKEFFECT: d --- d d

    DESCRIPTION:

    Duplicate the double number on the stack.

    GLOSSARY INDEX

    SEE ALSO: JUGGLING OVER


    DROP

    STACKEFFECT: n ---

    DESCRIPTION:

    Drop the number from the stack.

    GLOSSARY INDEX

    SEE ALSO: JUGGLING DUP


    DUP

    STACKEFFECT: n --- n n

    DESCRIPTION:

    Duplicate the value on the stack.

    GLOSSARY INDEX

    SEE ALSO: JUGGLING OVER


    OVER

    STACKEFFECT: nl n2 --- nl n2 n1

    DESCRIPTION:

    Copy the second stack value, placing it as the new top.

    GLOSSARY INDEX

    SEE ALSO: JUGGLING DUP


    ROT

    STACKEFFECT: nl n2 n3 --- n2 n3 nl

    DESCRIPTION:

    Rotate the top three values on the stack, bringing the third to the top.

    GLOSSARY INDEX

    SEE ALSO: JUGGLING SWAP


    SWAP

    STACKEFFECT: nl n2 --- n2 n1

    DESCRIPTION:

    Exchange the top two values on the stack.

    GLOSSARY INDEX

    SEE ALSO: JUGGLING ROT


    LOGIC

    OVERVIEW:

    The wordset LOGIC contains logic operators and comparison operators. A comparison operators (such as = ) delivers a logical flag, 1 for true, 0 for false, representing a condition (such as that two numbers are equal). The logical operators ( AND etc.) work on all 32, one by one. In this way they are useful for mask operations, as well as for combining conditions represented as flags. But beware that IF only cares whether the top of the stack is non-zero, such that to IF - can mean non-equal. Such conditions cannot be directly combined using logical operators, but 0= 0= can help.


    0<

    STACKEFFECT: n --- f

    DESCRIPTION:

    Leave a true flag if the number is less than zero (negative), otherwise leave a false flag.

    GLOSSARY INDEX

    SEE ALSO: LOGIC <


    0=

    STACKEFFECT: n --- f

    DESCRIPTION:

    Leave a true flag f is the number n is equal to zero, otherwise leave a false flag.

    GLOSSARY INDEX

    SEE ALSO: LOGIC =


    <

    STACKEFFECT: n1 n2 --- f

    DESCRIPTION:

    Leave a true flag if n1 is less than n2 ;otherwise leave a false flag.

    GLOSSARY INDEX

    SEE ALSO: LOGIC = > 0<


    =

    STACKEFFECT: n1 n2 --- f

    DESCRIPTION:

    Leave a true flag if n1=n2 ; otherwise leave a false flag.

    GLOSSARY INDEX

    SEE ALSO: LOGIC < > 0= -


    >

    STACKEFFECT: n1 n2 --- f

    DESCRIPTION:

    Leave a true flag if n1 is greater than n2 ; otherwise a false flag.

    GLOSSARY INDEX

    SEE ALSO: LOGIC > = 0<


    AND

    STACKEFFECT: n1 n2 --- n2

    DESCRIPTION:

    Leave the bitwise logical and of n1 and n2 as n3 .

    GLOSSARY INDEX

    SEE ALSO: LOGIC XOR OR


    OR

    STACKEFFECT: n1 n2 --- or

    DESCRIPTION:

    Leave the bit-wise logical or of two 32 bit values.

    GLOSSARY INDEX

    SEE ALSO: LOGIC AND XOR


    U<

    STACKEFFECT: u1 u2 --- f

    DESCRIPTION:

    Leave a true flag if u1 is less than u2 ; otherwise leave a false flag.(Interpreted as unsigned numbers).

    GLOSSARY INDEX

    SEE ALSO: LOGIC <


    XOR

    STACKEFFECT: nl n2 --- xor

    DESCRIPTION:

    Leave the bitwise logical exclusive or of two values.

    GLOSSARY INDEX

    SEE ALSO: LOGIC AND OR


    MEMORY

    OVERVIEW:

    The wordset MEMORY contains words to fetch and store numbers from doubles, cells or bytes in memory. There are also words to copy blocks of memory or fill them, and words that fetch a cell, operate on it and store it back.


    !

    STACKEFFECT: n addr ---

    DESCRIPTION:

    Store 16 bits of n at address.

    GLOSSARY INDEX

    SEE ALSO: MEMORY @ C! 2! L! P! PC!


    +!

    STACKEFFECT: n addr ---

    DESCRIPTION:

    Add n to the value at the address.

    GLOSSARY INDEX

    SEE ALSO: MEMORY TOGGLE !


    2!

    STACKEFFECT: addr--- x1 x2

    DESCRIPTION:

    Store a pair of _32_ bits values x1 x2 to consecutive cells at addr . x2 is stored at the lowest address.

    GLOSSARY INDEX

    SEE ALSO: MEMORY 2@ ! C!


    2@

    STACKEFFECT: addr--- x1 x2

    DESCRIPTION:

    Leave a pair of _32_ bits values x1 x2 from consequitive cells at addr . x2 is fetched from the lowest address.

    GLOSSARY INDEX

    SEE ALSO: MEMORY 2! @ C@


    @

    STACKEFFECT: addr --- n

    DESCRIPTION:

    Leave the 32 bit contents n of addr .

    GLOSSARY INDEX

    SEE ALSO: MEMORY ! C@ 2@ P@ PC@ L@


    BLANKS

    STACKEFFECT: addr count --

    DESCRIPTION:

    Shorthand for ``BL FILL''.

    GLOSSARY INDEX

    SEE ALSO: MEMORY


    C!

    STACKEFFECT: b addr ---

    DESCRIPTION:

    Store 8 bits at addr . On word addressing computers, further specification is necessary regarding byte addressing.

    GLOSSARY INDEX

    SEE ALSO: MEMORY C@ !


    C@

    STACKEFFECT: addr --- b

    DESCRIPTION:

    Leave the 8 bit contents of memory address. On the Intel architectures there are no restrictions regarding byte addressing.

    GLOSSARY INDEX

    SEE ALSO: MEMORY C! @ 2@


    CELL+

    STACKEFFECT: n1 --- n2

    DESCRIPTION:

    Advance the memory pointer n1 by one 32 cel to n2. This is invaluable for writing portable code. Many of the screens of fig-Forth run on both 16 and 32 bits systems, thanks to this.

    GLOSSARY INDEX

    SEE ALSO: MEMORY


    CMOVE

    STACKEFFECT: from to count --

    DESCRIPTION:

    Move the specified quantity of bytes beginning at address from to address to . The contents of address from is moved first proceeding toward high memory. As the Pentintel 86-family is byte-addressing there are no restrictions.

    GLOSSARY INDEX

    SEE ALSO: MEMORY


    EM

    STACKEFFECT: ---- addr

    DESCRIPTION:

    A constant leaving the address just above the highest memory in use.

    GLOSSARY INDEX

    SEE ALSO: MEMORY DP


    ERASE

    STACKEFFECT: addr n --

    DESCRIPTION:

    Shorthand for ``0 FILL''.

    GLOSSARY INDEX

    SEE ALSO: MEMORY


    FILL

    STACKEFFECT: addr quan b --

    DESCRIPTION:

    Fill memory at the address with the specified quantity of bytes b .

    GLOSSARY INDEX

    SEE ALSO: MEMORY


    L!

    STACKEFFECT: n nseg addr ---

    DESCRIPTION:

    Store 32 bits of n at address rseg:addr, interpreted as if it was a real mode segment plus offset addres. This only works if the data segment is mapped directly (not paged) from physical address 0H .

    GLOSSARY INDEX

    SEE ALSO: MEMORY L@ ! C! 2!


    L@

    STACKEFFECT: rseg addr --- n

    DESCRIPTION:

    Leave the 32 bit contents of rseg:addr, interpreted as if it was a real mode segment plus offset addres. This only works if the data segment is mapped directly (not paged) from physical address 0H .

    GLOSSARY INDEX

    SEE ALSO: MEMORY L! @ C@ 2@


    P!

    STACKEFFECT: n port ---

    DESCRIPTION:

    Store the 32 bit data n to the port address port .

    GLOSSARY INDEX

    SEE ALSO: MEMORY P@ PC! PC@ !


    P@

    STACKEFFECT: port --- n

    DESCRIPTION:

    Fetch the 32 bit contents n from the port address port. A port address is always 16 bits .

    GLOSSARY INDEX

    SEE ALSO: MEMORY P! PC@ PC! @


    PC!

    STACKEFFECT: b port ---

    DESCRIPTION:

    Store a byte b to the port address port. A port address is always 16 bits .

    GLOSSARY INDEX

    SEE ALSO: MEMORY PC@ P! P@ !


    PC@

    STACKEFFECT: port --- b

    DESCRIPTION:

    Fetch a byte b from the port address port. A port address is always 16 bits .

    GLOSSARY INDEX

    SEE ALSO: MEMORY PC! P@ P! @


    TOGGLE

    STACKEFFECT: addr b --

    DESCRIPTION:

    Complement the contents of addr by the bit pattern b .

    GLOSSARY INDEX

    SEE ALSO: MEMORY XOR +!


    MISC

    OVERVIEW:

    The wordset MISC contains words that defy categorisation.


    .CPU

    STACKEFFECT: ---

    DESCRIPTION:

    Print the name of the CPU processor present in the boot up parameters. Using the bizar convention of a base-36 number.

    GLOSSARY INDEX

    SEE ALSO: MISC ABORT COLD


    EXECUTE

    STACKEFFECT: addr -

    DESCRIPTION:

    Execute the definition whose code field address is given by addr .

    GLOSSARY INDEX

    SEE ALSO: MISC ' CFA


    NOOP

    STACKEFFECT:

    DESCRIPTION:

    Do nothing. Primarily useful as a placeholder.

    GLOSSARY INDEX

    SEE ALSO: MISC


    TASK

    STACKEFFECT:

    DESCRIPTION:

    A no-operation word which marks the boundary between the forth system and applications.

    GLOSSARY INDEX

    SEE ALSO: MISC COLD


    U0

    STACKEFFECT: --- addr

    DESCRIPTION:

    A user variable, leaving the start address of the user area. This is for reference only. What is taken into account by user variables is the corresponding initialisation variable.

    GLOSSARY INDEX

    SEE ALSO: MISC USER +ORIGIN


    X

    STACKEFFECT:

    DESCRIPTION:

    This is pseudonym for the "null" or dictionary entry for a name of one character of ascii null. All buffers being interpreted ends with this word, that is actually executed. It terminates interpretation of a line of text from the terminal or of a disc buffer,

    GLOSSARY INDEX

    SEE ALSO: MISC


    MULTIPLYING

    OVERVIEW:

    The original 16 bits Forth's have problems with scaling (See also OPERATOR). Operators with intermediate results of double precision solve this and are present in the MULTIPLYING wordset. In this 32-bit Forth you will have less need, but scaling remain tricky.. Formatting is done with double's exclusively, and relies on this wordset. Operators with mixed precision and unsigned operators allow to build arbitray precision from them in high level code.


    */MOD

    STACKEFFECT: n1 n2 n3 --- n4 n5

    DESCRIPTION:

    Leave the quotient n5 and remainder n4 of the operation n1*n2/n3 A 31 bit intermediate product is used as for */ .

    GLOSSARY INDEX

    SEE ALSO: MULTIPLYING */ /MOD


    */

    STACKEFFECT: n1 n2 n3 --- n4

    DESCRIPTION:

    Leave the ratio n4 = n1*n2/n3 where all are signed numbers. Retention of an intermediate 31 bit product permits greater accuracy than would. be available with the sequence: n1 n2 * n3 /

    GLOSSARY INDEX

    SEE ALSO: MULTIPLYING */MOD /MOD


    M*

    STACKEFFECT: n1 n2 --- d

    DESCRIPTION:

    A mixed magnitude math operation which leaves the double number d : the signed product of two signed number n1 and n2 .

    GLOSSARY INDEX

    SEE ALSO: MULTIPLYING M/MOD M/ *


    M/MOD

    STACKEFFECT: ud1 u2 --- u3 ud4

    DESCRIPTION:

    An unsigned mixed magnitude math operation which leaves a double quotient ud4 and remainder u3 , from a double dividend ud1 and single divisor u2 .

    GLOSSARY INDEX

    SEE ALSO: MULTIPLYING /MOD M/ M*


    M/

    STACKEFFECT: d n1 --- n2 n3

    DESCRIPTION:

    A mixed magnitude math operator which leaves the signed remainder n2 and signed quotient n3 from a double number dividend d and divisor n1 . The remainder takes its sign from the dividend.

    GLOSSARY INDEX

    SEE ALSO: MULTIPLYING M/MOD / M*


    U*

    STACKEFFECT: u1 u2 --- ud

    DESCRIPTION:

    A mixed magnitude math operation which leaves the double number d : the unsigned product of two unsigned numbers n1 and n2 .

    GLOSSARY INDEX

    SEE ALSO: MULTIPLYING U/ M*.*


    U/

    STACKEFFECT: ud u1 --- u2 u3

    DESCRIPTION:

    Leave the unsigned remainder u2 and unsigned quotient u3 from the unsigned double dividend ud and unsigned divisor u1 .

    GLOSSARY INDEX

    SEE ALSO: MULTIPLYING U* M/ /


    OPERATOR

    OVERVIEW:

    The wordset OPERATOR contains the familiar operators for addition, multiplication etc. The result of the operation is always an integer number, so division can't be precise. The combination of / and MOD (remainder) is such that you can get the original back: n m / m * n m MOD + allways has the value m . This is true for all Forth's. On fig-Forth the / is a symmetric division, i.e. -n m / give the same result as n m /, but negated. The forgeoing rule now has the consequence that MOD n m has 2m-1 possible outcomes instead of m . This is very worrysome for mathematicians, who stick to the rule that MOD n m gives a result in the range 0 ... m-1 (floored division).


    *

    STACKEFFECT: n1 n2 --- prod

    DESCRIPTION:

    Leave the signed product of two signed numbers.

    GLOSSARY INDEX

    SEE ALSO: OPERATOR + - / MOD


    +

    STACKEFFECT: n1 n2 --- sum

    DESCRIPTION:

    Leave the sum of n1+n2 .

    GLOSSARY INDEX

    SEE ALSO: OPERATOR - * / MOD


    -

    STACKEFFECT: n1 n2 --- diff

    DESCRIPTION:

    Leave the difference of n1-n2 .

    GLOSSARY INDEX

    SEE ALSO: OPERATOR MINUS + * / MOD


    /MOD

    STACKEFFECT: n1 n2 --- rem quot

    DESCRIPTION:

    Leave the remainder and signed quotient of n1/n2 . The remainder has the sign of the dividend.

    GLOSSARY INDEX

    SEE ALSO: OPERATOR */MOD */ M/MOD


    /

    STACKEFFECT: n1 n2 --- quot

    DESCRIPTION:

    Leave the signed quotient of n1/n2 . It the result is interpreted as logical value, it means n1 si not equal to n2

    GLOSSARY INDEX

    SEE ALSO: OPERATOR + - * MOD */MOD


    ABS

    STACKEFFECT: n --- u

    DESCRIPTION:

    Leave the absolute value of n as u .

    GLOSSARY INDEX

    SEE ALSO: OPERATOR


    MAX

    STACKEFFECT: n1 n2 --- max

    DESCRIPTION:

    Leave the greater of two numbers.

    GLOSSARY INDEX

    SEE ALSO: OPERATOR MIN


    MINUS

    STACKEFFECT: n1 --- n2

    DESCRIPTION:

    Leave the two's complement of a number, i.e. n2 is -n1

    GLOSSARY INDEX

    SEE ALSO: OPERATOR -


    MIN

    STACKEFFECT: n1 n2 --- min

    DESCRIPTION:

    Leave the smaller of two numbers.

    GLOSSARY INDEX

    SEE ALSO: OPERATOR MAX


    MOD

    STACKEFFECT: n1 n2 --- mod

    DESCRIPTION:

    Leave the remainder of n1/n2 , with the same sign as n1 .

    GLOSSARY INDEX

    SEE ALSO: OPERATOR + - * / MOD */MOD


    OUTPUT

    OVERVIEW:

    The wordset OUTPUT contains words to output to the terminal and such. For disk I/O: See also STORAGE


    ."

    STACKEFFECT:

    DESCRIPTION:

    Used in the form: ." cccc" Compiles an in-line string cccc (delimited by the trailing ") with an execution proceedure to transmit the text to the selected output device. If executed outside a definition, ." will immediately print the text until the final ". The maximum number of characters may be an installation dependent value.

    GLOSSARY INDEX

    SEE ALSO: OUTPUT OUT (.")


    .R

    STACKEFFECT: n1 n2 ---

    DESCRIPTION:

    Print the number n1 right aligned in a field whose width is n2 . No following blank is printed.

    GLOSSARY INDEX

    SEE ALSO: OUTPUT OUT .


    .

    STACKEFFECT: n ---

    DESCRIPTION:

    Print a number from a signed 32 bit two's complement value, converted according to the numeric BASE . A trailing blanks follows.

    GLOSSARY INDEX

    SEE ALSO: OUTPUT OUT U. .R D.R D.


    ?

    STACKEFFECT: addr --

    DESCRIPTION:

    Print the value contained at the address in free according to the current base.

    GLOSSARY INDEX

    SEE ALSO: OUTPUT OUT


    CR

    STACKEFFECT:

    DESCRIPTION:

    Transmit a carriage return and line feed to the selected output device.

    GLOSSARY INDEX

    SEE ALSO: OUTPUT OUT


    D.R

    STACKEFFECT: d n ---

    DESCRIPTION:

    Print a signed double number d right aligned in a field n characters wide.

    GLOSSARY INDEX

    SEE ALSO: OUTPUT OUT D.


    D.

    STACKEFFECT: d ---

    DESCRIPTION:

    Print a signed double number d, according to the current BASE . A blank follows.

    GLOSSARY INDEX

    SEE ALSO: OUTPUT OUT . D.R


    EMIT

    STACKEFFECT: c ---

    DESCRIPTION:

    Transmit ascii character c to the output device. All terminal I/O goes through TYPE. OUT is not observed.

    GLOSSARY INDEX

    SEE ALSO: OUTPUT TYPE OUT


    OUT

    STACKEFFECT: --- addr

    DESCRIPTION:

    A user variable that reflects the position at the current line of the output device where the next character transmitted will appear. The first position is zero.

    GLOSSARY INDEX

    SEE ALSO: OUTPUT EMIT TYPE CR


    SPACES

    STACKEFFECT: n ---

    DESCRIPTION:

    Transmit n ascii blanks to the output device.

    GLOSSARY INDEX

    SEE ALSO: OUTPUT SPACE OUT


    SPACE

    STACKEFFECT:

    DESCRIPTION:

    Transmit an ascii blank to the output device.

    GLOSSARY INDEX

    SEE ALSO: OUTPUT EMIT OUT


    TYPE

    STACKEFFECT: addr count ---

    DESCRIPTION:

    Transmit count characters from addr to the output device. All terminal I/O goes through this word. It is high level so terminal I/O can be redirected, by forthref(revectoring) it and the usual redirection or tee-ing by Linux. OUT is not observed.

    GLOSSARY INDEX

    SEE ALSO: OUTPUT EMIT OUT


    U.

    STACKEFFECT: u ---

    DESCRIPTION:

    Print a number from a unsigned 32 bit value, converted according to the numeric BASE . A trailing blanks follows.

    GLOSSARY INDEX

    SEE ALSO: OUTPUT OUT . .R D.R D.


    PARSING

    OVERVIEW:

    The outer interpreter is responsible for parsing, i.e. it gets a word from the input stream and interprets or compiles it, advacing the IN pointer. The wordset PARSING contains the words used by this interpreter and other words that consume characters from the input stream. In this way the outer interpreter need not be very smart, because its capabilities can be extended by new words based on those building blocks.


    (.")

    STACKEFFECT:

    DESCRIPTION:

    The run-time proceedure, compiled by ." which transmits the following in-line text to the selected output device.

    GLOSSARY INDEX

    SEE ALSO: PARSING ."


    (

    STACKEFFECT:

    DESCRIPTION:

    Used in the form: ( cccc) Ignore a comment that will be delimited by a right parenthesis on the same line. May occur during execution or in a colon-definition. A blank after the leading parenthesis is required.

    GLOSSARY INDEX

    SEE ALSO: PARSING


    ENCLOSE

    STACKEFFECT: addr1 c --- addr1 n1 n2 n3

    DESCRIPTION:

    The text scanning primitive used by WORD . From the text address addr1 and an ascii delimiting character c , is determined the byte offset to the first non-delimiter character n1 , the offset to the first delimiter after the text n2 , and the offset to the first character not included. This proceedure will not process past an ascii "null", treating it as an unconditional delimiter.

    GLOSSARY INDEX

    SEE ALSO: PARSING


    INTERPRET

    STACKEFFECT:

    DESCRIPTION:

    Repeatedly fetch the next text word in the input stream and execute it (STATE is 1) or compile it (STATE is 1). Text from the input stream: terminal ( BLK is 0 ) or disc (other value) . If the word name cannot be found after a search of CONTEXT and then CURRENT it is converted to a number according to the current base. If a decimal point is found as part of a number, the number value that is left is a double number, otherwise a single number. The decimal point has no other purpose. That also failing, an error message echoing the name with a " ?" will be given.

    GLOSSARY INDEX

    SEE ALSO: PARSING WORD NUMBER


    QUERY

    STACKEFFECT:

    DESCRIPTION:

    Input 80 characters of text (or until a "return") from the operators terminal. Text is positioned at the address contained in TIB with IN set to zero.

    GLOSSARY INDEX

    SEE ALSO: PARSING


    STATE

    STACKEFFECT: --- addr

    DESCRIPTION:

    A user variable containing the compilation state. A non-zero value indicates compilation. The value itself may be implementation dependent.

    GLOSSARY INDEX

    SEE ALSO: PARSING


    WORD

    STACKEFFECT: c ---

    DESCRIPTION:

    Read the next text characters from the input stream being interpreted, until a delimiter c is found, storing the packed character string beginning at the dictionary buffer HERE . WORD leaves the character count in the first byte, the characters, and ends with two or more blanks. Leading occurrences of c are ignored. If BLK is zero text is taken from the terminal input buffer, otherwise from the disc block stored in BLK .

    GLOSSARY INDEX

    SEE ALSO: PARSING BLK IN


    [

    STACKEFFECT:

    DESCRIPTION:

    Used in a colon-definition in form:

    : xxx [ words ] more ;

    Suspend compilation. The words after [ are executed, not compiled. This allows calculation or compilation exceptions before resuming compilation with ]

    GLOSSARY INDEX

    SEE ALSO: PARSING LITERAL ]


    ]

    STACKEFFECT:

    DESCRIPTION:

    Resume compilation, to the completion of a colon-definition.

    GLOSSARY INDEX

    SEE ALSO: PARSING [


    SCREEN

    OVERVIEW:

    Most of the mass storage is used for screen's that have 16 lines of 64 characters. They are used for source code and documentation. Each screen is a whole number of BLOCK's, in our case it is one block. The SCREEN wordset contains facilities to view screens, and load them, that is compiling them and thus extending the base system. A system is customized by loading source screens, possibly one of these extension is a text editor for screens.


    (LINE)

    STACKEFFECT: n1 n2 --- addr count

    DESCRIPTION:

    Convert the line number n1 and the screen n2 to the disc buffer address containing the data. A count of 64 indicates the full line text length.

    GLOSSARY INDEX

    SEE ALSO: SCREEN -LINE


    -->

    STACKEFFECT:

    DESCRIPTION:

    Continue interpretation with the next disc screen.

    GLOSSARY INDEX

    SEE ALSO: SCREEN LOAD


    .LINE

    STACKEFFECT: line scr --

    DESCRIPTION:

    Print on the terminal device, a line of text from the disc by its line and screen number. Trailing blanks are suppressed, which leads to a tremendous speed advantage on modern glass tty's.

    GLOSSARY INDEX

    SEE ALSO: SCREEN C/L


    ;S

    STACKEFFECT:

    DESCRIPTION:

    Stop interpretation of a screen. ;S is also the run-time word compiled at the end of a colon-definition which returns execution to the calling proceedure.

    GLOSSARY INDEX

    SEE ALSO: SCREEN


    B/SCR

    STACKEFFECT: --- n

    DESCRIPTION:

    This constant leaves the number of blocks per editing screen. An editing screen is 1024 bytes organized as 16 lines of 64 characters each. In fact B/SCR is 1, and screens correspond one to one with blocks.

    GLOSSARY INDEX

    SEE ALSO: SCREEN BLOCK


    C/L

    STACKEFFECT: --- c

    DESCRIPTION:

    A constant that leaves the number of characters on a line of a standard screen.

    GLOSSARY INDEX

    SEE ALSO: SCREEN LIST LINE


    INDEX

    STACKEFFECT: from to --

    DESCRIPTION:

    Print the first line of each screen over the range from , to . This is used to view the comment lines of an area of text on disc screens.

    GLOSSARY INDEX

    SEE ALSO: SCREEN LIST


    LIST

    STACKEFFECT: n ---

    DESCRIPTION:

    Display the ascii text of screen n on the selected output device. SCR contains the screen number during and after this process.

    GLOSSARY INDEX

    SEE ALSO: SCREEN


    LOAD

    STACKEFFECT: n ---

    DESCRIPTION:

    Interrupt the current input stream in order to interpret screen n . At the end of the screen, barring errors or forced changes, it continues with the interrupted input stream.

    GLOSSARY INDEX

    SEE ALSO: SCREEN --> QUIT ;S


    R#

    STACKEFFECT: --- addr

    DESCRIPTION:

    A user variable which may contain the location of an editing cursor, or other file related function.

    GLOSSARY INDEX

    SEE ALSO: SCREEN


    SCR

    STACKEFFECT: --- addr

    DESCRIPTION:

    A user variable containing the screen number most recently reference by LIST .

    GLOSSARY INDEX

    SEE ALSO: SCREEN BLOCK


    TRIAD

    STACKEFFECT: scr --

    DESCRIPTION:

    Display on the selected output device the three screens which include that numbered scr , beginning with a screen evenly divisible by three. Output is suitable for source text records, and includes a reference line at the bottom taken from line 15 of screen 4.

    GLOSSARY INDEX

    SEE ALSO: SCREEN MESSAGE


    SECURITY

    OVERVIEW:

    The wordset SECURITY contains words that are used by control words to abort with an error message if the control structure is not correct. Some say that this is not Forth-like. You only need to know them if want to extend the CONTROL wordset.


    !CSP

    STACKEFFECT:

    DESCRIPTION:

    Save the stack position in CSP. Used as part of the compiler security.

    GLOSSARY INDEX

    SEE ALSO: SECURITY


    ?COMP

    STACKEFFECT:

    DESCRIPTION:

    Issue error message if not compiling.

    GLOSSARY INDEX

    SEE ALSO: SECURITY ?ERROR


    ?CSP

    STACKEFFECT:

    DESCRIPTION:

    Issue error message if stack position differs from value saved in CSP .

    GLOSSARY INDEX

    SEE ALSO: SECURITY


    ?EXEC

    STACKEFFECT:

    DESCRIPTION:

    Issue an error message if not executing.

    GLOSSARY INDEX

    SEE ALSO: SECURITY ?ERROR


    ?LOADING

    STACKEFFECT:

    DESCRIPTION:

    Issue an error message if not loading

    GLOSSARY INDEX

    SEE ALSO: SECURITY ?ERROR


    ?PAIRS

    STACKEFFECT: n1 n2 --

    DESCRIPTION:

    Issue an error message if n1 does not equal n2 . The message indicates that compiled conditionals do not match.

    GLOSSARY INDEX

    SEE ALSO: SECURITY ?ERROR


    ?STACK

    STACKEFFECT:

    DESCRIPTION:

    Issue an error message is the stack is out of bounds.

    GLOSSARY INDEX

    SEE ALSO: SECURITY ?ERROR


    CSP

    STACKEFFECT: ---- addr

    DESCRIPTION:

    A user variable temporarily storing the stack pointer position, for compilation error checking.

    GLOSSARY INDEX

    SEE ALSO: SECURITY


    STACKS

    OVERVIEW:

    The wordset STACKS contains words related to the data stack and return stack. Words can be moved between both stacks. Stacks can be reinitialised and the value used to initialise the stack pointer's can be altered.


    >R

    STACKEFFECT: n ---

    DESCRIPTION:

    Remove a number from the computation stack and place as the most accessable on the return stack. Use should be balanced with R> in the same definition.

    GLOSSARY INDEX

    SEE ALSO: STACKS R


    R0

    STACKEFFECT: --- addr

    DESCRIPTION:

    A user variable containing the initial location of the return stack.

    GLOSSARY INDEX

    SEE ALSO: STACKS RP!


    R>

    STACKEFFECT: --- n

    DESCRIPTION:

    Remove the top value from the return stack and leave it on the computation stack.

    GLOSSARY INDEX

    SEE ALSO: STACKS >R R


    RP!

    STACKEFFECT:

    DESCRIPTION:

    Initialize the return stack pointer from user variable R0 .

    GLOSSARY INDEX

    SEE ALSO: STACKS


    RP@

    STACKEFFECT: --- addr

    DESCRIPTION:

    Return the address addr of the current return stack position, i.e. pointing the current topmost value. (e.g. 1 >R RP@ @ . R> would type 1 )

    GLOSSARY INDEX

    SEE ALSO: STACKS S0 SP!


    R

    STACKEFFECT: --- n

    DESCRIPTION:

    Copy the top of the return stack to the computation stack.

    GLOSSARY INDEX

    SEE ALSO: STACKS >R


    S0

    STACKEFFECT: --- addr

    DESCRIPTION:

    A user variable that contains the initial value for the data stack pointer.

    GLOSSARY INDEX

    SEE ALSO: STACKS SP!


    SP!

    STACKEFFECT:

    DESCRIPTION:

    Initialize the stack pointer from S0 .

    GLOSSARY INDEX

    SEE ALSO: STACKS


    SP@

    STACKEFFECT: --- addr

    DESCRIPTION:

    Return the address addr of the stack position, as it was before SP@ was executed. (e.g. 1 2 SP@ @ ... would type 2 2 1 )

    GLOSSARY INDEX

    SEE ALSO: STACKS S0 SP!


    STORAGE

    OVERVIEW:

    The wordset STORAGE contains words to input and output to the mass storage, in this fig-Forth to the file ``BLOCKS.BLK''. They are the underlying the SCREEN facilities.


    #BUFF

    STACKEFFECT: --- c

    DESCRIPTION:

    A constant that leaves the number of block buffers.

    GLOSSARY INDEX

    SEE ALSO: STORAGE BLOCK


    +BUF

    STACKEFFECT: add1 --- addr2 f

    DESCRIPTION:

    Advance the disc buffer address addr1 to the address of the next buffer addr2 . Boolean f is false when addr2 is the buffer presently pointed to by variable PREV

    GLOSSARY INDEX

    SEE ALSO: STORAGE BLOCK


    B/BUF

    STACKEFFECT: --- n

    DESCRIPTION:

    This constant leaves the number of bytes per disc buffer, the byte count read from disc by BLOCK .

    GLOSSARY INDEX

    SEE ALSO: STORAGE B/SCR


    BLK

    STACKEFFECT: --- addr

    DESCRIPTION:

    A user variable containing the block number being interpreted. If zero, input is being taken from the terminal input buffer.

    GLOSSARY INDEX

    SEE ALSO: STORAGE BLOCK TIB


    BLOCK-EXIT

    STACKEFFECT: ---

    DESCRIPTION:

    A block file must have been opened by BLOCK-INIT . Close the currently open block file BLOCK-HANDLE, i.e. the mass storage words no longer work, and will result in error messages.

    GLOSSARY INDEX

    SEE ALSO: STORAGE BLOCK LIST LOAD DISK-ERROR


    BLOCK-FILE

    STACKEFFECT: ---addr

    DESCRIPTION:

    Leave the address addr of a counted string, the name of a file in which blocks are (to be) allocated. The name may contain a path and be at most 254 characters long. The default name is BLOCKS.BLK .

    GLOSSARY INDEX

    SEE ALSO: STORAGE BLOCK-HANDLE BLOCK-INIT BLOCK-EXIT


    BLOCK-HANDLE

    STACKEFFECT: ---n

    DESCRIPTION:

    Leave a file handle in n . If it is negative there is no block file open, otherwise the handle is used by the system to access blocks.

    GLOSSARY INDEX

    SEE ALSO: STORAGE BLOCK-FILE BLOCK-INIT BLOCK-EXIT


    BLOCK-INIT

    STACKEFFECT: ---

    DESCRIPTION:

    Map the blocks on the block file BLOCK-FILE, i.e. the mass storage words refer to the blocks in this file, using BLOCK-HANDLE to acces it. If successful, WARNING is reinitialised to use disk messages.

    GLOSSARY INDEX

    SEE ALSO: STORAGE BLOCK LIST LOAD BLOCK-EXIT DISK-ERROR


    BLOCK

    STACKEFFECT: n --- addr

    DESCRIPTION:

    Leave the memory address of the block buffer containing block n, which is the physical disk block OFFSET+n. If the block is not already in memory, it is transferred from disc to which ever buffer was least recently written. If the block occupying that buffer has been marked as updated, it is rewritten to disc before block n is read into the buffer. In this experimental version PMASK restricts the number of blocks to 0FFH.

    GLOSSARY INDEX

    SEE ALSO: STORAGE BUFFER R/W OFFSET UPDATE FLUSH


    BUFFER

    STACKEFFECT: n --- addr

    DESCRIPTION:

    Obtain the next memory buffer, assigning it to block n . If the contents of the buffer is marked as updated, it is written to the disc. The block is not read from the disc. The address left is the first cell within the buffer for data storage.

    GLOSSARY INDEX

    SEE ALSO: STORAGE BLOCK USE PREV


    DISK-ERROR

    STACKEFFECT: --- addr

    DESCRIPTION:

    Leave the address addr of a variable containing the latest disk error in opening, using or closing the block file. Negative means an error (the Unix errno and zero means okay.)

    GLOSSARY INDEX

    SEE ALSO: STORAGE BLOCK LINUX-ERROR


    EMPTY-BUFFERS

    STACKEFFECT:

    DESCRIPTION:

    Mark all block-buffers as empty, not necessarily affecting the contents. Updated blocks are not written to the disc. This is also an initialization proceedure before first use of the disc.

    GLOSSARY INDEX

    SEE ALSO: STORAGE FLUSH BLOCK SCREEN


    FIRST

    STACKEFFECT: --- n

    DESCRIPTION:

    A constant that leaves the address of the first (lowest) block buffer.

    GLOSSARY INDEX

    SEE ALSO: STORAGE BLOCK LIMIT


    FLUSH

    STACKEFFECT:

    DESCRIPTION:

    Transfer the content of each UPDATE d block buffer to disk. They are no longer associated with a block and their content is no longer available.

    GLOSSARY INDEX

    SEE ALSO: STORAGE EMPTY-BUFFERS BLOCK SCREEN


    LIMIT

    STACKEFFECT: ---- n

    DESCRIPTION:

    A constant leaving the address just above the highest memory available for a disc buffer. Actually this is the highest system memory.

    GLOSSARY INDEX

    SEE ALSO: STORAGE BLOCK FIRST


    OFFSET

    STACKEFFECT: --- addr

    DESCRIPTION:

    A user variable which may contain a block offset to disc drives, such as to free part of it for boot-code. As blocks are allocated in a file on the host operating system it is 0. The contents of OFFSET is added to the stack number by BLOCK before calling R/W . Messages by MESSAGE are independent of OFFSET .

    GLOSSARY INDEX

    SEE ALSO: STORAGE BLOCK MESSAGE


    PREV

    STACKEFFECT: ---- addr

    DESCRIPTION:

    A variable containing the address of the disc buffer most recently referenced. The UPDATE command marks this buffer to be later written to disc.

    GLOSSARY INDEX

    SEE ALSO: STORAGE BLOCK


    R/W

    STACKEFFECT: addr blk f --

    DESCRIPTION:

    The fig-FORTH standard disc read-write linkage. addr specifies the source or destination block buffer, blk is the sequential number of the referenced physical block; and f is a flag for f=0 write and f=l read. R/W determines the location on mass storage, performs the read-write and aborts on errors.

    GLOSSARY INDEX

    SEE ALSO: STORAGE BLOCK


    UPDATE

    STACKEFFECT:

    DESCRIPTION:

    Marks the most recently referenced block (pointed to by PREV ) as altered. The block will subsequently be transferred automatically to disc should its buffer be required for storage of a different block.

    GLOSSARY INDEX

    SEE ALSO: STORAGE BLOCK SCREEN


    USE

    STACKEFFECT: --- addr

    DESCRIPTION:

    A variable containing the address of the block buffer to use next, as the least recently written.

    GLOSSARY INDEX

    SEE ALSO: STORAGE BLOCK


    STRING

    OVERVIEW:

    The wordset STRING contains words that manipulate strings of characters.


    -TRAILING

    STACKEFFECT: addr n1 --- addr n2

    DESCRIPTION:

    Adjusts the character count n1 of a text string beginning at address addr so as not to contain trailing blanks.

    GLOSSARY INDEX

    SEE ALSO: STRING


    BL

    STACKEFFECT: --- c

    DESCRIPTION:

    A constant that leaves the ascii value for "blank".

    GLOSSARY INDEX

    SEE ALSO: STRING


    COUNT

    STACKEFFECT: addr1 --- addr2 n

    DESCRIPTION:

    Leave the byte address addr2 and byte count n of a message text beginning at address addr1 . It is presumed that the first byte at addr1 contains the text byte count and the actual text starts with the second byte.

    GLOSSARY INDEX

    SEE ALSO: STRING TYPE


    MATCH

    STACKEFFECT: add1 n1 addr2 n2 -- f o

    DESCRIPTION:

    This word supposedly compares strings. Its documentation looked like this

    STACK PARAMETERS: ( cursor:addr byte:left str:addr str:len --- flag new:cursor:offset ) This version of MATCH will handle string lengths up to 65535 bytes in length.

    I hope I interpreted this stack diagram right.

    GLOSSARY INDEX

    SEE ALSO: STRING


    SUPERFLUOUS

    OVERVIEW:

    The wordset SUPERFLUOUS contains words that are superfluous, because they are equivalent to small sequences of code. Traditionally one hoped to speed Forth up by coding these words directly


    0

    STACKEFFECT: --- 0

    DESCRIPTION:

    Leave the number 0.

    GLOSSARY INDEX

    SEE ALSO: SUPERFLUOUS CONSTANT


    1+

    STACKEFFECT: n1 --- n2

    DESCRIPTION:

    Shorthand for ``1 +''.

    GLOSSARY INDEX

    SEE ALSO: SUPERFLUOUS


    1

    STACKEFFECT: --- 1

    DESCRIPTION:

    Leave the number 1.

    GLOSSARY INDEX

    SEE ALSO: SUPERFLUOUS CONSTANT


    2+

    STACKEFFECT: n1 --- n2

    DESCRIPTION:

    Shorthand for ``2 +''.

    GLOSSARY INDEX

    SEE ALSO: SUPERFLUOUS


    2

    STACKEFFECT: --- 2

    DESCRIPTION:

    Leave the number 2.

    GLOSSARY INDEX

    SEE ALSO: SUPERFLUOUS CONSTANT


    3

    STACKEFFECT: --- 3

    DESCRIPTION:

    Leave the number 3.

    GLOSSARY INDEX

    SEE ALSO: SUPERFLUOUS CONSTANT


    SYSTEM

    OVERVIEW:

    The wordset SYSTEM contains words that call the underlying operating system or functions available in the BIOS-rom.


    ?LINUX-ERROR

    STACKEFFECT: errno ---

    DESCRIPTION:

    Handle the error errno by interpreting it as returned from a Linux system call. If it is negative error -n is displayed and the word is aborted.

    GLOSSARY INDEX

    SEE ALSO: SYSTEM ?ERROR


    BYE

    STACKEFFECT: ---

    DESCRIPTION:

    Return to the host environment Linux.

    GLOSSARY INDEX

    SEE ALSO: SYSTEM COLD


    LINOS

    STACKEFFECT: p1 p2 p3 n---ret

    DESCRIPTION:

    Do a Linux system call (man 2) with parameters p1 p2 p3. ret is the return value of the call. If it is negative, it is mostly an error, such as known by errno . This makes available forthemph(all) facilities present in Linux.

    GLOSSARY INDEX

    SEE ALSO: SYSTEM ?LINUX-ERROR


    VOCABULARIES

    OVERVIEW:

    The dictionary is subdivided in non-overlapping subsets: the vocabulary's. See also DICTIONARY. They are created by the defining word VOCABULARY and filled by defining words while that vocabulary is CURRENT . They regulate how words are found, different vocabularies can have words with the same names. The wordset VOCABULARIES contains words that manipulate those vocabularies.


    CONTEXT

    STACKEFFECT: --- addr

    DESCRIPTION:

    A user variable containing a pointer to the vocabulary within which dictionary searches will first begin.

    GLOSSARY INDEX

    SEE ALSO: VOCABULARIES VOCABULARY CURRENT


    CURRENT

    STACKEFFECT: --- addr

    DESCRIPTION:

    A user variable containing a pointer to the vocabulary to which new words will be added.

    GLOSSARY INDEX

    SEE ALSO: VOCABULARIES VOCABULARY CONTEXT


    DEFINITIONS

    STACKEFFECT:

    DESCRIPTION:

    Used in the form: cccc DEFINITIONS Set the CURRENT vocabulary to the CONTEXT vocabulary. In the example, executing vocabulary name cccc made it the CONTEXT vocabulary and executing DEFINITIONS made both specify vocabulary cccc .

    GLOSSARY INDEX

    SEE ALSO: VOCABULARIES VOCABULARY


    FORTH

    STACKEFFECT:

    DESCRIPTION:

    The name of the primary vocabulary. Execution makes FORTH the CONTEXT vocabulary. Until additional user vocabularies are defined, new user definitions become a part of FORTH . FORTH is immediate, so it will execute during the creation of a colon-definition, to select this vocabulary at compile time.

    GLOSSARY INDEX

    SEE ALSO: VOCABULARIES VOCABULARY


    LATEST

    STACKEFFECT: --- addr

    DESCRIPTION:

    Leave the name field address ( NFA ) of the topmost word in the CURRENT vocabulary.

    GLOSSARY INDEX

    SEE ALSO: VOCABULARIES VOCABULARY


    VOC-LINK

    STACKEFFECT: --- addr

    DESCRIPTION:

    A user variable containing the address of the DLFA in the word most recently created by VOCABULARY . All vocabulary names are linked by these fields to allow control for FORGET ting thru multiple vocabularies.

    GLOSSARY INDEX

    SEE ALSO: VOCABULARIES VOCABULARY