"Core words + extensions"

core [ANS] /* core words */
* ! ( val addr -- )

store value at addr (sizeof CELL)

FORTH/ANS core (dpANS.6.1.0010) ordinary primitive

* # ( n.n -- n.n' )

see also HOLD for old-style forth-formatting words
and PRINTF of the C-style formatting - this word
divides the argument by BASE and add it to the
picture space - it should be used inside of <#
and #>

FORTH/ANS core (dpANS.6.1.0030) ordinary primitive

* #> ( n.n -- str-addr str-len )

see also HOLD for old-style forth-formatting words
and PRINTF of the C-style formatting - this word
drops the argument and returns the picture space
buffer

FORTH/ANS core ordinary primitive

* #S ( n.n -- n.n ) f

see also HOLD for old-style forth-formatting words
and PRINTF of the C-style formatting - this word
does repeat the word # for a number of times, until
the argument becomes zero. Hence the result is always
null - it should be used inside of <# and #>

FORTH/ANS core (dpANS.6.1.0050) ordinary primitive

* ( f: a -- n,n )

b is the integer representation of a

we use truncation towards zero.
compare with F>S and its "FROUND>S" / "FTRUNC>S"

FORTH/ANS core (dpANS11.6.1.0080) immediate primitive

* * ( a b -- a*b )

return the multiply of the two args

FORTH/ANS core (dpANS.6.1.0090) ordinary primitive

*/

[] no special info, see general notes

FORTH/ANS core (dpANS.6.1.0100) ordinary primitive

*/MOD

[] no special info, see general notes

FORTH/ANS core (dpANS.6.1.0110) ordinary primitive

* + ( a b -- a+b )

return the sum of the two args

FORTH/ANS core (dpANS.6.1.0120) ordinary primitive

* +! ( val addr -- )

add val to the value found in addr
 simulate:
   : +! TUCK @ + SWAP ! ;

FORTH/ANS core (dpANS.6.1.0130) ordinary primitive

* +LOOP ( increment -- )

compile ((+LOOP)) which will use the increment
as the loop-offset instead of just 1. See the
DO and LOOP construct.

FORTH/ANS core (dpANS.6.1.0140) compiling primitive

* , ( val -- )

store the value in the dictionary
 simulate:
   : , DP  1 CELLS DP +!  ! ;

FORTH/ANS core (dpANS.6.1.0150) ordinary primitive

* - ( a b -- a-b )

return the difference of the two arguments

FORTH/ANS core (dpANS.6.1.0160) ordinary primitive

* . ( val -- )

print the numerical value to stdout - uses BASE

FORTH/ANS core (dpANS.6.1.0180) ordinary primitive

* ." ( [string<">] -- )

print the string to stdout

FORTH/ANS core compiling primitive

* / ( a b -- a/b )

return the quotient of the two arguments

FORTH/ANS core (dpANS.6.1.0230) ordinary primitive

* /MOD ( a b -- m n )

divide a and b and return both
quotient n and remainder m

FORTH/ANS core (dpANS.6.1.0240) ordinary primitive

* 0< ( val -- cond )

return a flag that is true if val is lower than zero
 simulate:
  : 0< 0 < ;

FORTH/ANS core ordinary primitive

* 0= ( val -- cond )

return a flag that is true if val is just zero
 simulate:
  : 0= 0 = ;

FORTH/ANS core (dpANS.6.1.0270) ordinary primitive

* 1+ ( val -- val+1 )

return the value incremented by one
 simulate:
  : 1+ 1 + ;

FORTH/ANS core (dpANS.6.1.0290) ordinary primitive

* 1- ( val -- val-1 )

return the value decremented by one
 simulate:
   : 1- 1 - ;

FORTH/ANS core (dpANS.6.1.0300) ordinary primitive

* 2! ( a,a addr -- )

double-cell store

FORTH/ANS core (dpANS.6.1.0310) ordinary primitive

* 2* ( a -- a*2 )

multiplies the value with two - but it
does actually use a shift1 to be faster
 simulate:
  : 2* 2 * ; ( canonic) : 2* 1 LSHIFT ; ( usual)

FORTH/ANS core (dpANS.6.1.0320) ordinary primitive

* 2/ ( a -- a/2 )

divides the value by two - but it
does actually use a shift1 to be faster
 simulate:
  : 2/ 2 / ; ( canonic) : 2/ 1 RSHIFT ; ( usual)

FORTH/ANS core (dpANS.6.1.0330) ordinary primitive

* 2@ ( addr -- a,a )

double-cell fetch

FORTH/ANS core (dpANS.6.1.0350) ordinary primitive

* 2DROP ( a b -- )

double-cell drop, also used to drop two items

FORTH/ANS core (dpANS.6.1.0370) ordinary primitive

* 2DUP ( a,a -- a,a a,a )

double-cell duplication, also used to duplicate
two items
 simulate:
   : 2DUP OVER OVER ; ( wrong would be : 2DUP DUP DUP ; !!) 

FORTH/ANS core (dpANS.6.1.0380) ordinary primitive

* 2OVER ( a,a b,b -- a,a b,b a,a )

double-cell over, see OVER and 2DUP
 simulate:
   : 2OVER SP@ 2 CELLS + 2@ ;

FORTH/ANS core (dpANS.6.1.0400) ordinary primitive

* 2SWAP ( a,a b,b -- b,b a,a )

double-cell swap, see SWAP and 2DUP
 simulate:
   : 2SWAP LOCALS| B1 B2 A1 A2 | B2 B1 A2 A1 ;

FORTH/ANS core (dpANS.6.1.0430) ordinary primitive

* : ( 'name' -- )

create a header for a nesting word and go to compiling
mode then. This word is usually ended with ; but
the execution of the resulting colon-word can also
return with EXIT

FORTH/ANS core (dpANS.6.1.0450) defining primitive

* ; ( -- )

compiles ((;)) which does EXIT the current
colon-definition. It does then end compile-mode
and returns to execute-mode. See : and :NONAME

FORTH/ANS core (dpANS.6.1.0460) compiling primitive

* < ( a b -- cond )

return a flag telling if a is lower than b

FORTH/ANS core (dpANS.6.1.0480) ordinary primitive

* <# ( -- )

see also HOLD for old-style forth-formatting words
and PRINTF of the C-style formatting - this word
does initialize the pictured numeric output space.

FORTH/ANS core (dpANS.6.1.0490) ordinary primitive

* = ( a b -- cond )

return a flag telling if a is equal to b

FORTH/ANS core (dpANS.6.1.0530) ordinary primitive

* > ( a b -- cond )

return a flag telling if a is greater than b

FORTH/ANS core ordinary primitive

* >BODY ( addr -- addr' )

adjust the execution-token (ie. the CFA) to point
to the parameter field (ie. the PFA) of a word.
this is not a constant operation - most words have their
parameters at "1 CELLS +" but CREATE/DOES-words have the
parameters at "2 CELLS +" and ROM/USER words go indirect
with a rom'ed offset i.e. "CELL + @ UP +"

FORTH/ANS core ordinary primitive

>IN

[] no special info, see general notes

FORTH/ANS core threadstate variable

* >NUMBER ( a,a str-adr str-len -- a,a' str-adr' str-len)

try to convert a string into a number, and place
that number at a,a respeciting BASE

FORTH/ANS core ordinary primitive

* >R ( value -- )

save the value onto the return stack. The return
stack must be returned back to clean state before
an exit and you should note that the return-stack
is also touched by the DO ... WHILE loop.
Use R> to clean the stack and R@ to get the
last value put by >R

FORTH/ANS core compiling primitive

* ?DUP ( value -- value|[nothing] )

one of the rare words whose stack-change is
condition-dependet. This word will duplicate
the value only if it is not zero. The usual
place to use it is directly before a control-word
that can go to different places where we can
spare an extra DROP on the is-null-part.
This makes the code faster and often a little
easier to read.
 example:
   : XX BEGIN ?DUP WHILE DUP . 2/ REPEAT ; instead of
   : XX BEGIN DUP WHILE DUP . 2/ REPEAT DROP ;

FORTH/ANS core (dpANS.6.1.0630) ordinary primitive

* @ ( addr -- value )

fetch the value from the variables address

FORTH/ANS core (dpANS.6.1.0650) ordinary primitive

* ABS ( value -- value' )

return the absolute value

FORTH/ANS core (dpANS.6.1.0690) ordinary primitive

* ACCEPT ( a n -- n' )

get a string from terminal into the named input
buffer, returns the number of bytes being stored
in the buffer. May provide line-editing functions.

FORTH/ANS core (dpANS.6.1.0695) ordinary primitive

* ALIGN ( -- )

will make the dictionary aligned, usually to a
cell-boundary, see ALIGNED

FORTH/ANS core (dpANS.6.1.0705) ordinary primitive

* ALIGNED ( addr -- addr' )

uses the value (being usually a dictionary-address)
and increment it to the required alignment for the
dictionary which is usually in CELLS - see also
ALIGN

FORTH/ANS core (dpANS.6.1.0706) ordinary primitive

* ALLOT ( count -- )

make room in the dictionary - usually called after
a CREATE word like VARIABLE or VALUE
to make for an array of variables. Does not
initialize the space allocated from the dictionary-heap.
The count is in bytes - use CELLS ALLOT to allocate
a field of cells.

FORTH/ANS core (dpANS.6.1.0710) ordinary primitive

* AND ( val mask -- val' )

mask with a bitwise and - be careful when applying
it to logical values.

FORTH/ANS core (dpANS.6.1.0720) ordinary primitive

BASE

[] no special info, see general notes

FORTH/ANS core (dpANS.6.1.0750) threadstate variable

* BEGIN ( -- ) compile-time: ( -- cs-marker )

start a control-loop, see WHILE and REPEAT

FORTH/ANS core (dpANS.6.1.0760) compiling primitive

BL

[] no special info, see general notes

FORTH/ANS core (dpANS.6.1.0770) ordinary constant

* C! ( value address -- )

store the byte-value at address, see !

FORTH/ANS core (dpANS.6.1.0850) ordinary primitive

* C, ( value -- )

store a new byte-value in the dictionary, implicit 1 ALLOT,
see ,

FORTH/ANS core (dpANS.6.1.0860) ordinary primitive

* C@ ( addr -- value )

fetch a byte-value from the address, see @

FORTH/ANS core (dpANS.6.1.0870) ordinary primitive

* CELL+ ( value -- value' )

adjust the value by adding a single Cell's width
- the value is often an address or offset, see CELLS

FORTH/ANS core (dpANS.6.1.0880) ordinary primitive

* CELLS ( value -- value' )

scale the value by the sizeof a Cell
the value is then often applied to an address or
fed into ALLOT

FORTH/ANS core (dpANS.6.1.0890) ordinary primitive

* CHAR ( 'word' -- value )

return the (ascii-)value of the following word's
first character.

FORTH/ANS core (dpANS.6.1.0895) ordinary primitive

* CHAR+ ( value -- value' )

increment the value by the sizeof one char
- the value is often a pointer or an offset,
see CHARS

FORTH/ANS core (dpANS.6.1.0897) ordinary primitive

* CHARS ( value -- value' )

scale the value by the sizeof a char
- the value is then often applied to an address or
fed into ALLOT (did you expect that sizeof(p4char)
may actually yield 2 bytes?)

FORTH/ANS core (dpANS.6.1.0898) ordinary primitive

* CONSTANT ( value 'name' -- )

CREATE a new word with runtime ((CONSTANT))
so that the value placed here is returned everytime
the constant's name is used in code. See VALUE
for constant-like names that are expected to change
during execution of the program. In a ROM-able
forth the CONSTANT-value may get into a shared
ROM-area and is never copied to a RAM-address.

FORTH/ANS core (dpANS.6.1.0950) defining primitive

* COUNT ( counted-string -- string-pointer string-length )

usually before calling TYPE

(as an unwarranted extension, this word does try to be idempotent).

FORTH/ANS core (dpANS.6.1.0980) ordinary primitive

* CR ( -- )

print a carriage-return/new-line on stdout

FORTH/ANS core (dpANS.6.1.0990) ordinary primitive

* DECIMAL ( -- )

set the BASE to 10
 simulate:
   : DECIMAL 10 BASE ! ;

FORTH/ANS core (dpANS.6.1.1170) ordinary primitive

* DEPTH ( -- value )

return the depth of the parameter stack before
the call, see SP@ - the return-value is in CELLS

FORTH/ANS core (dpANS.6.1.1200) ordinary primitive

* DO ( end start -- ) ... LOOP

pushes $end and $start onto the return-stack ( >R )
and starts a control-loop that ends with LOOP or
+LOOP and may get a break-out with LEAVE . The
loop-variable can be accessed with I

FORTH/ANS core (dpANS.6.1.1240) compiling primitive

* DOES> ( -- pfa )

does twist the last CREATE word to carry
the (DOES>) runtime. That way, using the
word will execute the code-piece following DOES>
where the pfa of the word is already on stack.
(note: FIG option will leave pfa+cell since does-rt is stored in pfa)

FORTH/ANS core compiling primitive

* DROP ( a -- )

just drop the word on the top of stack, see DUP

FORTH/ANS core (dpANS.6.1.1260) ordinary primitive

* DUP ( a -- a a )

duplicate the cell on top of the stack - so the
two topmost cells have the same value (they are
equal w.r.t = ) , see DROP for the inverse

FORTH/ANS core (dpANS.6.1.1290) ordinary primitive

* ELSE ( -- )

will compile an ((ELSE)) BRANCH that performs an
unconditional jump to the next THEN - and it resolves
an IF for the non-true case

FORTH/ANS core (dpANS.6.1.1310) compiling primitive

* EMIT ( char -- )

print the char-value on stack to stdout

FORTH/ANS core (dpANS.6.1.1320) ordinary primitive

* ENVIRONMENT? ( a1 n1 -- false | ?? true )

check the environment for a property, usually
a condition like questioning the existance of
specified wordset, but it can also return some
implementation properties like "WORDLISTS"
(the length of the search-order) or "#LOCALS"
(the maximum number of locals)
Here it implements the environment queries as a SEARCH-WORDLIST 

in a user-visible vocabulary called ENVIRONMENT
 : ENVIRONMENT?
   ['] ENVIRONMENT >WORDLIST SEARCH-WORDLIST
   IF  EXECUTE TRUE ELSE  FALSE THEN ;

FORTH/ANS core (dpANS.6.1.1345) ordinary primitive

* EVALUATE ( str-ptr str-len -- )

INTERPRET the given string, SOURCE id
is -1 during that time.

FORTH/ANS core (dpANS7.6.1.1360) ordinary primitive

* EXECUTE ( xt -- )

run the execution-token on stack - this will usually
trap if it was null for some reason, see >EXECUTE
 simulate:
  : EXECUTE >R EXIT ;

FORTH/ANS core (dpANS.6.1.1370) ordinary primitive

* EXIT ( -- )

will unnest the current colon-word so it will actually
return the word calling it. This can be found in the
middle of a colon-sequence between : and ;

FORTH/ANS core (dpANS.6.1.1380) compiling primitive

* FILL ( mem-addr mem-length char -- )

fill a memory area with the given char, does now
simply call memset()

FORTH/ANS core (dpANS.6.1.1540) ordinary primitive

* FIND ( bstring -- cfa|bstring -1|0|1 )

looks into the current search-order and tries to find
the name string as the name of a word. Returns its
execution-token or the original-bstring if not found,
along with a flag-like value that is zero if nothing
could be found. Otherwise it will be 1 (a positive value)
if the word had been immediate, -1 otherwise (a negative
value).

FORTH/ANS core (dpANS16.6.1.1550) ordinary primitive

* FM/MOD ( n1.n1 n2 -- m n )

divide the double-cell value n1 by n2 and return
both (floored) quotient n and remainder m

FORTH/ANS core (dpANS.6.1.1561) ordinary primitive

* HERE ( -- dp-value )

used with WORD and many compiling words
 simulate:   : HERE DP @ ;

FORTH/ANS core (dpANS.6.1.1650) ordinary primitive

* HOLD ( char -- )

the old-style forth-formatting system -- this
word adds a char to the picutred output string.

FORTH/ANS core (dpANS.6.1.1670) ordinary primitive

* I ( -- value )

returns the index-value of the innermost DO .. LOOP

FORTH/ANS core (dpANS.6.1.1680) compiling primitive

* IF ( value -- ) .. THEN

checks the value on the stack (at run-time, not compile-time)
and if true executes the code-piece between IF and the next
ELSE or THEN . Otherwise it has compiled a branch over
to be executed if the value on stack had been null at run-time.

FORTH/ANS core (dpANS.6.1.1700) compiling primitive

* IMMEDIATE ( -- )

make the LATEST word immediate, see also CREATE

FORTH/ANS core (dpANS.6.1.1710) ordinary primitive

* INVERT ( value -- value' )

make a bitwise negation of the value on stack.
see also NEGATE

FORTH/ANS core (dpANS.6.1.1720) ordinary primitive

* J ( -- value )

get the current DO ... LOOP index-value being
the not-innnermost. (the second-innermost...)
see also for the other loop-index-values at
I and K

FORTH/ANS core (dpANS.6.1.1730) compiling primitive

* KEY ( -- char )

return a single character from the keyboard - the
key is not echoed.

FORTH/ANS core (dpANS.6.1.1750) ordinary primitive

* LEAVE ( -- )

quit the innermost DO .. LOOP - it does even
clean the return-stack and branches to the place directly
after the next LOOP

FORTH/ANS core (dpANS.6.1.1760) compiling primitive

* LITERAL ( value -- ) immediate

if compiling this will take the value from the compiling-stack
and puts in dictionary so that it will pop up again at the
run-time of the word currently in creation. This word is used
in compiling words but may also be useful in making a hard-constant
value in some code-piece like this:
 : DCELLS [ 2 CELLS ] LITERAL * ; ( will save a multiplication at runtime)
(in most configurations this word is statesmart and it will do nothing
in interpret-mode. See LITERAL, for a non-immediate variant)

FORTH/ANS core (dpANS.6.1.1780) compiling primitive

* LOOP ( -- )

resolves a previous DO thereby compiling ((LOOP)) which
does increment/decrement the index-value and branch back if
the end-value of the loop has not been reached.

FORTH/ANS core (dpANS.6.1.1800) compiling primitive

* LSHIFT ( value shift-val -- value' )

does a bitwise left-shift on value

FORTH/ANS core (dpANS.6.1.1805) ordinary primitive

* M* ( a b -- m,m )

multiply and return a double-cell result

FORTH/ANS core (dpANS.6.1.1810) ordinary primitive

* MAX ( a b -- c )

return the maximum of a and b

FORTH/ANS core (dpANS.6.1.1870) ordinary primitive

* MIN ( a b -- c )

return the minimum of a and b

FORTH/ANS core (dpANS.6.1.1880) ordinary primitive

* MOD ( a b -- c )

return the module of "a mod b"

FORTH/ANS core (dpANS.6.1.1890) ordinary primitive

* MOVE ( from to length -- )

memcpy an area

FORTH/ANS core (dpANS.6.1.1900) ordinary primitive

* NEGATE ( value -- value' )

return the arithmetic negative of the (signed) cell
 simulate:   : NEGATE -1 * ;

FORTH/ANS core (dpANS.6.1.1910) ordinary primitive

* OR ( a b -- ab )

return the bitwise OR of a and b - unlike AND this
is usually safe to use on logical values

FORTH/ANS core (dpANS.6.1.1980) ordinary primitive

* OVER ( a b -- a b a )

get the value from under the top of stack. The inverse
operation would be TUCK

FORTH/ANS core (dpANS.6.1.1990) ordinary primitive

* POSTPONE ( [word] -- )

will compile the following word at the run-time of the
current-word which is a compiling-word. The point is that
POSTPONE takes care of the fact that word may be
an IMMEDIATE-word that flags for a compiling word, so it
must be executed (and not pushed directly) to compile
sth. later. Choose this word in favour of COMPILE
(for non-immediate words) and [COMPILE] (for immediate
words)

FORTH/ANS core (dpANS.6.1.2033) compiling primitive

* QUIT ( -- ) no-return

this will throw and lead back to the outer-interpreter.
traditionally, the outer-interpreter is called QUIT
in forth itself where the first part of the QUIT-word
had been to clean the stacks (and some other variables)
and then turn to an endless loop containing QUERY
and EVALUATE (otherwise known as INTERPRET )
- in pfe it is defined as a THROW ,
 : QUIT -56 THROW ;

FORTH/ANS core (dpANS.6.1.2050) ordinary primitive

* R> ( R: a -- a R: )

get back a value from the return-stack that had been saved
there using >R . This is the traditional form of a local
var space that could be accessed with R@ later. If you
need more local variables you should have a look at LOCALS|
which does grab some space from the return-stack too, but names
them the way you like.

FORTH/ANS core compiling primitive

* R@ ( R: a -- a R: a )

fetch the (upper-most) value from the return-stack that had
been saved there using >R - This is the traditional form of a local
var space. If you need more local variables you should have a
look at LOCALS| , see also >R and R> . Without LOCALS-EXT
there are useful words like 2R@ R'@ R"@ R!

FORTH/ANS core (dpANS.6.1.2070) compiling primitive

* RECURSE ( ? -- ? )

when creating a colon word the name of the currently-created
word is smudged, so that you can redefine a previous word
of the same name simply by using its name. Sometimes however
one wants to recurse into the current definition instead of
calling the older defintion. The RECURSE word does it
exactly this.
   traditionally the following code had been in use:
   : GREAT-WORD [ UNSMUDGE ] DUP . 1- ?DUP IF GREAT-WORD THEN ;
   now use
   : GREAT-WORD DUP . 1- ?DUP IF RECURSE THEN ;

FORTH/ANS core (dpANS.6.1.2120) immediate primitive

* REPEAT ( -- )

ends an unconditional loop, see BEGIN

FORTH/ANS core (dpANS.6.1.2140) compiling primitive

* ROT ( a b c -- b c a )

rotates the three uppermost values on the stack,
the other direction would be with -ROT - please
have a look at LOCALS| and VAR that can avoid
its use.

FORTH/ANS core (dpANS.6.1.2160) ordinary primitive

* RSHIFT ( value shift-val -- value' )

does a bitwise logical right-shift on value
(ie. the value is considered to be unsigned)

FORTH/ANS core (dpANS.6.1.2162) ordinary primitive

* S" ( [string<">] -- string-address string-length)

if compiling then place the string into the currently
compiled word and on execution the string pops up
again as a double-cell value yielding the string's address
and length. To be most portable this is the word to be
best being used. Compare with C" and non-portable "

FORTH/ANS core compiling primitive

* S>D ( a -- a,a' )

signed extension of a single-cell value to a double-cell value

FORTH/ANS core ordinary primitive

* SIGN ( a -- )

put the sign of the value into the hold-space, this is
the forth-style output formatting, see HOLD

FORTH/ANS core (dpANS.6.1.2210) ordinary primitive

* SM/REM ( a.a b -- c d )

see /MOD or FM/MOD or UM/MOD or SM/REM

FORTH/ANS core (dpANS.6.1.2214) ordinary primitive

* SOURCE ( -- buffer IN-offset )

the current point of interpret can be gotten through SOURCE.
The buffer may flag out TIB or BLK or a FILE and IN gives
you the offset therein. Traditionally, if the current SOURCE
buffer is used up, REFILL is called that asks for another
input-line or input-block. This scheme would have made it
impossible to stretch an [IF] ... [THEN] over different blocks,
unless [IF] does call REFILL

FORTH/ANS core (dpANS.6.1.2216) ordinary primitive

* SPACE ( -- )

print a single space to stdout, see SPACES
 simulate:    : SPACE  BL EMIT ;

FORTH/ANS core (dpANS.6.1.2220) ordinary primitive

* SPACES ( n -- )

print n space to stdout, actually a loop over n calling SPACE ,
but the implemenation may take advantage of printing chunks of
spaces to speed up the operation.

FORTH/ANS core (dpANS.6.1.2230) ordinary primitive

STATE

[] no special info, see general notes

FORTH/ANS core (dpANS15.6.2.2250) threadstate variable

* SWAP ( a b -- b a )

exchanges the value on top of the stack with the value beneath it

FORTH/ANS core (dpANS.6.1.2260) ordinary primitive

* THEN ( -- )

does resolve a branch coming from either IF or ELSE

FORTH/ANS core (dpANS.6.1.2270) compiling primitive

* TYPE ( string-pointer string-length -- )

prints the string-buffer to stdout, see COUNT and EMIT

FORTH/ANS core (dpANS.6.1.2310) ordinary primitive

* U. ( value )

print unsigned number to stdout

FORTH/ANS core (dpANS.6.1.2320) ordinary primitive

* U< ( a b -- cond )

unsigned comparison, see <

FORTH/ANS core ordinary primitive

* UM* ( a b -- c,c )

unsigned multiply returning double-cell value

FORTH/ANS core (dpANS.6.1.2360) ordinary primitive

* UM/MOD ( a b -- c,c )

see /MOD and SM/REM

FORTH/ANS core (dpANS.6.1.2370) ordinary primitive

* UNLOOP ( -- )

drop the DO .. LOOP runtime variables from the return-stack,
usually used just in before an EXIT call. Using this multiple
times can unnest multiple nested loops.

FORTH/ANS core (dpANS.6.1.2380) compiling primitive

* UNTIL ( cond -- )

ends an control-loop, see BEGIN and compare with WHILE

FORTH/ANS core (dpANS.6.1.2390) compiling primitive

* VARIABLE ( 'name' -- )

CREATE a new variable, so that everytime the variable is
name, the address is returned for using with @ and !
- be aware that in FIG-forth VARIABLE did take an argument
being the initial value. ANSI-forth does different here.

FORTH/ANS core (dpANS.6.1.2410) defining primitive

* WHILE ( cond -- )

middle part of a BEGIN .. WHILE .. REPEAT
control-loop - if cond is true the code-piece up to REPEAT
is executed which will then jump back to BEGIN - and if
the cond is null then WHILE will branch to right after
the REPEAT
(compare with UNTIL that forms a BEGIN .. UNTIL loop)

FORTH/ANS core (dpANS.6.1.2430) compiling primitive

* WORD ( delimiter-char -- here-addr )

read the next SOURCE section (thereby moving >IN ) up
to the point reaching $delimiter-char - the text is placed
at HERE - where you will find a counted string. You may
want to use PARSE instead.

FORTH/ANS core (dpANS.6.1.2450) ordinary primitive

* XOR ( a b -- ab )

return the bitwise-or of the two arguments - it may be unsafe
use it on logical values. beware.

FORTH/ANS core (dpANS.6.1.2490) ordinary primitive

* [ ( -- )

leave compiling mode - often used inside of a colon-definition
to make fetch some very constant value and place it into the
currently compiled colon-defintion with , or LITERAL
- the corresponding unleave word is ]

FORTH/ANS core (dpANS.6.1.2500) immediate primitive

* ['] ( [name] -- ) immediate

will place the execution token of the following word into
the dictionary. See ' for non-compiling variant.

FORTH/ANS core (dpANS.6.1.2510) compiling primitive

* [CHAR] ( [word] -- char )

in compile-mode, get the (ascii-)value of the first charachter
in the following word and compile it as a literal so that it
will pop up on execution again. See CHAR and forth-83 ASCII

FORTH/ANS core (dpANS.6.1.2520) compiling primitive

* ] ( -- )

enter compiling mode - often used inside of a colon-definition
to end a previous [ - you may find a , or LITERAL
nearby in example texts.

FORTH/ANS core (dpANS.6.1.2540) ordinary primitive

/* core extension words */ #TIB

[] no special info, see general notes

FORTH/ANS core (dpANS.6.2.0060) threadstate variable

* .( ( [message] -- )

print the message to the screen while reading a file. This works
too while compiling, so you can whatch the interpretation/compilation
to go on. Some Forth-implementations won't even accept a ." message"
outside compile-mode while the (current) pfe does.

FORTH/ANS core (dpANS.6.2.0200) immediate primitive

* .R ( val prec -- )

print with precision - that is to fill
a field of the give prec-with with
right-aligned number from the converted value

FORTH/ANS core (dpANS.6.2.0210) ordinary primitive

* 0<> ( value -- cond )

returns a logical-value saying if the value was not-zero.
This is most useful in turning a numerical value into a
boolean value that can be fed into bitwise words like
AND and XOR - a simple IF or WHILE doesn't
need it actually.

FORTH/ANS core ordinary primitive

* 0> ( value -- cond )

return value greater than zero
 simulate:    : 0> 0 > ;

FORTH/ANS core (dpANS.6.2.0280) ordinary primitive

* 2>R ( a,a -- R: a,a )

save a double-cell value onto the return-stack, see >R

FORTH/ANS core (dpANS.6.2.0340) compiling primitive

* 2R> ( R: a,a -- a,a R: )

pop back a double-cell value from the return-stack, see R>
and the earlier used 2>R

FORTH/ANS core compiling primitive

* 2R@ ( R: a,a -- a,a R: a,a )

fetch a double-cell value from the return-stack, that had been
previously been put there with 2>R - see R@ for single value.
This can partly be a two-cell LOCALS| value, without LOCALS-EXT
there are alos other useful words like 2R! R'@ R"@

FORTH/ANS core (dpANS.6.2.0415) compiling primitive

* :NONAME ( -- cs.value )

start a colon nested-word but do not use CREATE - so no name
is given to the colon-definition that follows. When the definition
is finished at the corresponding ; the start-address (ie.
the execution token) can be found on the outer cs.stack that may
be stored used elsewhere then.

FORTH/ANS core (dpANS.6.2.0455) defining primitive

* <> ( a b -- cond )

return true if a and b are not equal, see =

FORTH/ANS core ordinary primitive

* ?DO ( end start -- ) .. LOOP

start a control-loop just like DO - but don't execute
atleast once. Instead jump over the code-piece if the loop's
variables are not in a range to allow any loop.

FORTH/ANS core (dpANS.6.2.0620) compiling primitive

* AGAIN ( -- )

ends an infinite loop, see BEGIN and compare with
WHILE

FORTH/ANS core (dpANS.6.2.0700) compiling primitive

* C" ( [string<">] -- bstring )

in compiling mode place the following string in the current
word and return the address of the counted string on execution.
(in exec-mode use a POCKET and leave the bstring-address of it),
see S" string" and the non-portable " string"

FORTH/ANS core compiling primitive

* CASE ( comp-value -- comp-value )

start a CASE construct that ends at ENDCASE
and compares the value on stack at each OF place

FORTH/ANS core (dpANS.6.2.0873) compiling primitive

* COMPILE, ( xt -- )

place the execution-token on stack into the dictionary - in
traditional forth this is not even the least different than
a simple , but in call-threaded code there's a big
difference - so COMPILE, is the portable one. Unlike
COMPILE , [COMPILE] and POSTPONE this word does
not need the xt to have actually a name, see :NONAME

FORTH/ANS core (dpANS.6.2.0945) ordinary primitive

* CONVERT ( a b -- a b )

digit conversion, obsolete, superseded by >NUMBER

FORTH/ANS core (dpANS.6.2.0970) ordinary primitive

* ENDCASE ( comp-value -- )

ends a CASE construct that may surround multiple sections of
OF ... ENDOF code-portions. The ENDCASE has to resolve the
branches that are necessary at each ENDOF to point to right after
ENDCASE

FORTH/ANS core (dpANS.6.2.1342) compiling primitive

* ENDOF ( -- )

resolve the branch need at the previous OF to mark
a code-piece and leave with an unconditional branch
at the next ENDCASE (opened by CASE )

FORTH/ANS core (dpANS.6.2.1343) compiling primitive

* ERASE ( ptr len -- )

fill an area will zeros.
 2000 CREATE DUP ALLOT ERASE

FORTH/ANS core (dpANS.6.2.1350) ordinary primitive

* EXPECT ( str-adr str-len -- )

input handling, see WORD and PARSE and QUERY
the input string is placed at str-adr and its length
 in SPAN - this word is superceded by ACCEPT

FORTH/ANS core (dpANS.6.2.1390) ordinary primitive

FALSE

[] no special info, see general notes

FORTH/ANS core (dpANS.6.2.1485) ordinary constant

* HEX ( -- )

set the input/output BASE to hexadecimal
 simulate:        : HEX 16 BASE ! ;

FORTH/ANS core (dpANS.6.2.1660) ordinary primitive

* MARKER ( 'name' -- )

create a named marker that you can use to FORGET ,
running the created word will reset the dict/order variables
to the state at the creation of this name.
 : MARKER PARSE-WORD (MARKER) ;
see also ANEW which is not defined in ans-forth but which uses
the MARKER functionality in the way it should have been defined.

FORTH/ANS core (dpANS.6.2.1850) ordinary primitive

* NIP ( a b -- b )

drop the value under the top of stack, inverse of TUCK
 simulate:        : NIP SWAP DROP ;

FORTH/ANS core (dpANS.6.2.1930) ordinary primitive

* OF ( comp-value case-value -- comp-value ) .. ENDOF

compare the case-value placed lately with the comp-value
being available since CASE - if they are equal run the
following code-portion up to ENDOF after which the
case-construct ends at the next ENDCASE

FORTH/ANS core (dpANS.6.2.1950) compiling primitive

* PAD ( -- addr )

transient buffer region

FORTH/ANS core (dpANS.6.2.2000) ordinary primitive

* PARSE ( delim-char -- buffer-start buffer-count )

parse a piece of input (not much unlike WORD) and place
it into the given buffer. The difference with word is
also that WORD would first skip any delim-char while
PARSE does not and thus may yield that one. In a newer
version, PARSE will not copy but just return the word-span
being seen in the input-buffer - therefore a transient space.

FORTH/ANS core (dpANS.6.2.2008) ordinary primitive

* PICK ( n -- value )

pick the nth value from under the top of stack and push it
note that
   0 PICK -> DUP         1 PICK -> OVER

FORTH/ANS core (dpANS.6.2.2030) ordinary primitive

* QUERY ( -- )

source input: read from terminal using _accept_ with the
returned string to show up in TIB of /TIB size.

FORTH/ANS core (dpANS.6.2.2040) ordinary primitive

* REFILL ( -- flag )

try to get a new input line from the SOURCE and set
>IN accordingly. Return a flag if sucessful, which is
always true if the current input comes from a
terminal and which is always false if the current input
comes from EVALUATE - and may be either if the
input comes from a file

FORTH/ANS core (dpANS11.6.2.2125) ordinary primitive

* RESTORE-INPUT ( xn ... x1 -- )

inverse of SAVE-INPUT

FORTH/ANS core (dpANS.6.2.2148) ordinary primitive

* ROLL ( xn xm ... x1 n -- xm ... x1 xn )

the extended form of ROT
    2 ROLL -> ROT

FORTH/ANS core (dpANS.6.2.2150) ordinary primitive

* SAVE-INPUT ( -- xn .. x1 )

fetch the current state of the input-channel which
may be restored with RESTORE-INPUT later

FORTH/ANS core (dpANS.6.2.2182) ordinary primitive

SOURCE-ID

[] no special info, see general notes

FORTH/ANS core (dpANS11.6.1.2218) loader code P4_DVaL

SPAN

[] no special info, see general notes

FORTH/ANS core (dpANS.6.2.2240) threadstate variable

TIB

[] no special info, see general notes

FORTH/ANS core (dpANS.6.2.2290) loader code P4_DVaL

* TO ( value [name] -- )

set the parameter field of name to the value, this is used
to change the value of a VALUE and it can be also used
to change the value of LOCALS|

FORTH/ANS core (dpANS13.6.1.2295) compiling primitive

TRUE

[] no special info, see general notes

FORTH/ANS core (dpANS.6.2.2298) ordinary constant

* TUCK ( a b -- b a b )

shove the top-value under the value beneath. See OVER
and NIP
 simulate:    : TUCK  SWAP OVER ;

FORTH/ANS core (dpANS.6.2.2300) ordinary primitive

* U.R ( value prec -- )

print right-aligned in a prec-field, treat value to
be unsigned as opposed to .R

FORTH/ANS core (dpANS.6.2.2330) ordinary primitive

* U> ( a b -- ab )

unsigned comparison of a and b, see >

FORTH/ANS core ordinary primitive

* UNUSED ( -- val )

return the number of cells that are left to be used
above HERE

FORTH/ANS core (dpANS.6.2.2395) ordinary primitive

* VALUE ( value 'name' -- )

CREATE a word and initialize it with value. Using it
later will push the value back onto the stack. Compare with
VARIABLE and CONSTANT - look also for LOCALS| and
VAR

FORTH/ANS core (dpANS.6.2.2405) defining primitive

* WITHIN ( a b c -- cond )

a widely used word, returns ( b <= a  a < c ) so
that is very useful to check an index a of an array
to be within range b to c

FORTH/ANS core (dpANS.6.2.2440) ordinary primitive

* [COMPILE] ( [word] -- )

while compiling the next word will be place in the currently
defined word no matter if that word is immediate (like IF )
- compare with COMPILE and POSTPONE

FORTH/ANS core (dpANS.6.2.2530) immediate primitive

* \ ( [comment] -- )

eat everything up to the next end-of-line so that it is
getting ignored by the interpreter.

FORTH/ANS core immediate primitive

FORTH
* " ( [string<">] -- bstring ) or perhaps ( [..] -- str-ptr str-len )

This is the non-portable word which is why the ANSI-committee
on forth has created the two other words, namely S" and C" ,
since each implementation (and in pfe configurable) uses another
runtime behaviour. FIG-forth did return bstring which is the configure
default for pfe.

FORTH/FORTH core immediate synonym

* PARSE-WORD ( "chars" -- c-addr u )

the ANS'94 standard describes this word in a comment
under PARSE, section A.6.2.2008 - quote:

Skip leading spaces and parse name delimited by a space. c-addr
is the address within the input buffer and u is the length of the
selected string. If the parse area is empty, the resulting string
has a zero length.

If both PARSE and PARSE-WORD are present, the need for WORD is
largely eliminated.

FORTH/FORTH core ordinary primitive

* <BUILDS ( 'name' -- )

make a HEADER whose runtime will be changed later
using DOES>

note that ans'forth does not define <BUILDS and
it suggests to use CREATE directly.

... if you want to write FIG-programs in pure pfe then you have
to use CREATE: to get the FIG-like meaning of CREATE whereas
the ans-forth CREATE is the same as <BUILDS
 : <BUILDS BL WORD HEADER DOCREATE A, 0 A, ;

FORTH/FORTH core defining primitive

CFA'

[] no special info, see general notes

FORTH/FORTH core ordinary primitive

[ANS] CREATE

[] no special info, see general notes

FORTH/ANS core (dpANS.6.1.1000) forthword synonym

* ' ( 'name' -- xt )

return the execution token of the following name. This word
is _not_ immediate and may not do what you expect in
compile-mode. See ['] and '> - note that in FIG-forth
the word of the same name had returned the PFA (not the CFA)
and was immediate/smart, so beware when porting forth-code
from FIG-forth to ANSI-forth.

FORTH/ANS core (dpANS.6.1.0070) forthword synonym

EXTENSIONS
* (MARKER) ( str-ptr str-len -- )

create a named marker that you can use to FORGET ,
running the created word will reset the dict/order variables
to the state at the creation of this name.
 : (MARKER) (CREATE) HERE , 
         GET-ORDER DUP , 0 DO ?DUP IF , THEN LOOP 0 , 
         ...
   DOES> DUP @ (FORGET) 
         ...
 ; 

FORTH/EXTENSIONS core ordinary primitive

* ANEW ( 'name' -- )

creates a MARKER if it doesn't exist,
or forgets everything after it if it does. (it just gets executed).
 : ANEW BL WORD   DUP FIND NIP IF EXECUTE THEN   (MARKER) ;

FORTH/EXTENSIONS core ordinary primitive

ENVIRONMENT /* enviroment hints (testing for -EXT will mark this wordset as present) */ ENVIRONMENT CORE-EXT

[] no special info, see general notes

ENVIRONMENT core ordinary constant

ENVIRONMENT /COUNTED-STRING

[] no special info, see general notes

ENVIRONMENT core ordinary constant

ENVIRONMENT /HOLD

[] no special info, see general notes

ENVIRONMENT core ordinary constant

ENVIRONMENT /PAD

[] no special info, see general notes

ENVIRONMENT core ordinary constant

ENVIRONMENT ADDRESS-UNIT-BITS

[] no special info, see general notes

ENVIRONMENT core ordinary constant

ENVIRONMENT FLOORED

[] no special info, see general notes

ENVIRONMENT core ordinary constant

ENVIRONMENT MAX-CHAR

[] no special info, see general notes

ENVIRONMENT core ordinary constant

ENVIRONMENT MAX-N

[] no special info, see general notes

ENVIRONMENT core ordinary constant

ENVIRONMENT MAX-U

[] no special info, see general notes

ENVIRONMENT core ordinary constant

* ENVIRONMENT STACK-CELLS ( -- value )

the number of cells allocated for the parameter stack of forth.
it can be set with a startup option to match different needs
of applications. (like ENVIRONMENT RETURN-STACK-CELLS) unless
the parameter-stack is made in hardware (like on some special
forth CPUs)

ENVIRONMENT core ordinary primitive

* ENVIRONMENT RETURN-STACK-CELLS ( -- value )

the number of cells allocated for the return stack of forth.
it can be set with a startup option to match different needs
of applications. (like ENVIRONMENT STACK-CELLS) unless
the return-stack is made in hardware (like on some special
forth CPUs) or aliased with the return-stack provided by
the hosting operating system for the forth process thread.

ENVIRONMENT core ordinary primitive