amforth - Forth pro ATmega

Tato stránka zpřístupňuje křížovou referenci jazyka amforth. Odkazy se generují automaticky na základě zdrojových souborů jazyka amforth.

Verze

Základní informace
Stránka jazyka amforth http://amforth.sourceforge.net/
Stránka pro download http://sourceforge.net/projects/amforth
Subversion server https://amforth.svn.sourceforge.net/svnroot/amforth
Subversion Info
URL https://amforth.svn.sourceforge.net/svnroot/amforth/trunk
Repository Root https://amforth.svn.sourceforge.net/svnroot/amforth
Repository UUID 1be2a6a9-e81f-0410-9be0-e59bd151596a
Last Changed Author mtrute
Last Changed Rev 328
Last Changed Date 2007-06-11 08:42:09 +0200 (Mon, 11 Jun 2007)

Seznam slov

Word Label Definition
! STORE ( n addr -- ) Memory
R( -- )
write 16bit to RAM memory (or IO or CPU registers)
# SHARP ( d1 -- d2) Numeric IO
R( -- )
compiles next digit to HLD
#> SHARP_G ( d1 -- addr count ) Numeric IO
R( -- )
convert HLD buffer to a usable string
#int NUMINT ( -- n ) Interrupt
R( -- )
number of interrupt vectors (0 based)
#s SHARP_S ( d1 -- 0) Numeric IO
R( -- )
call # until a value of zero is reached
#tib NUMBERTIB ( -- addr ) System
R( -- )
address of variable holding the number of characters in TIB
' TICK ( -- XT ) Dictionary
R( -- )
search dictionary, returns XT or throw an exception -13
( LPARENTHESIS ( -- ) Compiler
R( -- )
skip everything up to the closing bracket on the same line
* MUL ( n1 n2 -- n3 ) Arithmetics
R( -- )
multiply routine
*/ STARSLASH (n1 n2 n3 -- n4) Arithmetics
R( -- )
signed multiply and division with double precision intermediate
*/mod STARSLASHMOD ( n1 n2 n3 -- rem quot) Arithmetics
R( -- )
signed multiply and division with double precision intermediate and remainder
+ PLUS ( n1 n2 -- n3) Arithmetics
R( -- )
addition
+! PLUSSTORE ( n addr -- ) Arithmetics
R( -- )
add value to content of RAM address
+loop PLOOP ( addr -- ) Control Structure
R( -- )
compile +loop and resolve branch
, COMMA ( n -- ) Dictionary
R( -- )
compile 16 bit into flash at here.
- MINUS ( n1 n2 -- n3 ) Arithmetics
R( -- )
subtract
. DOT ( n -- ) Numeric IO
R( -- )
prints TOS in free number format
." DOTSTRING ( -- ) Compiler
R( -- )
compiles string into dictionary to be typed at runtime
." DOTSTRING ( -- ) Compiler
R( -- )
compiles string into dictionary to be typed at runtime
.s DOTS ( -- ) Tools
R( -- )
stack dump
.s DOTS ( -- ) Tools
R( -- )
stack dump
/ SLASH ( n1 n2 -- n3) Arithmetics
R( -- )
diviion
/int INTOFF ( -- sreg ) Interrupt
R( -- )
turns off all interrupts and leaves SREG in TOS
/key SLASHKEY ( -- f) Character IO
R( -- )
fetch 'key? vector and execute it if not zero. Leave true if a character can be read, false otherwise
/mod SLASHMOD ( n1 n2 -- rem quot) Arithmetics
R( -- )
signed division n1/n2 with remainder
/string SLASHSTRING ( addr1 u1 n-- addr2 u2 ) String
R( -- )
adjust string from addr1 to addr1+n, reduce length from u1 to u2
0 ZERO ( -- 0 ) Arithmetics
R( -- )
leaves the value 0 on TOS
0< LESSZERO ( n1 -- flag) Compare
R( -- )
compare with zero
0<> NOTEQUALZERO ( n -- flag ) Compare
R( -- )
compare with zero
0= EQUALZERO ( n -- flag ) Compare
R( -- )
compare with 0 (zero)
0> GREATERZERO ( n1 -- flag ) Compare
R( -- )
compare with zero
1+ 1PLUS ( n1 -- n2 ) Arithmetics
R( -- )
optimized increment
1- 1MINUS ( n1 -- n2 ) Arithmetics
R( -- )
optimized decrement (CORE)
1ms 1MS ( -- ) Time
R(--)
busy waits (almost) exactly 1 millisecond
2* 2STAR ( n1 -- n2 ) Arithmetics
R( -- )
arithmetic shift left
2/ 2SLASH ( n1 -- n2 ) Arithmetics
R( -- )
arithmetic shift right
: COLON ( -- ) Compiler
R( -- )
create named entry in the dictionary
:noname COLONNONAME ( -- xt ) Compiler
R( -- )
create unnamed entry in the dictionary
; SEMICOLON ( -- ) Compiler
R( -- )
finish colon defintion, compiles (exit) and returns to interpreter state
< LESS ( n1 n2 -- flasg) Compare
R( -- )
compare two values
<# L_SHARP ( -- ) Numeric IO
R( -- )
emties counted string at address from hld
<> NOTEQUAL ( n1 n2 -- flag) Compare
R( -- )
compare two values
= EQUAL ( n1 n2 -- flag ) Compare
R( -- )
compares two values
> GREATER ( n1 n2 -- flag ) Compare
R( -- )
compares two values (signed)
>< BYTESWAP ( n1 -- n2 ) Arithmetics
R( -- )
swap the bytes of the TOS
>in G_IN ( -- addr ) System
R( -- )
pointer to current read position in TIB
>r TO_R ( n -- ) Stack
R( -- n)
move TOS to TOR
?do QDO ( -- addr ) Control Structure
R( -- )
start do .. [+]loop
?do QDO ( -- addr ) Control Structure
R( -- )
start do .. [+]loop
?dup QDUP ( n1 -- [ n1 n1 ] | 0) Stack
R( -- )
duplicate TOS if non-zero
@ FETCH ( addr -- n ) Memory
R( -- )
read 1 cell from RAM (or IO or CPU register)
Edefer EDEFER ( n <name> -- ) Compiler
R( -- )
creates a defer vector which is kept in eeprom.
Edefer EDEFER ( n <name> -- ) Compiler
R( -- )
creates a defer vector which is kept in eeprom.
Rdefer RDEFER ( n <name> -- ) Compiler
R( -- )
creates a RAM based defer vector
Rdefer RDEFER ( n <name> -- ) Compiler
R( -- )
creates a RAM based defer vector
[ LBRACKET ( -- ) Compiler
R( -- )
put system to interpreter state
['] BRACKETTICK ( -- XT ) Compiler
R( -- )
what does ' in the interpreter mode do in colon definitions
\ BACKSLASH ( -- ) Compiler
R( -- )
everything up to the end of the current line is a comment
] RBRACKET ( -- ) Compiler
R( -- )
turn on compiler
abort ABORT ( n*x -- ) Exceptions
R( n*y -- )
send an exception -1
abort" ABORTSTRING ( n*x -- ) Exceptions
R( n*y -- )
check flag. If true emit some text and throw exception -2
abort" ABORTSTRING ( n*x -- ) Exceptions
R( n*y -- )
check flag. If true emit some text and throw exception -2
abs ABS ( n1 -- u1 ) Arithmetics
R( -- )
get the absolute value
accept ACCEPT ( addr n1 -- n2 ) System
R( -- )
reads a line with with KEY into addr until n2 characters are reveived or cr/lf detected.
again AGAIN ( addr -- ) Control Structure
R( -- )
go back to begin
allot ALLOT ( n -- ) System
R( -- )
allocate memory in RAM
and AND ( n1 n2 -- n3 ) Logic
R( -- )
bitwise and
base BASE ( -- addr ) Numeric IO
R( -- )
base fo numeric IO
baud0 BAUD0 ( -- v) System Value
R( -- )
returns usart0 baudrate
begin BEGIN ( -- addr ) Control Structure
R( -- )
start a control structture
bl BL ( -- 32 ) Character IO
R( -- )
put ascii code of the blank to the stack
c! CSTORE ( c addr -- ) Memory
R( -- )
store a byte to RAM address
c@ CFETCH ( addr - c1 ) Memory
R( -- )
fetch a single byte from RAM (or IO or CPU register)
case CASE ( -- 0 ) Control Structure
R( -- )
case CASE ( -- 0 ) Control Structure
R( -- )
catch CATCH ( xt -- ) Exceptions
R( -- ) or R( ny -- )
execute the XT and restore stack frame if an exception is thrown
char CHAR ( -- c ) Tools
R( -- )
first character of the next word
cmove> CMOVE_G (addr-from addr-to n -- ) Memory
R( -- )
copy data in RAM
cold COLD ( -- ) System
R( -- )
main entry word. executes turnkey operation and executes quit
compile COMPILE ( -- ) Dictionary
R( -- )
copy the next flash cell to HERE
constant CONSTANT ( n -- ) Compiler
R( -- )
create a named constant
count COUNT ( addr -- addr+1 n) String
R( -- )
addr is the address of a counted string in RAM
cr CR ( -- ) Character IO
R( -- )
emits CR/LF
create CREATE ( -- ) Dictionary
R( -- )
create a complete dictionary header.
cscan CSCAN ( addr1 n1 c -- addr1 n2 ) String
R( -- )
Scan string at addr1/n1 until first c, leaving addr1/n2, char at n2 is last non-c character
cskip CSKIP ( addr1 n1 c -- addr2 n2 ) String
R( -- )
skips leading occurancies in string at addr1/n1 leaving addr2/n2 pointing to the 1st non-c character
d+ DPLUS ( d1 d2 -- d3) Arithmetics
R( -- )
add double cell values
d+ DPLUS ( d1 d2 -- d3) Arithmetics
R( -- )
add double cell values
d- DMINUS ( d1 d2 -- d3 ) Arithmetics
R( -- )
subtract double cell values
d- DMINUS ( d1 d2 -- d3 ) Arithmetics
R( -- )
subtract double cell values
d2* D2STAR ( d1 -- d2 ) Arithmetics
R( -- )
shift a double cell left
d2* D2STAR ( d1 -- d2 ) Arithmetics
R( -- )
shift a double cell left
d2/ D2SLASH ( d1 -- d2 ) Arithmetics
R( -- )
shift a double cell value right
d< DLESS ( d1 d2 -- flasg) Compare
R( -- )
compare two values
d> DGREATER ( d1 d2 -- flag ) Compare
R( -- )
compares two values (signed)
d>s D2S ( d1 -- n1 ) Conversion
R( -- )
shrink double cell value to single cell.
decimal DECIMAL ( -- ) Numeric IO
R( -- )
set base to 10 (decimal)
defer! DEFERSTORE ( xt1 xt2 -- ) System
R( -- )
stores xt1 as the xt to be executed when xt2 is called
defer@ DEFERFETCH ( xt1 -- xt2 ) System
R( -- )
returns the XT assoziates with the given XT
depth DEPTH ( -- n ) Stack
R( -- )
currently used data stack size in cells
digit DIGIT ( c base -- number flag ) Numeric IO
R( -- )
convert character to number, set flag if successful
dinvert DINVERT ( d1 -- d2) Arithmetics
R( -- )
flip all bits in the double cell value
dinvert DINVERT ( d1 -- d2) Arithmetics
R( -- )
flip all bits in the double cell value
do DO ( -- addr ) Control Structure
R( -- )
start do .. [+]loop
does> DOES ( -- ) Compiler
R( -- )
dp DP ( -- eaddr) System Pointer
R( -- )
first unused address in flash (NRWW is always used)
drop DROP ( n -- ) Stack
R( -- )
drop TOS
dup DUP ( n -- n n ) Stack
R( -- )
duplicate TOS
e! ESTORE ( n addr -- ) Memory
R( -- )
write to eeprom address
e@ EFETCH ( addr - n) Memory
R( -- )
read 2 bytes from eeprom
edp EDP ( -- eaddr) System Pointer
R( -- )
first unused address in eeprom
else ELSE ( addr1 -- addr2) Compiler
R( -- )
emit EMIT ( -- eaddr) Character IO
R( -- )
fetch the emit vector and execute it
emit? EMITQ ( -- c) Character IO
R( -- )
fetch emit? vector and execute it
endcase ENDCASE ( f -- ) Compiler
R( -- )
endcase ENDCASE ( f -- ) Compiler
R( -- )
endof ENDOF ( addr1 -- addr2 ) Compiler
R( -- )
endof ENDOF ( addr1 -- addr2 ) Compiler
R( -- )
execute EXECUTE ( xt -- ) System
R( -- )
execute XT
exit EXIT ( -- ) Compiler
R( xt -- )
end of current colon word
f_cpu F_CPU ( -- f_cou ) System
R( -- )
put the cpu frequency on stack
find FIND ( addr -- -- [ addr 0 ] | [ xt [-1|1]] ) Tools
R( -- )
search dictionary
handler HANDLER ( -- addr ) Exceptions
R( -- )
used by catch/throw
heap HEAP ( -- eaddr) System Pointer
R( -- )
address of first unallocated RAM
here HERE ( -- addr ) System Pointer
R( -- )
hex HEX ( -- ) Numeric IO
R( -- )
set base to 16 (decimal)
hld HLD ( -- addr ) Numeric IO
R( -- )
address of buffer for pictured numeric output
hold HOLD ( c -- ) Numeric IO
R( -- )
prepend character to pictured numeric output buffer
i I ( -- n ) Control Structure
R( loop-sys -- loop-sys)
current loop counter
i! ISTORE ( n addr -- ) Memory
R( -- )
writes a cell in flash
i@ IFETCH ( addr -- n1 ) Memory
R( -- )
reads a cell from flash, addr is cell address, not byte addres first byte gets into the lower word on tos
icount ICOUNT ( adr -- adr n ) Tools
R( -- )
get count byte out of packed counted string in flash
idump IDUMP ( addr len -- ) Tools
R( -- )
dumps flash memory beginning with address addr and len cells long
idump IDUMP ( addr len -- ) Tools
R( -- )
dumps flash memory beginning with address addr and len cells long
if IF ( -- addr ) Control Structure
R( -- )
start conditional branch
immediate IMMEDIATE ( -- ) Compiler
R( -- )
set immediate flag
int INTON ( -- ) Interrupt
R( -- )
turns on all interrupts
int! INTSTORE ( xt i -- ) Interrupt
R( -- )
stores XT as interrupt vector i
int@ INTFETCH ( i -- xt ) Interrupt
R( -- )
fetches XT from interrupt vector i
interpret INTERPRET ( -- ) System
R(i*x - j*x )
interpret input word by word. may throw exceptions
invert INVERT ( n1 -- n2) Arithmetics
R( -- )
1-complement of TOS
is IS ( xt1 c<char> -- ) System
R( --)
stores xt into defer or compiles code to do so at runtime
is IS ( xt1 c<char> -- ) System
R( --)
stores xt into defer or compiles code to do so at runtime
itype ITYPE ( addr n -- ) Tools
R( -- )
reads packed string from flash and emit it
j J ( -- n ) Control Structure
R( loop-sys1 loop-sys2 -- loop-sys1 loop-sys2)
loop counter of outer loop
key KEY ( -- c ) Character IO
R( -- )
fetch key vector and execute it
key? KEYQ ( -- f) Character IO
R( -- )
fetch 'key? vector and execute it. Leave true if a character can be read, false otherwise
leave LEAVE ( -- )
R(next limit counter -- next )
runtime of leave
leave LEAVE ( -- )
R(next limit counter -- next )
runtime of leave
literal LITERAL ( n -- ) Compiler
R( -- )
compile a literal in colon defintions
log2 LOG2 ( n1 -- n2 ) Arithmetics
R( -- )
logarithm base 2 or highest set bitnumber
loop LOOP ( addr -- ) Control Structure
R( -- )
cpmpile (loop) and resolve branch
lshift LSHIFT ( n1 n2 -- n3) Arithmetics
R( -- )
logical shift left
m* MSTAR ( n1 n2 -- d) Arithmetics
R( -- )
multiply 2 cells to a double cell
max MAX ( n1 n2 -- n1|n2 ) Compare
R( -- )
compare two values, leave the bigger one
min MIN ( n1 n2 -- n1|n2 ) Compare
R( -- )
compare two values leave the smaller one
mod MOD ( n1 n2 -- n3) Arithmetics
R( -- )
remainder of division
negate NEGATE ( n1 -- n2 ) Logic
R( -- )
2-complement
noop NOOP ( -- ) Tools
R( -- )
do nothing
not NOT ( flag -- flag' ) Logic
R( -- )
identical to 0=
number NUMBER (addr -- n ) Numeric IO
R( -- )
convert a word to a number, throw exception -1 on error
of OF ( -- ) Compiler
R( -- )
see case
of OF ( -- ) Compiler
R( -- )
see case
or OR ( n1 n2 -- n3 ) Logic
R( -- )
logical or
over OVER ( n1 n2 -- n1 n2 n1 ) Stack
R( -- )
stack manipulation
pad PAD ( -- addr ) System Pointer
R( -- )
scratch buffer.
parse PARSE ( char "ccc" -- c-addr u ) String
R( -- )
in input buffer parse ccc delimited string by the delimiter char.
pause PAUSE ( -- ) Multitasking
R( -- )
fetch pause vector and execute it. may make a context/task switch
quit QUIT ( -- ) System
R( -- )
main loop of amforth. accept - interpret in an endless loop
r> R_FROM ( -- n ) Stack
R( n --)
move TOR to TOS
r@ R_FETCH ( -- n) Stack
R( n -- n )
fetch content of TOR
recurse RECURSE ( -- ) Compiler
R( -- )
compile XT of the word beeing currently defined into dictionary (! not conforming to ANS!)
refill REFILL ( -- f ) IO
R( -- )
refills the input buffer
repeat REPEAT (addr1 -- addr2 ) Control Structure
R( -- )
go back to begin
rot ROT ( n1 n2 n3 -- n2 n3 n1) Stack
R( -- )
stack manupulation
rp RP ( -- addr) Stackpointer
R( -- )
address of variable to store the return stack pointer for inactive tasks
rp! RP_STORE ( n -- ) Stackpointer
R( -- xy)
set return stack pointer
rp0 RP0 ( -- addr) Stackpointer
R( -- )
start value of return stack
rp@ RP_FETCH ( -- n) Stackpointer
R( -- )
current return stack pointer address
rshift RSHIFT ( n1 n2 -- n3 ) Arithmetics
R( -- )
logical shift right
rx0 RX0 ( -- c) Hardware Access
R( --)
get 1 character from input queue, wait if needed
rx0? RX0Q ( -- f) Hardware Access
R( --)
check if unread characters are in the input queue.
s" SQUOTE ( <cchar> -- ) Compiler
R( -- )
compiles a string to flash, at runtime leaves ( -- addr count) on stack
s" SQUOTE ( <cchar> -- ) Compiler
R( -- )
compiles a string to flash, at runtime leaves ( -- addr count) on stack
s, SCOMMA ( addr len -- ) Compiler
R( -- )
compiles a string from RAM to Flash
s>d S2D ( n1 -- d1 ) Conversion
R( -- )
extend (signed) single cell value to double cell
sign SIGN ( n -- ) Numeric IO
R( -- )
place a - in HLD if value is negative
sleep SLEEP ( -- ) Interrupt
R( -- )
calls the MCU sleep instruction. Not useful itself!
source SOURCE ( addr1 u1 n-- addr2 u2 ) System
R( -- )
adjust string from addr1 to addr1+n, reduce length from u1 to u2
sp SP ( -- addr) Stackpointer
R( -- )
address of variable to store data stack pointer for inactive tasks
sp! SP_STORE ( addr -- i*x) Stackpointer
R( -- )
data stack pointer changed to addr
sp0 SP0 ( -- addr) Stackpointer
R( -- )
start of data stack
sp@ SP_FETCH ( -- n) Stackpointer
R( -- )
current data stack pointer
space SPACE ( -- ) Character IO
R( -- )
emits a space (bl)
state STATE ( -- addr ) Compiler
R( -- )
system state
swap SWAP ( n1 n2 -- n2 n1) Stack
R( -- )
stack manipulation
then THEN ( addr -- ) Compiler
R( -- )
finish if
throw THROW ( n -- ) Exceptions
R( -- )
throw an exception
tib TIB ( -- addr ) System Pointer
R( -- )
terminal input buffer address
to TO ( n <name> -- ) Tools
R( --)
store the TOS to value (an EEPROM 16bit cell)
turnkey TURNKEY ( -- eaddr) System Pointer
R( -- )
address of the variable that holds an XT to be started by cold before quit takes over
tx0 TX0 (c -- ) Hardware Access
R( --)
put 1 character into output queue, wait if needed, enable UDRIE0 interrupt
tx0? TX0Q ( -- f) Hardware Access
R( --)
check if a character can be appended to output queue.
type TYPE ( addr n -- ) Character IO
R( -- )
emits a string
u*/mod USTARSLASHMOD ( u1 u2 u3 -- rem quot) Arithmetics
R( -- )
unsigned division with remainder u3 * u2 / u1
u. UDOT ( n -- ) Numeric IO
R( -- )
unsigned numeric output
u. UDOT ( n -- ) Numeric IO
R( -- )
unsigned numeric output
u/mod USLASHMOD (u1 u2 -- rem quot) Arithmetics
R( -- )
unsigned division with remainder
u< ULESS ( u1 u2 -- flasg) Compare
R( -- )
compare values u1 < u2 (unsigned)
u> UGREATER ( u1 u2 -- flag ) Compare
R( -- )
compares u1 > u2 (unsigned)
um/mod UMSLASHMOD ( ud u2 -- rem quot) Arithmetics
R( -- )
unsigned division ud / u2 with remainder
unloop UNLOOP ( -- ) Control Structure
R(loop-sys -- )
remove loop-sys
until UNTIL ( addr -- ) Compiler
R( -- )
finish begin with conditional branch
unused UNUSED ( -- n ) Tools
R( -- )
number of unused flash cells
up! UP_STORE ( addr -- ) System
R( -- )
set user pointer
up@ UP_FETCH ( -- addr ) System
R( -- )
get user pointer
usart0 USART0 ( -- ) Hardware Access
R( --)
initialize usart0
user USER ( n -- ) Compiler
R( -- )
define a new user variable
value VALUE ( n <name> -- ) Compiler
R( -- )
allocate space for 1 cell in EEPROM. used in conjunction with TO
variable VARIABLE ( -- ) Compiler
R( -- )
create a variable entry and allocate RAM space for it
ver VER ( -- ) Tools
R( -- )
emits the version string
wdr WDR ( -- ) Interrupt
R( -- )
calls the MCU wdr instruction
while WHILE ( dest -- orig dest ) Control Structure
R( -- )
control structure
word WORD ( c -- addr ) Tools
R( -- )
skip leading delimiter characters and parses TIB to the next delimiter. copy the word into PAD
words WORDS ( -- ) Tools
R( -- )
emits a list of all (visible) words in the dictionary
words WORDS ( -- ) Tools
R( -- )
emits a list of all (visible) words in the dictionary
xor XOR ( n1 n2 -- n3) Logic
R( -- )
exclusive or