of816/docs/forth_dictionary.md

29 KiB

Forth Dictionary

Updated: 2020-10-31 15:02:22 -0700

!

( n addr -- ) Store n at addr.

"

  • Immediate.

Compiling: ( [text<">] -- ) Parse string, including IEEE 1275-1994 hex interpolation.

Execution: ( -- addr u ) Return parsed string.

#

( ud1 -- ud2 ) Divide ud1 by BASE, convert remainder to char and HOLD it, ud2 = quotient.

#>

( ud -- ) Conclude pictured numeric output.

#IN

( -- addr ) Variable containing number of chars in the current input buffer.

#LINE

( -- addr ) Variable containing the number of lines output.

#OUT

( -- addr ) Variable containing the number of chars output on the current line.

#S

( ud -- 0 ) Perform # until quotient is zero.

$2VALUE

( n1 n2 addr u -- ) Create a definition that pushes the first two cells of the body. initially n1 and n2

$BYTE-EXEC

( addr xt -- ) evaluate FCode at addr with fetch function xt, do not save FCode evaluator state

$CREATE

( addr u -- ) Like CREATE but use addr u for name.

$DIRECT

( -- addr ) addr = address of the CPU direct page

$EMPTY-WL

( -- wid ) Create a new empty wordlist (danger!).

$ENV?-WL

( -- wid ) Return the WID of the wordlist for environmental queries.

$FIND

( c-addr u -- xt true | c-addr u false ) Find word in search order.

$FORGET

( xt -- ) Forget word referenced by xt and subsequent words.

$HEX(

  • Immediate.

( [text<)>] -- addr u ) Parse hex digits, return in allocated string.

$MEMTOP

( -- addr ) addr = top of usable data space

$NUMBER

( addr len -- true | n false ) Attmept to convert string to number.

$RESTORE-INPUT

( xn...x1 n f1 -- f2 ) restore current source input state, including source ID if f1 is true.

( c-addr u -- 0 | xt +-1 ) Search for word in current search order.

$SOURCE-ID

( -- a-addr ) variable containing current input source ID

$SYSIF

( ... u -- ... ) Call system interface function u.

$TMPSTR

( addr1 u1 -- addr2 u1 ) Allocate a temporary string buffer for interpretation semantics of strings and return the address and length of the buffer. If taking the slot used by an existing buffer, free it.

$VALUE

( n addr u -- ) Create a definition that pushes the first cell of the body, initially n.

'

( [old-name< >] -- xt ) Parse old-name in input stream, return xt of word.

(

  • Immediate.

( [text<)>] -- ) Parse and discard text until a right paren or end of input.

(.)

( n -- addr u ) Convert n to text via pictured numeric output.

(CR

( -- ) Emit a CR with no linefeed, set #OUT to 0.

(IS-USER-WORD)

( addr u xt -- ) Create a DEFER definition for string with xt as its initial behavior.

(SEE)

( xt -- ) Attempt to decompile the word at xt.

(TO)

( n xt | n1 n2 xt -- ) change the first cell or two of the body of xt if xt is a 2VALUE, change the first two cells of the body if xt is any other created word, change the first cell of the body

(U.)

( u -- addr u ) Convert u to text via pictured numeric output.

*

( n1 n2 -- n3 ) n3 = n1*n2

*/

( n1 n2 n3 -- n4 ) n4 = quot of n1*n2/n3.

*/MOD

( n1 n2 n3 -- n4 n5 ) n4, n5 = rem, quot of n1*n2/n3.

+

( x1 x2 -- x3 ) x3 = x1 + x2

+!

( n addr -- ) Add n to value at addr.

+LOOP

  • Immediate.
  • Compile-only.

Compilation: ( do-sys -- )

Execution: ( u|n -- ) Add u|n to loop index and continue loop if within bounds.

,

( n -- ) Compile cell n into the dictionary.

-

( x1 x2 -- x3 ) x3 = x1 - x2

-1

( -- -1 )

-ROT

( x1 x2 x3 -- x3 x1 x2 )

-TRAILING

( addr u1 -- addr u2 ) u2 = length of string with trailing spaces omitted.

.

( n -- ) Output n.

."

  • Immediate.

( [text<">] -- ) Parse text and output.

.(

  • Immediate.

( [text<)>] -- ) Parse text until a right paren or end of input, output text.

.D

( n -- ) Output n in decimal base.

.H

( n -- ) Output n in hexadecimal base.

.R

( n u -- ) Output n in a field of u chars.

.S

( -- ) Display stack contents.

.VERSION

( -- ) Display version information.

/

( n1 n2 -- n3 ) Divide n1 by n2, giving quotient n3.

/C

( -- u ) u = size of char in bytes.

/C*

( n1 -- n2 ) n2 = n1 * size of char.

/L

( -- u ) u = size of long in bytes.

/L*

( n1 -- n2 ) n2 = n1 * size of long.

/MOD

( n1 n2 -- n3 n4 ) Divide n1 by n2, giving quotient n4 and remainder n3.

/N

( -- u ) u = size of cell in bytes.

/N*

( n1 -- n2 ) n2 = n1 * size of cell.

/STRING

( c-addr1 u1 n -- c-addr2 u2 ) Adjust string.

/W

( -- u ) u = size of word in bytes.

/W*

( n1 -- n2 ) n2 = n1 * size of word.

0

( -- 0 )

0<

( n -- f ) f = true if n < 0, false if not.

0<=

( n -- f ) f = true if n <= 0, false if not.

0<>

( x -- f ) f = false if x is zero, true if not.

0=

( x -- f ) f = true if x is zero, false if not.

0>

( n -- f ) f = true if n > 0, false if not.

0>=

( n -- f ) f = true if n >= 0, false if not.

1

( -- 1 )

1+

( x1 -- x2 ) x2 = x1 + 1

1-

( x1 -- x2 ) x2 = x1 - 1

2

( -- 2 )

2!

( n1 n2 addr -- ) Store two consecutive cells at addr.

2*

( u1 -- u2 ) Shift n1 one bit left.

2+

( x1 -- x2 ) x2 = x1 + 2

2-

( x1 -- x2 ) x2 = x1 - 2

2/

( x1 -- x2 ) Shift x1 one bit right, extending sign bit.

2>R

( n1 n2 -- ) (R: -- n1 n2 )

2@

( addr -- n1 n2 ) Fetch two consecutive cells from addr.

2CONSTANT

( n1 n2 [name< >] -- ) Create name, name does ( -- n1 n2 ) when executed.

2DROP

( x1 x2 -- )

2DUP

( x1 x2 -- x1 x2 x1 x2 )

2LITERAL

  • Immediate.

2OVER

( x1 x2 x3 x4 -- x1 x2 x3 x4 x1 x2 )

2R>

( R: x1 x2 -- ) ( -- x1 x2 )

2R@

( R: n1 n2 -- n1 n2 ) ( -- n1 n2 )

2ROT

( x1 x2 x3 x4 x5 x6 -- x3 x4 x5 x6 x1 x2 )

2S>D

( n1 n2 -- d1 d2 ) Convert two numbers to double-numbers.

2SWAP

( x1 x2 x3 x4 -- x3 x4 x1 x2 )

2VALUE

( n1 n2 [name< >] -- ) Create a definition that pushes n1 and n2 on the stack, n1 and n2 can be changed with TO.

3

( -- 3 )

3DROP

( x1 x2 x3 -- )

3DUP

( x1 x2 x3 -- x1 x2 x3 x1 x2 x3 )

:

( [name< >] -- colon-sys ) Parse name, start colon definition and enter compiling state.

:NONAME

( -- colon-sys ) Create an anonymous colon definition and enter compiling state. The xt of the anonymous definition is left on the stack after ;.

:TEMP

( -- colon-sys ) Create a temporary anonymous colon definition and enter compiling state. The temporary definition is executed immediately after ;.

;

  • Immediate.
  • Compile-only.

( colon-sys -- ) Consume colon-sys and enter interpretation state, ending the current definition. If the definition was temporary, execute it.

;CODE

  • Immediate.
  • Compile-only.

( -- ) End compiler mode, begin machine code section of definition.

;]

  • Immediate.
  • Compile-only.

Compilation: ( quot-sys -- ) End a quotation.

Execution: ( -- xt ) Leave xt of the quotation on the stack.

<

( n1 n2 -- f ) f = true if n1 < n2, false if not.

<#

( -- ) Begin pictured numeric output.

<<

( u1 u2 -- u3 ) u3 = u1 << u2

<=

( n1 n2 -- f ) f = true if n1 <= n2, false if not.

<>

( x1 x2 -- f ) f = true if x1 <> x2, false if not.

<W@

( addr -- n ) Fetch sign-extended word from addr.

=

( x1 x2 -- f ) f = true if x1 = x2, false if not.

>

( n1 n2 -- f ) f = true if n1 > n2, false if not.

>=

( n1 n2 -- f ) f = true if n1 >= n2, false if not.

>>

( u1 u2 -- u3 ) u3 = u1 >> u2

>>A

( x1 x2 -- x3 ) x3 = x1 >> x2, extending sign bit.

>BODY

( xt -- a-addr) return body of word at xt, if unable then throw exception -31

>IN

( -- addr ) Variable containing offset to the current parsing area of input buffer.

( xt -- addr|0 ) Get link field of word at xt or 0 if none.

>NAME

( xt -- c-addr u ) Get string name of word at xt, or ^xt if anonymous/noname. Uses pictured numeric output.

>NUMBER

( ud1 addr1 u1 -- ud2 addr2 u2 ) Convert text to number.

>R

( n -- ) (R: -- n )

>R@

( n -- n ) ( R: -- n )

?

( addr -- ) Output signed contents of cell at addr.

?DO

  • Immediate.
  • In interpretation state, starts temporary definition.

Compilation: ( -- do-sys )

Execution: ( limit start -- ) Start DO loop, skip if limit=start.

?DUP

( 0 -- 0 ) | ( n1 -- n1 n2 ) n2 = n1.

?LEAVE

  • Compile-only.

( f -- ) Exit do loop if f is nonzero.

@

( addr -- n ) Fetch n from addr.

A"

( [text<">] -- c-addr u ) Parse text in input buffer, copy to allocated string.

ABORT

( -- ) Execute -1 THROW.

ABORT"

  • Immediate.

Compilation/Interpretation: ( [text<">] -- )

Execution: ( f -- ) If f is true, display text and execute -2 THROW.

ABS

( n1 -- n2 ) Take the absolute value of n1.

ACCEPT

( addr len -- u ) get input line of up to len chars, stor at addr, u = # chars accepted

ACONCAT

( addr1 u1 addr2 u2 -- addr3 u1+u2 ) Concatenate allocated strings, freeing the originals.

AGAIN

  • Immediate.
  • Compile-only.

Compilation: ( dest -- ) Resolve dest.

Execution: ( -- ) Jump to BEGIN.

AHEAD

  • Immediate.
  • In interpretation state, starts temporary definition.

Compilation: ( -- orig )

Execution: ( -- ) Jump ahead as to the resolution of orig.

ALIAS

( [name1< >] [name2< >] -- ) create name1, name1 is a synonym for name2

ALIGN

( u -- u ) Align u (no-op in this implementation).

ALIGNED

( u1 -- u2 ) u2 = next aligned address after u1.

ALLOC-MEM

( u -- c-addr ) Allocate memory from heap.

ALLOT

( n -- ) Allocate n bytes in the dictionary.

ALSO

( -- ) Duplicate the first wordlist in the search order.

AND

( u1 u2 -- u3 ) u3 = u1 & u2

ASCII

  • Immediate.

( [word< >] -- char ) Perform either CHAR or [CHAR] per the current compile state.

AT-XY

( u1 u2 -- ) Place cursor at col u1 row u2 (uses ANSI escape sequence).

BASE

( -- a-addr ) Variable containing current numeric base.

BEGIN

  • Immediate.
  • In interpretation state, starts temporary definition.

Compilation: ( -- dest )

Execution: ( -- ) start a BEGIN loop

BEHAVIOR

( xt -- ) Return the first cell of the body of word at xt, normally a DEFER word but will do the same on some other types of words (CREATE, VARIABLE, VALUE, etc).

BELL

( -- )

BETWEEN

( n1 n2 n3 -- f ) f = true if n2<=n1<=n3, false otherwise

BINARY

( -- ) Store 2 to BASE.

BL

( -- )

BLANK

( addr len -- ) Fill memory with spaces.

BLJOIN

( b.l b2 b3 b.h -- q ) Join bytes into quad.

BODY>

( a-addr -- xt ) return xt of word with body at a-addr, if unable throw exc. -31

BOUNDS

( n1 n2 -- n1+n2 n1 )

BS

( -- )

BSX

( byte -- sign-extended )

BUFFER:

( n [name< >] -- ) Allocate n bytes of memory, create definition that returns the address of the allocated memory.

BWJOIN

( b.l b.h -- w ) Join bytes into word.

BYE

( -- ) Restore system stack pointer and exit Forth.

BYTE-LOAD

( addr xt -- ) Evaluate FCode at addr with fetch function xt, saving and

C!

( char addr -- ) Store char at addr.

C,

( char -- ) Compile char into dictionary.

C;

( code-sys -- ) Consume code-sys, end CODE or LABEL definition.

C@

( addr -- char ) Fetch char from addr.

CA+

( u1 n -- u2 ) u2 = u1 + n * size of char in bytes.

CA1+

( n1 -- n2 ) n2 = n1 + size of char.

CARRET

( -- )

CASE

  • Immediate.
  • In interpretation state, starts temporary definition.

Compilation: ( -- case-sys ) start a CASE...ENDCASE structure

Execution: ( -- )

CATCH

( xt -- xi ... xj n|0 ) Call xt, trap exception, and return it in n.

CELL+

( u1 -- u2 ) u2 = u1 + size of cell in bytes.

CELLS

( n1 -- n2 ) n2 = n1 * size of cell.

CHAR

( [word< >] -- char ) Parse word from input stream, return value of first char.

CHAR+

( u1 -- u2 ) u2 = u1 + size of char in bytes.

CHARS

( n1 -- n2 ) n2 = n1 * size of char.

CICOMP

( addr1 addr2 u1 -- n1 ) Case-insensitive compare two strings of length u1.

CLEAR

( ... -- ) Empty stack.

CMOVE

( addr1 addr2 len -- ) Move memory, startomg from the bottom.

CMOVE>

( addr1 addr2 len -- ) Move memory, starting from the top.

CODE

( [name< >] -- code-sys ) Create a new CODE definiion.

COMP

( addr1 addr2 u1 -- n1 ) Compare two strings of length u1.

COMPARE

( addr1 u1 addr2 u2 -- n1 ) Compare two strings.

COMPILE

  • Immediate.
  • Compile-only.

( -- ) Compile code to compile the immediately following word which must resolve to an xt. Better to use POSTPONE in most cases.

COMPILE,

( xt -- ) Compile xt into the dictionary.

CONSTANT

( n [name< >] -- ) alias of VALUE, OF816 doesn't have true constants

CONTEXT

( -- addr ) Return address of cell with first wid in the search order. if search order is empty, sets the search order to contain the CURRENT word list.

CONTROL

  • Immediate.

( [name< >] ) Parse name, place low 5 bits of first char on stack. If compiling state, compile it as a literal.

COUNT

( addr -- addr+1 u ) Count packed string at addr.

CPEEK

( addr -- char true ) Access memory at addr, returning char.

CPOKE

( char addr -- true ) Store char at addr.

CR

( -- ) Emit a CR/LF combination, increment #LINE, set #OUT to 0.

CREATE

( [name< >] -- ) Create a definition, when executed pushes the body address.

D#

  • Immediate.

( [number< >] n ) Parse number as decimal, compile as literal if compiling.

D+

( d1 d2 -- d3 ) d3 = d1 + d2

D-

( d1 d2 -- d3 ) d3 = d1 - d2

D.

( d -- ) Output d.

D.R

( d u -- ) Output d in a field of u chars.

D>S

( d -- n ) Convert double-number to number.

DABS

( d1 -- d1|d2 ) Take the absolute value of d1.

DEBUG-MEM

( -- ) Display heap and temporary string information.

DECIMAL

( -- ) Store 10 to BASE.

DEFER

( [name< >] -- ) Create definition that executes the first word of the body as an xt.

DEFINITIONS

( -- ) Set the compiler wordlist to the first wordlist in the search order.

DEPTH

( xu ... x1 -- xu ... x1 u )

DIGIT

( char base -- digit true | char false ) Attempt to convert char to digit.

DNEGATE

( d1 -- d2 ) Negate d1.

DO

  • Immediate.
  • In interpretation state, starts temporary definition.

Compilation: ( -- do-sys )

Execution: ( limit start -- ) Start DO loop.

DOES>

  • Immediate.
  • Compile-only.

( -- ) alter execution semantics of most recently-CREATEd definition to perform the execution semantics of the code following DOES>.

DROP

( x -- )

DUMP

( addr len -- ) Dump memory.

DUP

( n1 -- n1 n2 ) n2 = n1.

ELSE

  • Immediate.
  • Compile-only.

Compilation: ( if-sys -- else-sys )

Execution: ( -- ) ELSE clause of IF ... ELSE ... THEN.

EMIT

( char -- ) Output char.

END-CODE

  • Immediate.
  • Compile-only.

( code-sys -- ) Synonym for C;.

ENDCASE

  • Immediate.
  • Compile-only.

Compilation: ( case-sys -- ) Conclude a CASE...ENDCASE structure.

Execution: ( | n -- ) Continue execution, dropping n if no OF matched.

ENDOF

  • Immediate.
  • Compile-only.

Compilation; ( case-sys of-sys -- case-sys ) Conclude an OF...ENDOF structure.

Execution: Continue execution at ENDCASE of case-sys.

ENVIRONMENT?

( c-addr u -- xn...x1 t | f ) Environmental query.

ERASE

( addr len -- ) Zero fill memory.

EVAL

synonym for EVALUATE

EVALUATE

( xxn...xx1 addr u -- yxn...yx1 ) Interpret text in addr u.

EVEN

( n1 -- n1|n2 ) n2 = n1+1 if n1 is odd.

EXECUTE

( xt -- ) execute xt, regardless of its flags

EXIT

  • Compile-only.

( -- ) Exit this word, to the caller.

EXIT?

( -- f ) If #LINE >= 20, prompt user to continue and return false if they want to.

EXPECT

( addr len -- ) get input line of up to len chars, stor at addr, actual len in SPAN

FALSE

( -- false ) false = all zero bits

FCODE-REVISION

( -- u ) Return FCode revision

FERROR

( -- ) Display FCode IP and byte, throw exception -256.

FIELD

Compilation: ( offset size [name< >] -- offset+size ) create name Execution of name: ( addr -- addr+offset)

FILL

( addr len char -- ) Fill memory with char.

FIND

( c-addr -- xt|0 ) Find packed string word in search order, 0 if not found.

FM/MOD

( d n1 -- n2 n3 ) Floored divide d by n1, giving quotient n3 and remainder n2.

FORGET

( [name< >] -- ) Attempt to forget name and subsequent definitions in compiler word list. This may have unintended consequences if things like wordlists and such were defined after name.

FORTH

( -- ) Set the first wordlist in the search order to the system words

FORTH-WORDLIST

( -- wid ) Return the WID of the wordlist containing system words.

FREE-MEM

( c-addr u -- ) Release memory to heap, u is currently ignored.

GET-CURRENT

( -- wid ) Get WID current compiler wordlist.

GET-ORDER

( -- widn ... wid1 u ) Get dictionary search order.

GET-TOKEN

( fcode# -- xt f ) Get fcode#'s xt and immediacy.

H#

  • Immediate.

( [number< >] n ) Parse number as hexadecimal, compile as literal if compiling.

HERE

( -- addr ) Return dictionary pointer.

HEX

( -- ) Store 16 to BASE.

HOLD

( c -- ) Place c in pictured numeric output.

I

  • Compile-only.

( -- n ) Copy inner loop index to stack.

IF

  • Immediate.
  • In interpretation state, starts temporary definition.

Compilation: ( -- if-sys )

Execution: ( n -- ) Begin IF ... ELSE ... ENDIF.

IMMEDIATE

( -- ) Mark last compiled word as an immediate word.

INVERT

( x1 -- x2 ) Invert the bits in x1.

J

  • Compile-only.

( -- n ) Copy second-inner loop index to stack.

KEY

( -- char ) wait for input char, return it

KEY?

( -- f ) f = true if input char is ready, false otherwise

L!

( n addr -- ) Store n at addr.

L,

( q -- ) Compile cell q into dictionary.

L@

( addr -- n ) Fetch n from addr.

LA+

( u1 n -- u2 ) u2 = u1 + n * size of long in bytes.

LA1+

( n1 -- n2 ) n2 = n1 + size of long.

LABEL

( [name< >] -- code-sys ) Create a new LABEL definition.

LAST

( -- addr ) Return address of last definition in current vocabulary.

LBFLIP

( q -- q' ) Flip the byte order of quad.

LBFLIPS

( addr len -- ) Perform LBFLIP on the cells in memory.

LBSPLIT

( u -- u1 ... u4 ) u1 ... u4 = bytes of u.

LCC

( char -- char' ) Lower case convert char.

LEAVE

  • Compile-only.

( -- ) Exit DO loop.

LEFT-PARSE-STRING

( str len char -- r-str r-len l-str l-len ) Parse string for char, returning the left and right sides.

LINEFEED

( -- )

LITERAL

  • Immediate.

Compilation: ( n -- )

Execution: ( -- n )

LOOP

  • Immediate.
  • Compile-only.

Compilation: ( do-sys -- )

Execution: ( -- ) Add 1 to loop index and continue loop if within bounds.

LPEEK

( addr -- cell true ) Access memory at addr, returning cell.

LPOKE

( cell addr -- true ) Store cell at addr.

LSHIFT

( u1 u2 -- u3 ) u3 = u1 << u2

LWFLIP

( q -- q ) Flip the word order of quad.

LWFLIPS

( addr len -- ) Perform LWFLIP on the cells in memory.

LWSPLIT

( u -- u1 ... u2 ) u1 ... u2 = words of u.

M*

( n1 n2 -- d ) d = n1*n2

MAX

( n1 n2 -- n1|n2 ) Return the greater of n1 or n2.

MIN

( n1 n2 -- n1|n2 ) Return the smaller of n1 or n2.

MOD

( n1 n2 -- n3 ) Divide n1 by n2, giving remainder n3.

MOVE

( addr1 addr2 len -- ) Move memory.

N>R

( xu ... x0 u -- ) ( R: -- x0 ... xu ) remove u+1 items from parameter stack and place on return stack.

NA+

( u1 n -- u2 ) u2 = u1 + n * size of cell in bytes.

NA1+

( n1 -- n2 ) n2 = n1 + size of cell.

NEGATE

( n1 -- n2 ) Negate n1.

NIP

( x1 x2 -- x2 )

NOOP

( -- ) Do nothing.

NOSHOWSTACK

( -- ) assuming STATUS is a defer, set it to NOOP

NOT

( x1 -- x2 ) Invert the bits in x1.

NR>

( R: x0 ... xu -- ) ( u -- xu ... x0 ) remove u+1 items from return stack and place on parameter stack.

O#

  • Immediate.

( [number< >] n ) Parse number as octal, compile as literal if compiling.

OCTAL

( -- ) Store 8 to BASE.

OF

  • Immediate.
  • Compile-only.

Compilation: ( case-sys -- case-sys of-sys ) Begin an OF...ENDOF structure.

Execution: ( x1 x2 -- | x1 ) Execute OF clause if x1 = x2, leave x1 on stack if not.

OFF

( addr -- ) Store all zero bits in cell at addr.

ON

( addr -- ) Store all one bits to cell at addr.

ONLY

( -- ) Set the search order to contain only the system wordlist.

OR

( u1 u2 -- u3 ) u3 = u1 | u2

ORDER

( -- ) Display the current search order and compiler wordlist.

OVER

( x1 x2 -- x1 x2 x2 )

PACK

( str len addr -- addr ) Pack string into addr, similar to PLACE in some Forths.

PAD

( -- a-addr ) return address of PAD

PAGE

( -- ) Clear screen & home cursor (uses ANSI escape sequence).

PARSE

( char [text] -- addr u ) Parse text from input stream, delimited by char.

PARSE-2INT

( str len -- val.lo val.hi ) Parse two integers from string in the form "n2,n2".

PARSE-NAME

( [word< >] -- addr u ) Alias of PARSE-WORD.

PARSE-WORD

( [word< >] -- addr u ) Parse word from input stream, return address and length.

PICK

( xu ... x1 x0 u -- xu ... x1 xu )

POSTPONE

  • Immediate.

( [name< >] -- ) Compile the compilation semantics of name.

PREVIOUS

( -- ) Remove the first wordlist in the search order.

QUIT

( -- ) ( R: ... -- ) Enter outer interpreter loop, aborting any execution.

R+1

( R: n1 -- n2 ) n2 = n1 + 1

R>

( R: x -- ) ( -- x )

R@

( R: n -- n ) ( -- n )

RB!

  • Immediate.

( byte addr -- ) Perform FCode-equivalent RB!: store byte.

RB@

  • Immediate.

( addr -- byte ) Perform FCode-equivalent RB@: fetch byte.

RDROP

( R: n -- )

RECURSE

  • Immediate.
  • Compile-only.

( -- ) Compile the execution semantics of the most current definition.

RECURSIVE

  • Immediate.
  • Compile-only.

( -- ) Make the current definition findable during compilation.

REFILL

( -- f ) refill input buffer, f = true if that worked, false if not

REPEAT

  • Immediate.
  • Compile-only.

Compilation: ( orig dest -- ) Resolve orig and dest.

Execution: ( -- ) Repeat BEGIN loop.

RESET-ALL

( -- ) Reset the system.

RESTORE-INPUT

( xn...x1 n -- f ) Restore current source input state, source ID must match current.

RL!

  • Immediate.

( cell addr -- ) Perform FCode-equivalent RL!, store cell.

RL@

  • Immediate.

( addr -- cell ) Perform FCode-equivalent RL@: fetch cell.

ROLL

( xu ... x0 u -- xu-1 .. x0 xu )

ROT

( x1 x2 x3 -- x2 x3 x1 )

RSHIFT

( u1 u2 -- u3 ) u3 = u1 >> u2

RW!

  • Immediate.

( word addr -- ) Perform FCode-equivalent RW!: store word.

RW@

  • Immediate.

( addr -- word ) Perform FCode-equivalent RW@: fetch word.

S"

  • Immediate.

( [text<">] -- addr u )

S.

( n -- ) Output n.

S>D

( n -- d ) Convert number to double-number.

SAVE-INPUT

SEAL

( -- ) Set the search order to contain only the current top of the order.

SEARCH

( c-addr1 u1 c-addr2 u2 -- c-addr3 u3 flag ) Search for substring.

SEARCH-WORDLIST

( c-addr u wid -- 0 | xt +-1 ) Search wordlist for word.

SEE

( [text< >] -- ) Attempt to decompile name.

SET-CURRENT

( wid -- ) Set the compiler wordlist.

SET-ORDER

( widn ... wid1 n -- ) Set dictionary search order.

SET-TOKEN

( xt fcode# f -- ) Set fcode# to execute xt, immediacy f.

SHOWSTACK

( -- ) assuming STATUS is a defer, set it to .S

SIGN

( n -- ) Place - in pictured numeric output if n is negative.

SIGNUM

( n -- s ) s = -1 if n is negative, 0 if 0, 1 if positive.

SLITERAL

  • Immediate.
  • Compile-only.

Compiling: ( addr1 u -- ) compile string literal into current def

Execution: ( -- addr2 u ) return compiled string

SM/REM

( d n1 -- n2 n3 ) Symmetric divide d by n1, giving quotient n3 and remainder n2.

SOURCE

( -- c-addr u ) return address and length of input source buffer

SOURCE-ID

( -- n ) return current input source id (0 = console, -1 = string, >0 = file)

SPACE

( -- ) emit a space

SPACES

( u -- ) emit u spaces

SPAN

SQRTREM

( u1 -- u2 u3 ) u2 = closest square root <= to the true root, u3 = remainder.

STATE

( -- addr ) Variable, zero if interpreting, nonzero if compiling.

STRUCT

( -- 0 )

SWAP

( x1 x2 -- x2 x1 )

THEN

  • Immediate.
  • Compile-only.

Compilation: ( if-sys|else-sys -- )

Execution: ( -- ) Conclustion of IF ... ELSE ... THEN.

THROW

( n -- ) Throw exception n if n is nonzero.

TO

  • Immediate.

( n [name< >] -- ) Change the first cell of the body of xt to n. Can be used on most words created with CREATE, DEFER, VALUE, etc. (even VARIABLE).

TRUE

( -- true ) true = all one bits

TUCK

( x1 x2 -- x2 x1 x2 )

TYPE

( addr u -- ) Output string.

U#

( u1 -- u2 ) Divide u1 by BASE, convert remainder to char and HOLD it, u2 = quotient.

U#>

( u -- ) Conclude pictured numeric output.

U#S

( u -- 0 ) Perform U# until quotient is zero.

U*

( u1 u2 -- u3 ) u3 = u1*u2

U.

( u -- ) Output u.

U.0

( u1 -- ) Output u1 with no trailing space.

U.R

( u1 u2 -- ) Output u1 in a field of u2 chars.

U/MOD

( u1 u2 -- u3 u4 ) Divide u1 by u2, giving quotient u4 and remainder u3.

U2/

( u1 -- u2 ) Shift n1 one bit right.

U<

( u1 u2 -- f ) f = true if u1 < u2, false if not.

U<=

( u1 u2 -- f ) f = true if u1 <= u2, false if not.

U>

( u1 u2 -- f ) f = true if u1 > u2, false if not.

U>=

( u1 u2 -- f ) f = true if u1 >= u2, false if not.

UD/MOD

( d1 n1 -- d2 n2 ) d2, n2 = remainder and quotient of d1/n1

UM*

( u1 u2 -- ud ) ud = u1*u2

UM/MOD

( ud u1 -- u2 u3 ) Divide ud by u1, giving quotient u3 and remainder u2.

UNALIGNED-L!

( n addr -- ) Store n at addr.

UNALIGNED-L@

( addr -- n ) Fetch n from addr.

UNALIGNED-W!

( word addr -- ) Store word at addr.

UNALIGNED-W@

( addr -- n ) Fetch word from addr.

UNLOOP

  • Compile-only.

( -- ) ( R: loop-sys -- ) Remove loop parameters from return stack.

UNTIL

  • Immediate.
  • Compile-only.

Compilation: ( dest -- )

Execution: ( x -- ) UNTIL clause of BEGIN...UNTIL loop

UNUSED

( -- u ) u = unused data space accounting for PAD and dynamic allocations

UPC

( char -- char' ) Upper case convert char.

VALUE

( n [name< >] -- ) Create a definition that pushes n on the stack, n can be changed with TO.

VARIABLE

( [name< >] -- ) Execute CREATE name and allocate one cell, initially a zero.

VOCABULARY

( "name"<> -- ) Create a new named wordlist definition. When name is executed, put the WID of the wordlist at the top of the search order. The WID is the address of the body of the named wordlist definition.

W!

( word addr -- ) Store word at addr.

W,

( word -- ) Compile word into dictionary.

W@

( addr -- word ) Fetch word from addr.

WA+

( u1 n -- u2 ) u2 = u1 + n * size of word in bytes.

WA1+

( n1 -- n2 ) n2 = n1 + size of word.

WBFLIP

( w -- w' ) Flip the byte order of w.

WBFLIPS

( addr len -- ) Perform WBFLIP on the words in memory.

WBSPLIT

( u -- u1 .. u2 ) u1 .. u2 = bytes of word u.

WHILE

  • Immediate.
  • Compile-only.

Compilation: ( dest -- orig dest )

Execution: ( x -- ) WHILE clause of BEGIN...WHILE...REPEAT loop

WITHIN

( n1|u1 n2|u2 n3|u3 -- f ) f = true if n2|u2 <= n1|u1 < n3|u3, false otherwise

WLJOIN

( w.l w.h -- q ) Join words into quad.

WORD

( char [text] -- addr ) Parse text from input stream delimited by char, return address of WORD buffer containing packed string.

WORDLIST

( -- wid ) Create a new wordlist.

WORDS

( -- ) Output the words in the CONTEXT wordlist.

WPEEK

( addr -- word true ) Access memory at addr, returning word.

WPOKE

( word addr -- true ) Store word at addr.

WSX

( word -- sign-extended )

XOR

( u1 u2 -- u3 ) u3 = u1 ^ u2

[

  • Immediate.
  • Compile-only.

( -- ) Enter interpretation state.

[']

  • Immediate.

( [old-name< >] -- xt ) Immediately parse old-name in input stream, return xt of word.

[:

  • Immediate.
  • Compile-only.

Compilation: ( -- quot-sys ) Start a quotation.

Execution: ( -- ) Skip over quotation code.

[CHAR]

  • Immediate.
  • Compile-only.

( [word< >] -- char ) Immediately perform CHAR and compile literal.

[COMPILE]

  • Immediate.

( [name< >] -- ) Compile name now. Better to use POSTPONE.

\

  • Immediate.

( [text] -- ) Discard the rest of the input buffer (or line during EVALUATE)

]

  • Immediate.

( -- ) Enter compilation state.