added option to temporarily disable sinopt (because optimising urasm expressions...
[urasm.git] / dox / urforth.txt
blob70942796b8f1dac00a830231a7498f0b2ee5c599
1 proper documentation will follow... maybe.
2 but please, read this document if you want to use UrForth.
3 UrForth is not a standard Forth system (it is a mixture of ANS, FIG,
4 and my own creations), and this document contains valuable bits of
5 knowledge about some non-standard UrForth features.
7 one of the non-standard UrForth features is locals support. it is
8 done like this:
9   : myword  ( a b -- c )
10     args: a b
11     locals: loc1 loc2
13     :a TO :loc1
14     :b TO :loc2
15     :loc1 :loc2 +
16   ;
17 here, "args:" will declare local variables, and automatically fill them
18 with arguments from the data stack. "locals:" declare "free" locals.
19 there can be more than one "locals:" section, but all such sections should
20 come before anything else. to use local, you must prepend its name with a
21 colon. the usual "TO" word is used to set local values.
23 "DOES>" works only on CREATEd words.
25 note that "/MOD" and other such words are the exact opposites of what the
26 standard says. "/MOD" return stack is "( quot rem )". i.e. the remainder is
27 always on top. in 83/ANS standards TOS is the quotient.
29 "ERROR" word accepts address and counter, and is fatal error (it cannot be
30 CATCHed). there are "?ERROR" and "?NOT-ERROR" words to check error coditions
31 too.
33 "VARIABLE" expects initial value on the stack (like in FIG-Forth). but
34 "DEFER" doesn't, and initialises new defered words with "NOOP" by default.
36 note that "LITERAL" is not immediate. use "IMM-LITERAL" if you need immediate
37 version. the same is for "STRLITERAL" -- there is "IMM-STRLITERAL".
39 there is no "POSTPONE" word. i was never able to understand what the fuck it
40 does. so "[COMPILE]" simply compiles the next word CFA to the current word,
41 regardless of its "immediate" flag. and "COMPILE" makes the current compiling
42 word compile next word on execution.
44 always use "COMPILE," to compile CFAs to the current word. this guarantees
45 that your code will survive internal VM changes (mostly). also, look into
46 "20-base-creatori.f" and "30-ifthen.f" to learn how to compile branches.
47 there are special words to put branch destinations, and if you will use
48 them instead of direct "!" or ",", your code will have a better chance to
49 work if i'll change "BRANCH" to be relative, for example.
52 there is "CASE" thing there. in addition to normal "OF", it has several more:
53   "NOT-OF", "<OF", "<=OF", ">OF", ">=OF", "U<OF", "U<=OF",
54   "U>OF", "U>=OF", "&OF", "AND-OF", "~AND-OF", "WITHIN-OF",
55   "UWITHIN-OF", "BOUNDS-OF"
57 there is also special "?OF", which takes the prepared boolean. basically, other
58 "OF"s could be written like this:
59   "OF" -> "DUP <number> = ?OF" (note "DUP" here)
61 and there are two Very Special forms: "IF-OF" and "IFNOT-OF". they are useful
62 to build several conditional checks in a row without endless "endif" sequence
63 at the end. the difference is that "IF-OF" doesn't do "DROP" on success. but
64 note that if you will not use "OTHERWISE", "ENDCASE" will compile "DROP" anyway.
66 ah, yes. there is optional "OTHERWISE" clause. it simply forbids dropping TOS
67 in "ENDCASE" (and doesn't drop anything itself). i.e. you can use it if none
68 of the cases were hit, and check the result in any way you want. it is basically
69 the same as "TRUE IF-OF".
72 when you creating words that compile some code, please, use compiler words
73 instead of "," and such. otherwise the peephole optimiser may screw everything.
75 to compile literal:
76   literal
78 to compile word:
79   compile smth
81 to compile word with code arguments:
82   ['] word compile-start, arg compile-arg, arg compile-end,
83   ['] word compile-start, arg compile-end,
85 note that "compile," doesn't expect code args! do not use it to compile
86 non-words, use "compile-imm," instead (this will not call the optimiser).
89 some global variables are state-local. also, each state has its own TIB,
90 independent of other states.
92 state-local vars are:
93 BASE
94 ( -- base-addr )
95 current number base.
97 TIB
98 ( -- addr )
99 current TIB.
102 ( -- ofs )
103 offset in current TIB.
106 ( -- pad )
107 return PAD address. this memory area can be used for storing temporary
108 values (like strings). you can assume to have at least 4096 bytes there.
109 WARNING! some words may use PAD for their own needs. this is mostly
110          words which does some string manipulation, like building strings
111          from parts, and such. note that number conversion buffer is
112          independent of PAD.
114 (STD-TIB-ADDR)
115 ( -- )
116 default TIB address. WARNING! if this user var contains a handle, that
117 handle will be freed on destroying the task. if you want to replace the
118 default TIB, make sure that you will free the old handle (if it is a handle).
120 STATE
121 ( -- addr )
122 current system state. `0` for interpretation, any other value for compilation.
124 CONTEXT
125 ( -- addr )
126 context vocabulary, i.e. vocabulary that will be used to look for words. note
127 that there is a stack of vocabularies there (see "ALSO" and other words), and
128 all of them will be searched after context one.
130 CURRENT
131 ( -- addr )
132 this is vocabulary that will be used to record new words. it is only checked
133 for duplicate word definitions, but otherwise is not participating in word
134 searching mechanics.
136 (SELF)
137 ( -- addr )
138 this is used in OOF. it holds address of the active class instance (object).
140 (USER-INTERPRET-NEXT-LINE)
141 ( -- addr )
142 this holds the address of a word which will be called by INTERPRET when it
143 hits EOL, and needs to read a new line to interpret (or compile).
145 (EXC-FRAME-PTR)
146 ( -- addr )
147 this is used in THROW/CATCH implementation, and holds current exception frame
148 address.
150 (USER-VAR-USED)
151 ( -- uvar-used-addr )
152 address of the variable contains first free user area address.
154 (USER-VAR-ADDR)
155 ( -- uvar-begin-addr )
156 start address of the user area.
158 (USER-VAR-SIZE)
159 ( -- uvar-size )
160 maximum user area size in bytes.
164 DEBUG:DUMP-STACK
165 ( -- )
166 dump data stack
168 DEBUG:BACKTRACE
169 ( -- )
170 show current backtrace (slow!)
172 DEBUG:DECOMPILE name
173 ( -- )
174 decompile given forth word.
176 SP0!
177 ( -- )
178 clear data stack.
180 RP0!
181 ( -- )
182 clear return stack.
184 note that address for memory operations may be a handle too. with handles,
185 low bits are used as offset, so you can directly address some bytes in handle
186 data area. currently, low 12 bits are reserved for offset, so you can address
187 4096 bytes inside a handle. but don't hardcode it, use "FORTH:(MAX-HANDLE-OFS)"
188 constant to get the maximum allowed offset (because it may change in the future).
190 also, UrForth is 32-bit system, and stores all numbers as little-endian. this
191 will not change, so you can write your code without checking cell size, or
192 byte order.
196 ( addr -- value8 )
197 load 8-bit value.
200 ( addr -- value16 )
201 load 16-bit value.
204 ( addr -- value32 )
205 load 32-bit value.
208 ( val8 addr -- )
209 store 8-bit value.
212 ( val16 addr -- )
213 store 16-bit value.
216 ( val32 addr -- )
217 store 32-bit value.
219 C!+1>A
220 ( byte -- )
221 store byte via A, advance A by 1.
223 W!+2>A
224 ( word -- )
225 store word via A, advance A by 2.
227 !+4>A
228 ( value -- )
229 store cell via A, advance A by 4.
231 C@+1>A
232 ( -- byte )
233 load byte via A, advance A by 1.
235 W@+2>A
236 ( -- word )
237 load word via A, advance A by 2.
239 @+4>A
240 ( -- value )
241 load cell via A, advance A by 4.
243 (DIRECT:@)
244 ( -- val32 )
245 address is code argument.
247 (DIRECT:0:!)
248 ( -- )
249 address is code argument.
251 (DIRECT:1:!)
252 ( -- )
253 address is code argument.
255 (DIRECT:-1:!)
256 ( -- )
257 address is code argument.
259 (DIRECT:!)
260 ( val32 -- )
261 address is code argument.
263 (DIRECT:+!)
264 ( val32 -- )
265 address is code argument.
267 (DIRECT:-!)
268 ( val32 -- )
269 address is code argument.
271 (DIRECT:+:@)
272 ( addr -- val32 )
273 addr offset is code argument. this is used for struct access.
275 (DIRECT:+:!)
276 ( val32 addr -- )
277 addr offset is code argument. this is used for struct access.
279 ~AND
280 ( a b -- a&~b )
282 SWAP!
283 ( addr value -- )
285 SWAP-C!
286 ( addr value -- )
288 SWAP-W!
289 ( addr value -- )
292 ( value addr -- )
294 OR-C!
295 ( value addr -- )
297 OR-W!
298 ( value addr -- )
300 ~AND!
301 ( value addr -- )
303 ~AND-C!
304 ( value addr -- )
306 ~AND-W!
307 ( value addr -- )
309 XOR!
310 ( value addr -- )
312 XOR-C!
313 ( value addr -- )
315 XOR-W!
316 ( value addr -- )
319 ( val8 -- )
320 compile 8-bit value.
323 ( val16 -- )
324 compile 16-bit value.
327 ( val -- )
328 compile 32-bit value.
331 (LIT)
332 ( -- n )
333 read 4 bytes immediately following this word, and push them
334 to the data stack. adjust IP to skip those bytes.
336 (LITCFA)
337 ( -- n )
338 read 4 bytes immediately following this word, and push them
339 to the data stack. adjust IP to skip those bytes. this is
340 the same as "(LIT)", but used to store CFAs of words. using
341 different words for different data types helps the debugger
342 and the decompiler.
344 (LITVOCID)
345 ( -- n )
346 the same as "(LIT)", but for vocids.
348 (LITSTR8)
349 ( -- addr count )
350 inline byte-counted string literal. note that the string
351 always have a trailing zero byte (which is not counted),
352 and always padded so it ends on a 4-byte boundary.
354 (BRANCH) ( -- )
355 read next 4 bytes, and set IP to that address.
357 (TBRANCH)
358 ( flag -- )
359 skip next 4 bytes if `flag` is 0, otherwise perform "(BRANCH)".
361 (0BRANCH)
362 ( flag -- )
363 skip next 4 bytes if `flag` is not 0, otherwise perform "(BRANCH)".
365 (+0BRANCH)
366 ( num -- )
367 skip next 4 bytes if `num` is positive or 0, otherwise perform "(BRANCH)".
369 (+BRANCH)
370 ( num -- )
371 skip next 4 bytes if `num` is positive (but not 0), otherwise perform "(BRANCH)".
373 (-BRANCH)
374 ( num -- )
375 skip next 4 bytes if `num` is negative, otherwise perform "(BRANCH)".
377 (OR-BRANCH)
378 ( !0 -- !0 ) -- jmp
379 ( 0 -- ) -- no jmp
380 useful for short-circuit logic, "OR" case. if TOS is not zero, do not
381 touch the stack, and perform the jump. if TOS is zero, drop zero, and
382 do not jump.
384 (AND-BRANCH)
385 ( 0 -- 0 ) -- jmp
386 ( !0 -- ) -- no jmp
387 useful for short-circuit logic, "AND" case. if TOS is zero, do not touch
388 the stack, and perform the jump. if TOS is not zero, drop zero, and do not
389 jump.
391 (?DUP-0BRANCH)
392 ( 0 -- ) -- jmp
393 ( !0 -- !0 ) -- no jmp
394 can be used to optimise "?DUP IF".
396 (CASE-BRANCH)
397 ( 0 -- ) -- jmp
398 ( n !0 -- ) -- no jmp
399 useful to implement "CASE". if TOS is zero, drop TOS and perform the jump.
400 if TOS is non-zero, drop TOS and one more value ("CASE" value), do not jump.
402 (DATASKIP)
403 ( -- )
404 read next 4 bytes, advance IP. then increment IP by the read number.
405 this is used to tell the decompiler that it should skip some inline
406 data instead of trying to decompile it.
408 EXECUTE
409 ( cfa )
410 pop word CFA address, and execute it.
412 EXECUTE-TAIL
413 ( cfa )
414 pop word CFA address, and execute it. returning from the executed
415 word will return to the upper word. i.e. this performs a tail call.
417 (FORTH-CALL)
418 ( pfa )
419 call forth code. it should end with "FORTH:(EXIT)".
421 (FORTH-TAIL-CALL)
422 ( pfa )
423 tail-calls forth code. it should end with "FORTH:(EXIT)".
425 (EXIT)
426 internal compiler word, placed at the end of colon definition.
427 pops a number from return stack, and sets IP to that number.
429 (L-ENTER)
430 this word is used to implement local variables and arguments.
431 it doesn't matter how it works, you should not used it anyway.
432 read the source code, if you're curious.
434 (L-LEAVE)
435 this word is used to implement local variables and arguments.
436 it doesn't matter how it works, you should not used it anyway.
437 read the source code, if you're curious.
439 (LOCAL@)
440 ( idx -- value )
441 read local variable with the given index. indices are 1-based.
443 (LOCAL!)
444 ( value idx -- )
445 write local variable with the given index. indices are 1-based.
448 ( n -- n n )
449 duplicates a number on the data stack.
451 ?DUP
452 ( n -- n n ) | ( 0 -- 0 )
453 duplicates a number on the data stack, but only if that number is not 0.
455 2DUP
456 ( n0 n1 -- n0 n1 n0 n1 )
458 DROP
459 ( n -- )
461 2DROP
462 ( n0 n1 -- )
464 SWAP
465 ( n0 n1 -- n1 n0 )
467 2SWAP
468 ( n0 n1 -- n1 n0 )
470 OVER
471 ( n0 n1 -- n0 n1 n0 )
473 2OVER
474 ( n0 n1 -- n0 n1 n0 )
477 ( n0 n1 n2 -- n1 n2 n0 )
479 NROT
480 ( n0 n1 n2 -- n2 n0 n1 )
483 ( a b -- b )
485 TUCK
486 ( a b -- b a b )
488 RDUP
489 ( n -- n n )
490 the same as "DUP", but for the return stack.
492 RDROP
493 ( n -- )
494 the same as "DROP", but for the return stack.
496 RSWAP
497 ( n0 n1 -- n1 n0 )
498 the same as "SWAP", but for the return stack.
500 ROVER
501 ( n0 n1 -- n0 n1 n0 )
502 the same as "OVER", but for the return stack.
504 RROT
505 ( n0 n1 n2 -- n1 n2 n0 )
506 the same as "ROT", but for the return stack.
508 RNROT
509 ( n0 n1 n2 -- n2 n0 n1 )
510 the same as "NROT", but for the return stack.
513 ( n -- | n )
514 move number from the data stack to the return stack.
517 ( | n -- n )
518 move number from the return stack to the data stack.
521 ( | n -- n | n )
522 copy number from the return stack to the data stack.
524 PICK
525 ( idx -- n )
526 copy n-th element at the data stack. "0 PICK" is the same as "DUP".
528 RPICK
529 ( idx -- n )
530 the same as "PICK", but for the return stack.
532 ROLL
533 ( idx -- n )
534 move n-th element at the data stack to the top. "1 ROLL" is the same as "SWAP".
536 RROLL
537 ( idx -- n )
538 the same as "ROLL", but for the return stack.
540 REFILL
541 ( -- eofflag )
542 read next input line. can cross include boundaries. pushes 0 if
543 there are no more input lines. TIB contents is undefined in this case.
545 REFILL-NOCROSS
546 ( -- eofflag )
547 read next input line. cannot cross include boundaries. pushes 0 if
548 there are no more input lines. TIB contents is undefined in this case.
550 (TIB-IN)
551 ( -- addr )
552 get address of the current TIB position.
553 WARNING! do not try to emulate "TIB-GETCH" and such with this word!
554          TIB usually ends with 0 byte, and if you will advance beyond
555          that 0, Bad Things will happen.
557 TIB-PEEKCH
558 ( -- char )
559 push current TIB char, do not advance >IN.
561 TIB-PEEKCH-OFS
562 ( ofs -- char )
563 peek TIB char with the given offset. "0 TIB-PEEKCH-OFS" is the same as "TIB-PEEKCH".
565 TIB-GETCH
566 ( -- char )
567 push current TIB char, advance >IN. it is safe to call this even
568 when you reached the end of TIB. in this case, returned char code
569 will be 0. i.e. "0" means "end of TIB".
571 TIB-SKIPCH
572 ( -- )
573 skip current TIB char. it is safe to call this even when you reached
574 the end of TIB.
577 (PARSE)
578 ( delim skip-leading-delim? -- addr count TRUE / FALSE )
579 does base TIB parsing; never copies anything.
580 as our reader is line-based, returns FALSE on EOL.
581 EOL is detected after skipping leading delimiters.
582 passing -1 as delimiter skips the whole line, and always returns FALSE.
583 finishing delimiter is always skipped.
585 PARSE-SKIP-BLANKS
586 ( -- )
587 skip all chars with codes <=32.
589 (PARSE-SKIP-COMMENTS)
590 ( allow-multiline? -- )
591 skip all blanks and comments. if multiline skip is not allowed, reaching
592 end of TIB while still waiting for the comment terminator is error.
593 single-line comments are ok, though.
595 PARSE-SKIP-LINE
596 ( -- )
597 advance >IN to the end of TIB.
599 PARSE-NAME
600 ( -- addr count )
601 parse with leading blanks skipping. doesn't copy anything.
602 return empty string on EOL.
604 PARSE
605 ( delim -- addr count TRUE / FALSE )
606 parse without skipping delimiters; never copies anything.
607 as our reader is line-based, returns FALSE on EOL.
608 passing 0 as delimiter skips the whole line, and always returns FALSE.
609 finishing delimiter is always skipped.
611 EMIT
612 ( n -- )
613 print char.
615 XEMIT
616 ( n -- )
617 "safe" char printer. all non-printable chars (including newline and such)
618 will be printed as "?".
620 LASTCR?
621 ( -- bool )
622 was last printed char a newline?
624 LASTCR!
625 ( bool -- )
626 force-set the flag for "LASTCR?" word.
629 ( -- )
630 print newline.
632 SPACE
633 ( -- )
634 print space.
636 SPACES
637 ( n -- )
638 print `n` spaces. if `n` is negative, prints nothing.
640 ENDCR
641 ( -- )
642 prints newline if the last printed char was not a newline.
644 TYPE
645 ( addr count -- )
646 print the string. negative count is ok, in this case the word prints nothing.
648 XTYPE
649 ( addr count -- )
650 the same as "TYPE", but uses "XEMIT".
652 FLUSH-EMIT
653 ( -- )
654 output can be buffered. it usually flushed when newline is printed, but
655 you can flush it manually using this word.
658 ( a b -- a+b )
661 ( a b -- a-b )
664 ( a b -- a*b )
667 ( a b -- a*b )
670 ( a b -- a/b )
673 ( a b -- a/b )
676 ( a b -- a%b )
678 UMOD
679 ( a b -- a%b )
681 /MOD
682 ( a b -- a/b, a%b )
683 note that the results are swaped, contrary to ANS idiocity.
684 i don't fuckin' know why ANS morons decided to make the stack
685 effect that contradicts the word name. "/MOD" clearly indicates
686 that quotient comes first.
688 U/MOD
689 ( a b -- a/b, a%b )
690 note that the results are swaped, contrary to ANS idiocity.
691 i don't fuckin' know why ANS morons decided to make the stack
692 effect that contradicts the word name. "/MOD" clearly indicates
693 that quotient comes first.
696 ( a b c -- a*b/c )
697 this uses 64-bit intermediate value.
700 ( a b c -- a*b/c )
701 this uses 64-bit intermediate value.
703 */MOD
704 ( a b c -- a*b/c a*b%c )
705 this uses 64-bit intermediate value.
706 note that the results are swaped, contrary to ANS idiocity.
707 i don't fuckin' know why ANS morons decided to make the stack
708 effect that contradicts the word name. "/MOD" clearly indicates
709 that quotient comes first.
712 ( a b c -- a*b/c )
713 this uses 64-bit intermediate value.
716 ( a b -- lo(a*b) hi(a*b) )
717 this leaves 64-bit result.
720 ( a b -- lo(a*b) hi(a*b) )
721 this leaves 64-bit result.
723 M/MOD
724 ( alo ahi b -- a/b a%b )
725 note that the results are swaped, contrary to ANS idiocity.
726 i don't fuckin' know why ANS morons decided to make the stack
727 effect that contradicts the word name. "/MOD" clearly indicates
728 that quotient comes first.
730 UM/MOD
731 ( alo ahi b -- a/b a%b )
732 note that the results are swaped, contrary to ANS idiocity.
733 i don't fuckin' know why ANS morons decided to make the stack
734 effect that contradicts the word name. "/MOD" clearly indicates
735 that quotient comes first.
738 ( a b -- a<b )
741 ( a b -- a<b )
744 ( a b -- a>b )
747 ( a b -- a>b )
750 ( a b -- a<=b )
753 ( a b -- a<=b )
756 ( a b -- a>=b )
759 ( a b -- a>=b )
762 ( a b -- a=b )
765 ( a b -- a<>b )
768 ( a -- !a )
770 LAND
771 ( a b -- a&&b )
772 logical "and".
775 ( a b -- a||b )
776 logical "or".
779 ( a b -- a&b )
780 bitwise "and".
783 ( a b -- a|b )
784 bitwise "or".
787 ( a b -- a^b )
788 bitwise "xor".
790 BITNOT
791 ( a -- ~a )
794 ( u -- u<<1 )
797 ( u -- u<<2 )
800 ( u -- u<<3 )
803 ( n -- n>>1 )
806 ( n -- n>>2 )
809 ( n -- n>>3 )
812 ( u -- u>>1 )
815 ( u -- u>>2 )
818 ( u -- u>>3 )
821 ( n count -- )
822 arithmetic shift; positive `n` shifts to the left.
825 ( n count -- )
826 logical shift; positive `n` shifts to the left.
828 COMPILER:(UNESCAPE)
829 ( addr count -- addr new-count )
830 process string escapes. modifies string in-place. the resulting string is
831 never bigger than the source one. negative counts are allowed.
833 (BASED-NUMBER)
834 ( addr count allowsign? base -- num TRUE / FALSE )
835 tries to convert the given string to the number, using the given
836 default base. if "allowsign?" is non-zero, properly process leading
837 number sign. this words understands numbers in non-default bases too
838 (like "0x29a", for example).
842 switch to interpretation mode.
845 switch to compilation mode.
847 (CREATE-WORD-HEADER)
848 ( addr count word-flags -- )
849 create word header in the dictionary, link word to the current vocabulary.
850 doesn't create CFA.
852 (CREATE-NAMELESS-WORD-HEADER)
853 ( word-flags -- )
854 create nameless word header in the dictionary, link word to the current vocabulary.
855 doesn't create CFA.
857 COMPILER:CFA,  ( cfa -- )
858 create CFA field.
860 FIND-WORD
861 ( addr count -- cfa TRUE / FALSE)
862 general word finder. checks wordlist stack, performs colon resolution.
864 (FIND-WORD-IN-VOC)
865 ( addr count vocid allowhidden? -- cfa TRUE / FALSE)
866 find word in the given wordlist. does no name resolution, and
867 doesn't look in parent wordlists.
869 FIND-WORD-IN-VOC
870 ( addr count vocid -- cfa TRUE / FALSE)
871 find word in the given wordlist. does no name resolution, and
872 doesn't look in parent wordlists. skips hidden words.
874 (FIND-WORD-IN-VOC-AND-PARENTS)
875 ( addr count vocid allowhidden? -- cfa TRUE / FALSE)
876 find word in the given wordlist. does no name resolution, but searches
877 parent wordlists if "vocid" is nested.
879 FIND-WORD-IN-VOC-AND-PARENTS
880 ( addr count vocid -- cfa TRUE / FALSE)
881 find word in the given wordlist. does no name resolution, but searches
882 parent wordlists if "vocid" is nested. skips hidden words.
884 COMPILER:?EXEC
885 check if we are in interpretation mode, and throws an error if we aren't.
887 COMPILER:?COMP
888 check if we are in compilation mode, and throws an error if we aren't.
891 string literal.
893 (VSP@)
894 ( -- vsp )
895 this word is used internally to work with wordlist stack.
897 (VSP!)
898 ( vsp -- )
899 this word is used internally to work with wordlist stack.
901 (VSP-AT@)
902 ( idx -- value )
903 this word is used internally to work with wordlist stack.
905 (VSP-AT!)
906 ( value idx -- )
907 this word is used internally to work with wordlist stack.
909 CFA->PFA
910 ( cfa -- pfa )
912 PFA->CFA
913 ( pfa -- cfa )
915 CFA->NFA
916 ( cfa -- nfa )
918 NFA->CFA
919 ( nfa -- cfa )
921 CFA->LFA
922 ( cfa -- lfa )
924 LFA->CFA
925 ( lfa -- cfa )
927 LFA->PFA
928 ( lfa -- pfa )
930 LFA->BFA
931 ( lfa -- bfa )
933 LFA->SFA
934 ( lfa -- sfa )
936 LFA->NFA
937 ( lfa -- nfa )
939 NFA->LFA
940 ( nfa -- lfa )
942 CFA->WEND
943 ( cfa -- wend-addr )
944 convert CFA to word end address.
946 DEBUG:IP->NFA
947 ( ip -- nfa / 0 )
948 convert instruction pointer to NFA. return 0 if cannot.
950 DEBUG:IP->FILE/LINE
951 ( ip -- addr count line TRUE / FALSE )
952 name is at PAD; it is safe to use PAD, because each task has its
953 own temp image.
955 DEBUG:IP->FILE-HASH/LINE
956 ( ip -- len hash line TRUE / FALSE )
957 return unique file hash and name length instead of string name.
958 used in debugger.
960 STRING:=
961 ( a0 c0 a1 c1 -- bool )
963 STRING:=CI
964 ( a0 c0 a1 c1 -- bool )
965 case-insensitive compare (only for ASCII).
967 STRING:HASH
968 ( addr count -- hash )
970 STRING:HASH-CI
971 ( addr count -- hash )
972 case-insensitive hash (only for ASCII).
974 ($DEFINE)
975 ( addr count -- )
976 add new conditional define. case-insensitive (for ASCII).
978 ($UNDEF)
979 ( addr count -- )
980 remove conditional define. case-insensitive (for ASCII).
982 ($DEFINED?)
983 ( addr count -- bool )
984 check if we have a conditional define. case-insensitive (for ASCII).
986 ERROR
987 ( addr count -- )
988 print error message and abort.
990 ?ERROR
991 ( errflag addr count -- )
992 if "errflag" is not zero, print error message and abort.
994 ?NOT-ERROR
995 ( errflag addr count -- )
996 if "errflag" is zero, print error message and abort.
998 (INCLUDE-BUILD-NAME)
999 ( addr count soft? system? -- addr count )
1000 build include name, put it to PAD as cell-counted string.
1001 return string address.
1003 (INCLUDE-LINE-FOFS)
1004 ( -- fofs )
1005 return file offset of the current TIB line. offset is at the
1006 start of the line.
1008 (INCLUDE-LINE-SEEK)
1009 ( lidx fofs -- )
1010 move current include file position to the given one. doesn't
1011 reset TIB, doesn't re-read line. sets file index to the given
1012 one too. note that this index will be incremented on next REFILL.
1014 (INCLUDE-DEPTH)
1015 ( -- depth )
1016 return number of items in the include stack.
1018 (INCLUDE-FILE-ID)
1019 ( isp -- id )
1020 isp 0 is current, then 1, etc.
1021 each include file has unique non-zero id.
1023 (INCLUDE-FILE-LINE)
1024 ( isp -- line )
1026 (INCLUDE-FILE-NAME)
1027 ( isp -- addr count )
1028 current file name; at PAD.
1030 (INCLUDE)
1031 ( addr count soft? system? -- )
1032 push current file to the include stack, open a new one. used internally.
1034 (INCLUDE-NO-REFILL)
1035 ( addr count soft? system? -- )
1036 the same as "(INCLUDE)", but doesn't do automatic "REFILL".
1038 (INCLUDE-DROP)
1039 ( -- )
1040 drop (close) current include file, and return to the previous one.
1041 doesn't do automatic "REFILL".
1043 $INCLUDE "str"
1044 immediate word.
1046 $INCLUDE-ONCE "str"
1047 includes file only once; unreliable on shitdoze, i believe.
1048 immediate word.
1050 HANDLE:NEW
1051 ( typeid -- hx )
1052 allocate a new handle with the given typeid. typeid is just a number
1053 without any special meaning. any number except "-1" is allowed.
1054 new handle size is 0.
1056 HANDLE:FREE
1057 ( hx -- )
1058 deallocate a handle, free all allocated handle memory.
1059 0 is allowed.
1061 HANDLE:TYPEID@
1062 ( hx -- typeid )
1064 HANDLE:TYPEID!
1065 ( typeid hx -- )
1067 HANDLE:SIZE@
1068 ( hx -- size )
1069 0 is allowed.
1071 HANDLE:SIZE!
1072 ( size hx -- )
1073 resize memory allocated for handle data.
1075 HANDLE:USED@
1076 ( hx -- used )
1077 "used" is just a number, which means nothing for most code.
1078 it is used to implement dynamic arrays.
1079 0 is allowed.
1081 HANDLE:USED!
1082 ( size hx -- )
1084 HANDLE:C@
1085 ( idx hx -- value )
1087 HANDLE:W@
1088 ( idx hx -- value )
1090 HANDLE:@
1091 ( idx hx -- value )
1093 HANDLE:C!
1094 ( value idx hx -- value )
1096 HANDLE:W!
1097 ( value idx hx -- )
1099 HANDLE:!
1100 ( value idx hx -- )
1102 HANDLE:LOAD-FILE
1103 ( addr count -- stx / FALSE )
1104 load file with the given name into newly allocated handle.
1105 return 0 (FALSE) if there is no such file.
1108 ( -- rega )
1109 get address register contents.
1112 ( rega -- )
1113 set address register contents.
1115 A-SWAP
1116 ( rega -- olda )
1117 swap TOS and the address register.
1119 +1>A
1120 ( -- )
1121 increment the address register.
1123 +2>A
1124 ( -- )
1125 increment the address register.
1127 +4>A
1128 ( -- )
1129 increment the address register.
1131 -1>A
1132 ( -- )
1133 decrement the address register.
1135 -2>A
1136 ( -- )
1137 decrement the address register.
1139 -4>A
1140 ( -- )
1141 decrement the address register.
1144 ( -- | rega )
1145 copy the address register to the return stack.
1148 ( | rega -- )
1149 restore the address register from the return stack.
1152 ( -- byte )
1155 ( -- word )
1158 ( -- value )
1161 ( byte -- )
1164 ( word -- )
1167 ( value -- )
1169 C@A+
1170 ( idx -- byte )
1171 safe way to access both dictionary memory, and handle memory.
1172 "idx" is used as offset from address register contents.
1174 W@A+
1175 ( idx -- word )
1176 safe way to access both dictionary memory, and handle memory.
1177 "idx" is used as offset from address register contents.
1180 ( idx -- value )
1181 safe way to access both dictionary memory, and handle memory.
1182 "idx" is used as offset from address register contents.
1184 C!A+
1185 ( byte idx -- )
1186 safe way to access both dictionary memory, and handle memory.
1187 "idx" is used as offset from address register contents.
1189 W!A+
1190 ( word idx -- )
1191 safe way to access both dictionary memory, and handle memory.
1192 "idx" is used as offset from address register contents.
1195 ( value idx -- )
1196 safe way to access both dictionary memory, and handle memory.
1197 "idx" is used as offset from address register contents.
1199 DEBUG:(DECOMPILE-CFA)
1200 ( cfa -- )
1202 GET-MSECS
1203 ( -- u32 )
1205 (UFO-INTERPRET-FINISHED-ACTION)
1206 ( -- )
1207 this is called by main loop when it is out of input stream. internally,
1208 it simply sets a flag to tell the VM that it should stop.
1210 (UFO-INTERPRET-NEXT-LINE)
1211 ( -- continue? )
1212 default word used to read next input line. return FALSE to exit from
1213 "INTERPRET".
1215 (INTERPRET-PARSE-NAME)
1216 ( -- addr count / FALSE )
1217 called by INTERPRET to read next word from the input stream. calls
1218 "(INTERPRET-NEXT-LINE)" to refill lines. return FALSE (without address)
1219 to exit from "INTERPRET", or next parsed word.
1221 (USER-INTERPRET-NEXT-LINE)
1222 user variable, holds address of "get next line" word. default value is
1223 CFA of "(UFO-INTERPRET-NEXT-LINE)".
1225 (INTERPRET-NEXT-LINE)
1226 ( -- continue? )
1227 peek "(USER-INTERPRET-NEXT-LINE)" and call read CFA.
1229 HERE
1230 ( -- dp )
1231 push current dictionary pointer to the data stack.
1232 NOTE: there are actually two DPs -- normal, and temporary. "(DP-TEMP)" is
1233 the temp one, and if it is 0, "(DP)" is used. UrForth has 1MB temp area
1234 (that's where PAD is too), it had different addresses, and vocabularies
1235 created in that area are not linked to the main voclink list. this is used,
1236 for example, in locals engine, to store names of locals. so if you're using
1237 locals in your word, do not use temp area while compiling that word.
1239 LATEST-LFA
1240 ( -- lfa )
1241 push LFA of the latest defined word in the current vocabulary. note that
1242 "smudge" bit doesn't matter here, it is always the last word you created
1243 header for. this includes "nonamed" words (which have empty string as a name).
1245 NOOP
1246 ( -- )
1247 does nothing. at all.
1249 COMPILER:(CTLID-COLON)
1250 ( -- ctlid-colon )
1251 semicolon expects this on the data stack.
1253 ' <name>
1254 ( -- cfa )
1255 find word, push its CFA to the data stack. note that the tick
1256 is NOT immediate. use "[']" if you need to compile next word CFA.
1259 start new word definition.
1262 end new word definition.
1264 ALIAS-FOR oldword IS newword
1265 ( -- )
1266 "newword" will do exactly the same as "oldword". word attributes
1267 will be copied too (hidden, immediate, etc.).
1269 LATEST-CFA
1270 ( -- cfa )
1272 LATEST-PFA
1273 ( -- pfa )
1275 LATEST-NFA
1276 ( -- nfa )
1278 LATEST-SFA
1279 ( -- sfa )
1281 ~AND
1282 ( a b -- a&~b )
1284 SWAP!
1285 ( addr value -- )
1288 ( value addr -- )
1290 ~AND!
1291 ( value addr -- )
1293 XOR!
1294 ( value addr -- )
1296 IMMEDIATE
1297 mark last defined word as immediate (or remove immediate mark if it is already set).
1299 (HIDDEN)
1300 mark last defined word as hidden. DO NOT USE. this is obsolete feature,
1301 and it will be removed. it is here for compatibility with my other Forth system.
1303 (PUBLIC)
1304 the opposite of "(HIDDEN)".
1306 -FIND-REQUIRED
1307 alias for the tick.
1309 PARSE-SKIP-COMMENTS
1310 ( -- )
1311 skip all comments and blanks, multiline mode.
1313 PARSE-SKIP-LINE-COMMENTS
1314 skip all comments and blanks, single line mode.
1316 (SET-DEF-WORD-FLAGS)
1317 ( flg -- )
1318 add (OR) default flag for new words.
1319 word flags are:
1320   (WFLAG-IMMEDIATE)
1321   (WFLAG-SMUDGE)
1322   (WFLAG-NORETURN)
1323   (WFLAG-HIDDEN)
1324   (WFLAG-CBLOCK)
1325   (WFLAG-VOCAB)
1326   (WFLAG-SCOLON)
1327   (WFLAG-PROTECTED)
1329 (RESET-DEF-WORD-FLAGS)
1330 ( flg -- )
1331 remove (~AND) default flag for new words.
1333 <PUBLIC-WORDS>
1334 ( -- )
1335 all following words will be public.
1337 <HIDDEN-WORDS>
1338 ( -- )
1339 all following words will be hidden.
1341 <PROTECTED-WORDS>
1342 ( -- )
1343 all following words will be protected. you cannot redefine
1344 protected words.
1346 <UNPROTECTED-WORDS>
1347 ( -- )
1348 all following words will not be protected.
1350 ONLY
1351 ( -- )
1352 clear the wordlist stack.
1354 ALSO
1355 ( -- )
1356 push context vocabulary onto the wordlist stack.
1358 PREVIOUS
1359 ( -- )
1360 pop vocabulary from the wordlist stack, and make in context.
1362 DEFINITIONS
1363 ( -- )
1364 make context vocabulary also current. "current" is the vocabulary
1365 that will receive new word definitions. "context" is the vocabulary
1366 that will be used to search words.
1369 ( a -- a+1 )
1372 ( a -- a+2 )
1375 ( a -- a+2 )
1378 ( a -- a-1 )
1381 ( a -- a-2 )
1384 ( a -- a-2 )
1387 ( n -- n==0 )
1390 ( n -- n<>0 )
1393 ( n -- n==0 )
1396 ( n -- n==0 )
1399 ( n -- n<>0 )
1402 ( n -- n<>0 )
1404 NOTNOT
1405 ( a -- !!a )
1408 ( a -- |a| )
1410 SIGN?
1411 ( n -- -1|0|1 )
1413 NEGATE
1414 ( n -- -n )
1416 LSHIFT
1417 ( n count -- n )
1419 RSHIFT
1420 ( n count -- n )
1422 ARSHIFT
1423 ( n count -- n )
1426 ( n count -- n )
1429 ( n count -- n )
1432 ( n count -- n )
1435 ( n count -- n )
1437 LO-WORD
1438 ( a -- a&0xffff )
1440 HI-WORD
1441 ( a -- [a>>16]&0xffff )
1443 LO-BYTE
1444 ( a -- a&0xff )
1446 HI-BYTE
1447 ( a -- [a>>8]&0xff )
1450 ( a b -- min[a,b] )
1453 ( a b -- max[a,b] )
1455 UMIN
1456 ( a b -- umin[a,b] )
1458 UMAX
1459 ( a b -- umax[a,b] )
1461 BSWAP16
1462 ( a -- n )
1464 BSWAP32
1465 ( a -- n )
1468 ( addr -- )
1471 ( addr -- )
1474 ( n addr -- )
1477 ( n addr -- )
1480 ( addr -- )
1483 ( addr -- )
1485 BCOUNT
1486 ( addr -- addr+1 count )
1488 COUNT
1489 ( addr -- addr+4 count )
1492 ( -- )
1494 DECIMAL
1495 ( -- )
1497 OCTAL
1498 ( -- )
1500 BINARY
1501 ( -- )
1503 WITHIN
1504 ( value a b -- value>=a&&value<b )
1506 UWITHIN
1507 ( value a b -- value>=a&&value<b )
1509 BOUNDS?
1510 ( value a b -- value>=a&&value<=b )
1511 numbers are unsigned.
1513 (HANDLE-ADDR?)
1514 ( addr -- )
1515 check if the given addres is actually a handle.
1517 COMPILER:SET-SMUDGE
1518 ( -- )
1519 set "smudge" bit for the latest word.
1521 COMPILER:RESET-SMUDGE
1522 ( -- )
1523 reset "smudge" bit for the latest word.
1525 COMPILER:SET-WARG
1526 ( warg -- )
1527 set argument type for the latest word. each word has "argument type" field,
1528 which inditates word argument type in the compiled code. arguments are:
1529   (WARG-NONE)
1530   (WARG-BRANCH)
1531   (WARG-LIT)
1532   (WARG-C4STRZ)
1533   (WARG-CFA)
1534   (WARG-CBLOCK)
1535   (WARG-VOCID)
1536   (WARG-C1STRZ)
1538 (WARG-MASK)
1539 ( -- mask )
1540 this mask can be used to get only argument type bits from the first NFA cell.
1542 COMPILER:(GET-NEW-WORD-FLAGS)
1543 ( -- flags )
1544 get sanitized new word flags. currently, only "hidden" and "protected" flags
1545 are retained, all other flags will be reset.
1547 COMPILER:(CREATE-HEADER)
1548 ( addr count -- )
1549 create new named word header with the default flags. additionally, sets
1550 "smudge" flag on the new word.
1552 COMPILER:(CREATE-NAMELESS)
1553 ( -- cfa )
1554 create new nameless word header with the default flags. additionally, sets
1555 "smudge" and "hidden" flags on the new word.
1556 return CFA address of the new word. CFA contents is not filled yet.
1558 COMPILER:(MK-CONST-VAR)
1559 ( value cfaidx -- )
1560 don't bother using this.
1562 COMPILER:FORTH-WORD?
1563 ( cfa -- bool )
1564 check if the given word is normal Forth word (i.e. defined with the colon).
1566 COMPILE
1567 ( cfa -- )
1568 compiles CFA to be executed.
1570 use the following words to compile branch destinations. this way your code
1571 will be independent of branch instruction operand format.
1573 ;; usage:
1574 ;;  compile (0branch)
1575 ;;  (mark>)
1576 ;;  ...
1577 ;;  (resolve>)
1579 ;;  (<mark)
1580 ;;  ...
1581 ;;  compile (branch)
1582 ;;  (<resolve)
1584 COMPILER:(BRANCH-ADDR!)
1585 ( destaddr addr -- )
1586 write "branch to destaddr" address to addr.
1588 COMPILER:(BRANCH-ADDR@)
1589 ( addr -- dest )  @ ;
1590 read branch address.
1592 COMPILER:(<J-MARK)
1593 ( -- addr )
1594 return addr suitable for "(<J-RESOLVE)".
1596 COMPILER:(<J-CHAIN)
1597 ( addr -- addr )
1598 use after "(<J-MARK)" to reserve jump and append it to jump chain.
1600 COMPILER:(<J-RESOLVE)
1601 ( addr -- )
1602 patch "forward jump" address to HERE. "addr" is the result of "(<J-MARK)".
1604 COMPILER:(MARK-J>)
1605 reserve room for branch address, return addr suitable for "(RESOLVE-J>)".
1607 COMPILER:(CHAIN-J>)
1608 use after "(MARK-J>)" to reserve jump and append it to jump chain.
1610 COMPILER:(RESOLVE-J>)
1611 ( addr -- )
1612 compile "forward jump" (possibly chain) from address to HERE. addr is the
1613 result of "(MARK-J>)". this resolves the whole "jump chain".
1616 COMPILER:?PAIRS
1617 ( a b -- )
1618 throw error if a <> b.
1620 ?2PAIRS
1621 ( a b c -- )
1622 throw error if a <> b and a <> c.
1624 LITERAL
1625 ( C:n -- )
1626 ( E:n -- n )
1627 compile number from the data stack as literal. NOT IMMEDIATE.
1629 IMM-LITERAL
1630 ( C:n -- )
1631 ( E:n -- n )
1632 immediate version of "LITERAL".
1634 STRLITERAL
1635 ( C:addr count -- )
1636 ( E: -- addr count )
1638 IMM-STRLITERAL
1639 immediate version of the previous word.
1641 CFALITERAL
1642 ( C:cfa -- )
1643 ( E:cfa -- cfa )
1645 IMM-CFALITERAL
1646 ( C:cfa -- )
1647 ( E:cfa -- cfa )
1649 [COMPILE] <wordname>
1650 force the next word to be compiled as normal word, even if it is an immediate one.
1653 compile next word CFA as CFA literal.
1655 COMPILER:(COMPILE-CFA-LITERAL)
1656 ( cfa -- )
1657 compile cfa literal to be compiled. ;-)
1659 COMPILE <wordname>
1660 compile next word to the currently defining word.
1662 [CHAR] <char>
1663 ( -- ch )
1664 push/compile first char of the next word as char code.
1665 note that words with more than one char will cause an error.
1667 RECURSE
1668 recursively call the currently defining word. this is required
1669 due to currently defining word being invisible yet (because it
1670 is not finished).
1672 RECURSE-TAIL
1673 tail-call recursion.
1675 CONSTANT <name>
1676 ( value -- )
1677 create new constant.
1679 VARIABLE <name>
1680 ( value -- )
1681 create new variable.
1683 (CREATE)
1684 ( addr count -- )
1685 this is what "CREATE" is using to create a new word.
1687 CREATE <name>
1688 ( -- )
1689 create new word. when executed, this new word will push its PFA.
1690 note that new word is not smudged.
1692 CREATE;
1693 ( -- )
1694 finish CREATEd word. this is required to correctly set SFA.
1695 note that "DOES>" automatically takes care of SFA, so you don't have
1696 to call this if you're using "DOES>".
1698 (DOES>)
1699 ( doer-addr -- )
1700 patch CREATEd word. put doer address to its CFA, VM will do the rest.
1701 this is used internally by the compiler.
1703 (SET-DOER)
1704 ( doer-pfa cfa -- )
1705 makes CFA word to execute "doer-pfa" as doer.
1706 this is used internally by the compiler. do not try to understand this.
1708 DOES>
1709 ( -- )  ( pfa )
1710 the usual Forth "CREATE" -- "DOES>" support.
1712 CELL
1713 ANS idiocity.
1715 CELLS
1716 ( n -- n*cells )
1717 ANS idiocity.
1719 CELL+
1720 ( n -- n+cell )
1721 ANS idiocity.
1723 CELL-
1724 ( n -- n-cell )
1725 ANS idiocity.
1727 +CELLS
1728 ( a n -- a+n*cells )
1729 ANS idiocity.
1731 -CELLS
1732 ( a n -- a+n*cells )
1733 ANS idiocity.
1735 .( text)
1736 immediately print the text.
1738 ." text"
1739 compile text printer.
1741 N-ALLOT
1742 ( n -- stard-addr )
1743 allocate n *bytes* in the current DP, return the address of
1744 the first allocated byte.
1746 ALLOT
1747 ( n -- )
1748 allocate n *bytes* in the current DP.
1750 ALIGN-HERE
1751 ( -- )
1752 align DP to 4-byte boundary.
1754 COMPILER:(NEW-WORDLIST)
1755 ( parentvocid need-hashtable? -- vocid )
1756 create new empty wordlist.
1758 COMPILER:(CREATE-NAMED-VOCAB)
1759 ( vocid addr count -- )
1760 create vocabulary word.
1762 COMPILER:(CREATE-VOCAB) <vocname>
1763 ( vocid -- )
1764 create vocabulary word.
1766 COMPILER:(IS-VOC-WORD?)
1767 ( cfa -- bool )
1768 check if the given CFA defined as a vocabulary header.
1770 COMPILER:(WORD->VOCID)
1771 ( cfa -- vocid )
1772 get vocid from the vocabulary word. doesn't check arguments.
1774 COMPILER:(VOCID-PARENT@)
1775 ( vocid -- vocid )
1776 get vocid parent vocabulary. return 0 if there is no parent.
1777 doesn't check arguments.
1779 COMPILER:(VOCID-PARENT!)
1780 ( parent-vocid vocid -- )
1781 set vocid parent vocabulary. doesn't check arguments.
1783 COMPILER:(VOCID-TYPEID@)
1784 ( vocid -- typeid )
1785 internal helper for STRUCT support.
1787 COMPILER:(VOCID-TYPEID!)
1788 internal helper for STRUCT support.
1790 (VOCABULARY-EX)
1791 ( addr count parent need-hashtbl? -- )
1792 useful low-level words to create vocabs with already parsed names.
1794 (VOCABULARY)
1795 ( addr count -- )
1797 (SIMPLE-VOCABULARY)
1798 ( addr count -- )
1799 creates vocabulary without a hash table.
1801 (NESTED-VOCABULARY)
1802 ( addr count -- )
1804 (SIMPLE-NESTED-VOCABULARY)
1805 ( addr count -- )
1807 VOCABULARY <vocname>
1809 SIMPLE-VOCABULARY <vocname>
1811 NESTED-VOCABULARY <vocname>
1813 SIMPLE-NESTED-VOCABULARY <vocname>
1815 VOCID: <vocname>
1816 ( -- vocid )
1817 return vocid for the given vocabulary. this word is immediate.
1819 VOC-LATEST
1820 ( vocid -- latest )
1821 return latest word LFA for the given vocid.
1823 ALSO-DEFS: <vocname>
1824 ( -- )
1825 this does "ALSO <vocname> DEFINITIONS"
1827 PREV-DEFS
1828 ( -- )
1829 this does "PREVIOUS DEFINITIONS".
1831 VOCAB-IF-NONE <vocname>
1832 create vocabulary if we don't have such word yet.
1834 NESTED-VOCAB-IF-NONE <vocname>
1835 create nested vocabulary if we don't have such word yet.
1837 SIMPLE-VOCAB-IF-NONE <vocname>
1838 create vocabulary if we don't have such word yet.
1840 SIMPLE-NESTED-VOCAB-IF-NONE <vocname>
1841 create nested vocabulary if we don't have such word yet.
1843 -TO  ( n -- )  \ name
1844 decrement value by n.
1846 +TO  ( n -- )  \ name
1847 increment value by n.
1849 -1-TO  ( -- )  \ name
1850 decrement value by 1.
1852 +1-TO  ( -- )  \ name
1853 increment value by 1.
1855 0-TO  ( -- )  \ name
1856 write 0 to value.
1858 ... FORTH:(TO-EXTENDER) ...
1859 ( addr count FALSE -- addr count FALSE / TRUE )
1860 "TO" can be extended to support things it doesn't know about yet.
1861 after parsing a name, "(TO-EXTENDER)" will be called (this is
1862 scattered colon word). note that due to how scattered colon works,
1863 you'd better DON'T use "EXIT", but pass a flag if you need to stop
1864 further processing. also, do not forget to check the flag at the
1865 start of your extender, because some other extender may already
1866 did its work before yours.
1868 ... FORTH:(EXIT-EXTENDER) ...
1869 ( -- )
1870 this scattered colon word allows you to extend "EXIT". "EXIT" is
1871 the immediate word that compiles word leaving instructions. you
1872 can compile your cleanup code before the standard cleanup.
1874 ... FORTH:(INTERPRET-CHECK-WORD) ...
1875 ( addr count FALSE -- addr count FALSE / TRUE )
1876 this is called by INTERPRET before the standard word processing.
1878 ... FORTH:(INTERPRET-WORD-NOT-FOUND) ...
1879 ( addr count FALSE -- addr count FALSE / TRUE )
1880 this is called by INTERPRET when word resolution failed.
1883 UrForth supports cooperative multitasking. it is also used to implement
1884 interactive debugger. tasks are called "execution states", or simply
1885 "states".
1887 MTASK:NEW-STATE
1888 ( cfa -- stid )
1889 create new state, return state id.
1891 MTASK:FREE-STATE
1892 ( stid -- )
1893 free state. state id should be valid, and should not be an active state.
1895 MTASK:STATE-NAME@
1896 ( stid -- addr count )
1897 copy state name to PAD.
1899 MTASK:STATE-NAME!
1900 ( addr count stid -- )
1901 set new state name. maximum name length is 127 chars. state name
1902 should not include char with code 0.
1904 MTASK:STATE-FIRST
1905 ( -- stid )
1906 get first state in the list of all created states. this is used to
1907 iterate over all states.
1908 WARNING! do not mutate state list while iterating! result will be UB.
1910 MTASK:STATE-NEXT
1911 ( stid -- stid / 0 )
1912 get next state id. used to iterate over all states.
1913 WARNING! do not mutate state list while iterating! result will be UB.
1915 MTASK:YIELD-TO
1916 ( ... argc stid -- )
1917 yield to another state. move argc numbers from the current state data
1918 stack to the new state data stack. push args to the new state data
1919 stack, and then push current state id. i.e. new state data stack will
1920 look like this:
1921   ( ... argc old-stid )
1922 it is ok to swith to the currently active state (it is a no-op).
1924 MTASK:SET-SELF-AS-DEBUGGER
1925 ( -- )
1926 register current task as system debugger. you can yeild from the debugger
1927 after this.
1929 DEBUG:(BP)
1930 ( -- )
1931 breakpoint. debugger task receives debugge stid on the data stack,
1932 and `-1` as yield argument count. i.e. debugger stack will be:
1933   ( -1 old-stid )
1935 MTASK:DEBUGGER-RESUME
1936 ( stid -- )
1937 resume debugee execution.
1939 DEBUG:SINGLE-STEP@
1940 ( -- enabled? )
1941 get "single stepping enabled" flag.
1943 MTASK:DEBUGGER-SINGLE-STEP
1944 ( stid -- )
1945 execute one debuggee instruction, and return to debugger.
1946 this is basically "YIELD", but to use in the debugger
1947 (and it doesn't pass any arguments). debugger stack will be:
1948   ( -2 old-stid )
1950 MTASK:STATE-IP@
1951 ( stid -- ip )
1952 get state instruction pointer.
1954 MTASK:STATE-IP!
1955 ( ip stid -- )
1956 set state instruction pointer.
1958 MTASK:STATE-A>
1959 ( stid -- regA )
1960 get address register contents.
1962 MTASK:STATE->A
1963 ( rega stid -- )
1964 set address register contents.
1966 MTASK:STATE-USER@
1967 ( addr stid -- valie )
1968 get other state user area cell.
1970 MTASK:STATE-USER!
1971 ( value addr stid -- )
1972 set other state user area cell.
1974 MTASK:STATE-RPOPCFA@
1975 ( -- flag )
1976 VM has special mode when it gets next CFA from the return stack
1977 instead of the address pointed by IP. this is used to implement
1978 "EXECUTE", for example. use this word to retrieve that flag.
1980 MTASK:STATE-RPOPCFA!
1981 ( flag -- )
1982 VM has special mode when it gets next CFA from the return stack
1983 instead of the address pointed by IP. this is used to implement
1984 "EXECUTE", for example. use this word to set that flag.
1986 MTASK:ACTIVE-STATE
1987 ( -- stid )
1988 return state id of the currently executing state.
1990 MTASK:YIELDED-FROM
1991 ( -- stid / 0 )
1992 return state which called "MTASK:YIELD-TO" last.
1994 MTASK:STATE-SP@
1995 ( stid -- depth )
1996 get the data stack depth for the given state.
1998 MTASK:STATE-RP@
1999 ( stid -- depth )
2000 get the return stack depth for the given state.
2002 MTASK:STATE-LP@
2003 ( stid -- lp )
2004 get local stack ptr.
2006 MTASK:STATE-LBP@
2007 ( stid -- lbp )
2008 get local stack base ptr.
2010 MTASK:STATE-SP!
2011 ( depth stid -- )
2012 set the data stack depth for the given state.
2014 MTASK:STATE-RP!
2015 ( stid -- depth )
2016 set the return stack depth for the given state.
2018 MTASK:STATE-LP!
2019 ( lp stid -- )
2020 set local stack ptr.
2022 MTASK:STATE-LBP!
2023 ( lbp stid -- )
2024 set local stack base ptr.
2026 MTASK:STATE-DS@
2027 ( idx stid -- value )
2028 read the data stack of the given state. note that the index is bound-checked.
2030 MTASK:STATE-RS@
2031 ( idx stid -- value )
2032 read the return stack of the given state. note that the index is bound-checked.
2034 MTASK:STATE-LS@
2035 ( idx stid -- value )
2036 read the locals stack of the given state. note that the index is bound-checked.
2038 MTASK:STATE-DS!
2039 ( value idx stid -- )
2040 write the data stack of the given state. note that the index is bound-checked.
2041 i.e. if you want to push some value, increase stack depth first.
2043 MTASK:STATE-RS!
2044 ( value idx stid -- )
2045 write the return stack of the given state. note that the index is bound-checked.
2046 i.e. if you want to push some value, increase stack depth first.
2048 MTASK:STATE-LS!
2049 ( value idx stid -- )
2050 write the locals stack of the given state. note that the index is bound-checked.
2051 i.e. if you want to push some value, increase stack depth first.
2053 MTASK:STATE-VSP@
2054 ( stid -- vsp )
2055 get wordlist stack pointer.
2057 MTASK:STATE-VSP!
2058 ( vsp stid -- )
2059 set wordlist stack pointer.
2061 MTASK:STATE-VSP-AT@
2062 ( idx stid -- )
2063 get wordlist stack contents.
2065 MTASK:STATE-VSP-AT!
2066 ( value idx stid -- )
2067 set wordlist stack contents.
2070 there are some words to work with TTY (only GNU/Linux).
2072 TTY:TTY?
2073 ( -- bool )
2074 check if input and output are valid TTY(s).
2076 TTY:RAW?
2077 ( -- bool )
2078 check if current TTY mode is raw.
2080 TTY:SIZE
2081 ( -- width height )
2082 get TTY size. for non-TTYs retur default 80x24.
2084 TTY:SET-RAW
2085 ( -- success-bool )
2086 switch TTY to raw mode.
2088 TTY:SET-COOKED
2089 ( -- success-bool )
2090 switch TTY to cooked mode.
2092 TTY:RAW-EMIT
2093 ( n -- )
2094 type char without any filtering or safety nets.
2096 TTY:RAW-TYPE
2097 ( addr count -- )
2098 type string without any filtering or safety nets.
2100 TTY:RAW-FLUSH
2101 ( -- )
2102 the output of the two words above is buffered. this words flushes
2103 the buffer. buffering is done because raw TTY is mostly used to
2104 build user interfaces, and sending accumulated terminal commands
2105 in one big chunk looks much better (most terminal emulators will
2106 process the whole chunk before refreshing their windows).
2108 TTY:RAW-READCH
2109 ( -- ch / -1 )
2110 -1 returned on error, or on EOF.
2111 read one char (without any interpretation) if TTY is in raw mode.
2112 note that 0 is a valid char (it is used to send Ctrl+Space in some
2113 terminal emulators). also note that there is no way to tell if we
2114 hit a EOF, or some error occured. in practice, it doesn't matter,
2115 because in both cases it means that TTY is unusable anymore.
2117 TTY:RAW-READY?
2118 ( -- bool )
2119 check if raw TTY has some data to read.
2122 file i/o words.
2124 FILES:ERRNO
2125 ( -- errno )
2126 last libc `errno`. can be used after failure to inspect error code.
2128 FILES:UNLINK
2129 ( addr count -- success? )
2130 delete file.
2132 FILES:OPEN-R/O
2133 ( addr count -- handle TRUE / FALSE )
2134 open file for reading. `handle` is always positive.
2136 FILES:OPEN-R/W
2137 ( addr count -- handle TRUE / FALSE )
2138 open file for writing. `handle` is always positive.
2140 FILES:CREATE
2141 ( addr count -- handle TRUE / FALSE )
2142 create new file, or truncate existing. `handle` can be any number, including
2143 `0` and negative numbers.
2145 FILES:CLOSE
2146 ( handle -- success? )
2147 close opened file.
2149 FILES:TELL
2150 ( handle -- ofs TRUE / FALSE )
2151 get current file position.
2153 FILES:SEEK-EX
2154 ( ofs whence handle -- TRUE / FALSE )
2155 set current file position. `whence` can be one of "FILES:SEEK-SET",
2156 "FILES:SEEK-CUR", "FILES:SEEK-END".
2158 FILES:SEEK
2159 ( ofs handle -- TRUE / FALSE )
2160 set current file position. the same as calling "SEEK-EX" with `whence`
2161 equal to "SEEK-SET".
2163 FILES:SIZE
2164 ( handle -- size TRUE / FALSE )
2165 get file size. `handle` cannot be 0.
2166 WARNING! on failure on valid handle, file position for that handle is undefined.
2168 FILES:READ
2169 ( addr count handle -- rdsize TRUE / FALSE )
2170 read bytes from file. this word can read less bytes than requirested. `count`
2171 can be 0 (in this case the function always succeeds). note that this function
2172 can read 0 bytes, and this is success too.
2174 FILES:READ-EXACT
2175 ( addr count handle -- TRUE / FALSE )
2176 read bytes from file. reading less then requested number of bytes is error.
2177 `count` can be 0 (in this case the function always succeeds).
2179 FILES:WRITE
2180 ( addr count handle -- TRUE / FALSE )
2181 write bytes from file. writing less bytes than requested is error. `count`
2182 can be 0 (in this case the function always succeeds).