of816/docs/forth_dictionary.md

25 KiB

Forth Dictionary

Updated: 2020-01-13 15:23:03 -0800

!

( n c-addr -- ) write cell n to c-addr

"

( "text"<"> -- c-addr u ) parse string, including hex interpolation

( 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 str len ) 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 state

$CREATE

( c-addr u -- ) like CREATE but use c-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(

( "text" -- c-addr u ) parse hex, 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

( 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

$VALUE

( n str len ) 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

(

( "text" -- ) parse and discard text until a right paren or end of input

(.)

( n -- c-addr u ) convert n to text via pictured numeric output

(CR

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

(IS-USER-WORD)

( str len xt -- ) create a DEFER definition for string with xt as its initial behavior

(SEE)

( xt -- ) attempt to decompile the word at xt

(U.)

( u -- c-addr u ) convert u to text via pictured numeric output

*

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

*/

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

*/MOD

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

+

( n1 n2 -- n3 ) n3 = n1+n2

+!

( n c-addr -- ) add n to value at c-addr

+LOOP

Compilation: ( C: do-sys -- )

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

,

( n -- ) compile cell n into the dictionary

-

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

-1

( -- -1 )

-ROT

( n1 n2 n3 -- n3 n1 n2 )

-TRAILING

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

.

( n -- ) output n

."

( "text"<"> -- ) output parsed text

.(

( "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 ) symmetric 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 ) symmetric 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 x < 0, false if not

0<=

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

0<>

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

0=

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

0>

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

0>=

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

1

( -- 1 )

1+

( n -- n' ) increment top stack item

1-

( n -- n' ) decrement top stack item

2

( -- 2 )

2!

( n1 n2 c-addr -- ) write consecutive cells n1 and n2 to c-addr

2*

( n -- n' ) shift n1 one bit left

2+

( n -- n' ) increment top stack item by 2

2-

( n -- n' ) decrement top stack item by 2

2/

( n -- n' ) shift n1 one bit right, extending sign bit

2>R

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

2@

( c-addr -- n1 n2 ) fetch two consecutive cells from c-addr

2CONSTANT

( n1 n2 "name"<> -- ) create name, name does ( -- n1 n2 ) when executed

2DROP

( n1 n2 -- )

2DUP

( n1 n2 -- n1 n2 n3 n4 ) n3 = n1, n4 = n2

2OVER

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

2R>

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

2R@

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

2ROT

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

2S>D

( n n -- d d ) convert two numbers to double-numbers

2SWAP

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

3

( -- 3 )

3DROP

( n1 n2 n3 -- )

3DUP

( n1 n2 n3 -- n1 n2 n3 n4 n5 n6 ) n4 = n1, n5 = n2, n6 = n3

:

( "name"<> -- colon-sys ) parse name, create 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 ;

;

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

;CODE

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

;]

<

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

<#

( -- ) begin pictured numeric output

<<

( n1 n2 -- n3 ) n3 = n1 << n2

<=

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

<>

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

<W@

( c-addr -- n ) fetch sign-extended word from c-addr

=

( n1 n2 -- f ) f = true if n1 = n2, 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

>>

( n1 n2 -- n3 ) n3 = n1 >> n2

>>A

( n1 n2 -- n3 ) n3 = n1 >> n2, 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 function at xt or 0 if none

>NAME

( xt -- c-addr u ) get string name of function at xt, or ^xt if anonymous/noname

>NUMBER

( ud1 c-addr1 u1 -- ud2 c-addr2 u2 ) convert text to number

>R

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

>R@

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

?

( a-addr -- ) output signed contents of cell at a-addr

?DO

Compilation: ( -- ) ( R: -- do-sys )

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

?DUP

( n -- n ) if n = 0, else ( n1 -- n1 n2 ) n2 = n1

?LEAVE

( f -- ) exit loop if f is nonzero

@

( c-addr -- n ) fetch cell from c-addr

A"

( "text"<"> -- c-addr u ) parse quoted text in input buffer, copy to allocated string

ABORT

( -- ) Execute -1 THROW.

ABORT"

Compilation/Interpretation: ( [text<">] -- ) Execution: ( f -- ) If f is true, display text and execute -2 THROW.

ABS

( n -- n' ) take the absolute value of n

ACCEPT

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

ACONCAT

( c-addr1 u1 c-addr2 u2 -- c-addr3 u1+u2 ) concatenate allocated strings

AGAIN

( C: dest -- ) ( R: -- ) resolve dest, jump to BEGIN

AHEAD

( C: orig ) ( E: -- ) jump ahead as resolved by e.g. THEN

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

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

AND

( n1 n2 -- n3 ) n3 = n1 & n2

ASCII

( "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 ) System BASE variable.

BEGIN

( C: -- dest ) ( E: -- ) start a BEGIN loop

BEHAVIOR

( "name"<> -- ) return the first cell of the body of name, which should be a DEFER word

BELL

( -- )

BETWEEN

( n1|u1 n2|u2 n3|u3 -- f ) f = true if n2|u2 <= n1|u1 <= n3|u3, 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 -- ) allocate memory immediately, create definition that returns address of memory

BWJOIN

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

BYE

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

BYTE-LOAD

( addr xt -- ) sav state, evaluate FCode at addr with fetch function xt, restore state

C!

( char c-addr -- ) write char n to c-addr

C,

( char -- ) compile char into dictionary

C;

( code-sys -- ) consume code-sys, end CODE or LABEL definition

C@

( c-addr -- char ) fetch char from c-addr

CA+

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

CA1+

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

CARRET

( -- )

CASE

Compilation: ( R: -- 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

( n1 ... nx -- ) empty stack

CMOVE

( addr1 addr2 len -- ) move startomg from the bottom

CMOVE>

( addr1 addr2 len -- ) move 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

( -- ) Compile code to compile the immediately following word. Better to use POSTPONE.

COMPILE,

( xt -- ) compile xt into the dictionary

CONSTANT

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

CONTEXT

( -- wid ) Return first wordlist in search order.

CONTROL

( "name"<> ) parse name, place low 5 bits of first char on stack, if compiling stat compile it as a literal

COUNT

( c-addr -- c-addr+1 u ) count packed string at c-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, set increment #LINE

CREATE

( "name"<> -- ) create a definition, when executed pushes the body address

D#

( "#"<> -- n | -- ) parse following 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

( d -- d' ) take the absolute value of d

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

( n1 ... nx -- n1 ... nx x )

DIGIT

( char base -- digit true | char false ) attempt to convert char to digit

DNEGATE

( d -- d' ) negate d

DO

Compilation: ( -- ) ( R: -- do-sys )

Execution: ( limit start -- ) begin DO loop

DOES>

( -- ) alter execution semantics of most recently-created definition to perform the following execution semantics.

DROP

( n1 -- )

DUMP

( addr len -- ) dump memory

DUP

( n1 -- n1 n2 ) n2 = n1

ELSE

( C: if-sys -- else-sys ) ( E: -- ) ELSE clause of IF ... ELSE ... THEN

EMIT

( char -- ) Output char.

END-CODE

( code-sys -- ) synonym for C;

ENDCASE

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

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

ENDOF

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 with spaces

EVAL

synonym for EVALUATE

EVALUATE

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

EVEN

( n1 -- n2 ) if n1 is odd, n2=n1+1, otherwise n2=n1

EXECUTE

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

EXIT

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

( offset size "name"<> -- offset+size ) create name, name exec: ( addr -- addr+offset)

FILL

( addr len char -- ) fill memory with char

FIND

( c-addr -- xt ) 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#

( "#"<> -- n | -- ) parse following number as hex, compile as literal if compiling

HERE

( -- c-addr ) return dictionary pointer

HEX

( -- ) store 16 to BASE

HOLD

( c -- ) place c in pictured numeric output

I

( -- n ) copy inner loop index to stack

IF

( C: if-sys ) ( E: n -- ) begin IF ... ELSE ... ENDIF

IMMEDIATE

( -- ) mark last compiled word as an immediate word

INVERT

( x -- x' ) invert the bits in x

J

( -- 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 c-addr -- ) write cell n to c-addr

L,

( q -- ) compile quad into the dictionary

L@

( c-addr -- n ) fetch cell from c-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

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

( -- ) exit 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

( n -- ) compile numeric literal n into dictionary, leave n on stack at execution

LOOP

Compilation: ( C: 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

( n1 n2 -- n3 ) n3 = n1 << n2

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 ) symmetric divide n1 by n2, giving remainder n3

MOVE

( addr1 addr2 len -- ) move memory

N>R

( x1 ... xn n -- n ) ( R: x1 ... xn -- )

NA+

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

NA1+

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

NEGATE

( n -- n' ) negate n

NIP

( n1 n2 -- n2 )

NOOP

( -- ) Do nothing.

NOSHOWSTACK

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

NOT

( x -- x' ) invert the bits in x

NR>

( R: x1 ... xn -- ) ( n -- x1 ... xn n )

O#

( "#"<> -- n | --) parse following number as octal, compile as literal if compiling

OCTAL

( -- ) store 8 to BASE

OF

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

( c-addr -- ) store all zero bits to cell at c-addr

ON

( c-addr -- ) store all one bits to cell at c-addr

ONLY

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

OR

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

ORDER

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

OVER

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

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 "word" -- c-addr u ) parse word 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"<> -- c-addr u ) alias of PARSE-WORD

PARSE-WORD

( "word"<> -- c-addr u ) parse word from input stream, return address and length

PICK

( x1 ... xn u -- x1 ... xn x(n-u) )

POSTPONE

( "name"<> -- )

PREVIOUS

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

QUIT

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

R+1

( R: n -- n' ) n' = n + 1

R>

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

R@

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

RB!

( byte addr -- ) perform FCode-equivalent RB!: store byte

RB@

( addr -- byte ) perform FCode-equivalent RB@: fetch byte

RDROP

( R: n -- )

RECURSE

( -- ) compile the execution semantics of the most recently-created definition

RECURSIVE

( -- ) make the current definition findable during compilation

REFILL

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

REPEAT

( C: orig dest -- ) (R: -- ) resolve orig and dest, repeat BEGIN loop

RESET-ALL

( -- ) Reset the system.

RESTORE-INPUT

RL!

( cell addr -- ) perform FCode-equivalent RL!, store cell

RL@

( addr -- cell ) perform FCode-equivalent RL@: fetch cell

ROLL

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

ROT

( n1 n2 n3 -- n2 n3 n1 )

RSHIFT

( n1 n2 -- n3 ) n3 = n1 >> n2

RW!

( word addr -- ) perform FCode-equivalent RW!: store word

RW@

( addr -- word ) perform FCode-equivalent RW@: fetch word

S"

( "text"<"> -- c-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-WORDLIST

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

SEE

( "name"<> -- ) 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

C: ( c-addr1 u -- ) R: ( -- c-addr 2 u ) compile string literal into current def

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

( -- a-addr ) STATE variable, zero if interpreting.

STRUCT

( -- 0 )

SWAP

( n1 n2 -- n2 n1 )

THEN

( C: if-sys|else-sys -- ) ( E: -- )

THROW

( n -- ) Throw exception n if n <> 0.

TO

( n "name"<> -- ) change the first cell of the body of xt to n. Can be used on

TRUE

( -- true ) true = all one bits

TUCK

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

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

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/

( n -- n' ) 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 c-addr -- ) write cell n to c-addr

UNALIGNED-L@

( c-addr -- n ) fetch cell from c-addr

UNALIGNED-W!

( word c-addr -- ) write word n to c-addr

UNALIGNED-W@

( c-addr -- n ) fetch word from c-addr

UNLOOP

( -- ) ( R: loop-sys -- ) remove loop parameters from stack

UNTIL

( C: dest -- ) ( R: 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 ALLOT 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 teh body of the named wordlist definition.

W!

( word c-addr -- ) write word n to c-addr

W,

( word -- ) compile word into dictionary

W@

( c-addr -- word ) fetch word from c-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

( C: dest -- orig dest ) ( E: 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 "word" -- c-addr ) parse word 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

( n1 n2 -- n3 ) n3 = n1 ^ n2

[

( -- ) Enter interpretation state.

[']

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

[:

[CHAR]

( "word"<> -- char ) immediately perform CHAR and compile literal

[COMPILE]

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

\

( "..." -- ) discard the rest of the input buffer (line during EVALUATE)

]

( -- ) Enter compilation state.