asm: added simple .SNA writer
[urasm.git] / dox / urforth.txt
blobf176ae2a3cc3125e0234ff20c3de8ae63f2b67c0
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 some global variables are state-local. also, each state has its own TIB,
53 independent of other states.
55 state-local vars are:
56 BASE
57 ( -- base-addr )
58 current number base.
60 TIB
61 ( -- addr )
62 current TIB.
64 >IN
65 ( -- ofs )
66 offset in current TIB.
68 PAD
69 ( -- pad )
70 return PAD address. this memory area can be used for storing temporary
71 values (like strings). you can assume to have at least 4096 bytes there.
72 WARNING! some words may use PAD for their own needs. this is mostly
73          words which does some string manipulation, like building strings
74          from parts, and such. note that number conversion buffer is
75          independent of PAD.
77 (STD-TIB-ADDR)
78 ( -- )
79 default TIB address. WARNING! if this user var contains a handle, that
80 handle will be freed on destroying the task. if you want to replace the
81 default TIB, make sure that you will free the old handle (if it is a handle).
83 STATE
84 ( -- addr )
85 current system state. `0` for interpretation, any other value for compilation.
87 CONTEXT
88 ( -- addr )
89 context vocabulary, i.e. vocabulary that will be used to look for words. note
90 that there is a stack of vocabularies there (see "ALSO" and other words), and
91 all of them will be searched after context one.
93 CURRENT
94 ( -- addr )
95 this is vocabulary that will be used to record new words. it is only checked
96 for duplicate word definitions, but otherwise is not participating in word
97 searching mechanics.
99 (SELF)
100 ( -- addr )
101 this is used in OOF. it holds address of the active class instance (object).
103 (USER-INTERPRET-NEXT-LINE)
104 ( -- addr )
105 this holds the address of a word which will be called by INTERPRET when it
106 hits EOL, and needs to read a new line to interpret (or compile).
108 (EXC-FRAME-PTR)
109 ( -- addr )
110 this is used in THROW/CATCH implementation, and holds current exception frame
111 address.
113 (USER-VAR-USED)
114 ( -- uvar-used-addr )
115 address of the variable contains first free user area address.
117 (USER-VAR-ADDR)
118 ( -- uvar-begin-addr )
119 start address of the user area.
121 (USER-VAR-SIZE)
122 ( -- uvar-size )
123 maximum user area size in bytes.
127 DEBUG:DUMP-STACK
128 ( -- )
129 dump data stack
131 DEBUG:BACKTRACE
132 ( -- )
133 show current backtrace (slow!)
135 DEBUG:DECOMPILE name
136 ( -- )
137 decompile given forth word.
139 SP0!
140 ( -- )
141 clear data stack.
143 RP0!
144 ( -- )
145 clear return stack.
147 note that address for memory operations may be a handle too. with handles,
148 low bits are used as offset, so you can directly address some bytes in handle
149 data area. currently, low 12 bits are reserved for offset, so you can address
150 4096 bytes inside a handle. but don't hardcode it, use "FORTH:(MAX-HANDLE-OFS)"
151 constant to get the maximum allowed offset (because it may change in the future).
153 also, UrForth is 32-bit system, and stores all numbers as little-endian. this
154 will not change, so you can write your code without checking cell size, or
155 byte order.
159 ( addr -- value8 )
160 load 8-bit value.
163 ( addr -- value16 )
164 load 16-bit value.
167 ( addr -- value32 )
168 load 32-bit value.
171 ( val8 addr -- )
172 store 8-bit value.
175 ( val16 addr -- )
176 store 16-bit value.
179 ( val32 addr -- )
180 store 32-bit value.
183 ( val8 -- )
184 compile 8-bit value.
187 ( val16 -- )
188 compile 16-bit value.
191 ( val -- )
192 compile 32-bit value.
195 (LIT)
196 ( -- n )
197 read 4 bytes immediately following this word, and push them
198 to the data stack. adjust IP to skip those bytes.
200 (LITCFA)
201 ( -- n )
202 read 4 bytes immediately following this word, and push them
203 to the data stack. adjust IP to skip those bytes. this is
204 the same as "(LIT)", but used to store CFAs of words. using
205 different words for different data types helps the debugger
206 and the decompiler.
208 (LITVOCID)
209 ( -- n )
210 the same as "(LIT)", but for vocids.
212 (LITSTR8)
213 ( -- addr count )
214 inline byte-counted string literal. note that the string
215 always have a trailing zero byte (which is not counted),
216 and always padded so it ends on a 4-byte boundary.
218 (BRANCH) ( -- )
219 read next 4 bytes, and set IP to that address.
221 (TBRANCH)
222 ( flag -- )
223 skip next 4 bytes if `flag` is 0, otherwise perform "(BRANCH)".
225 (0BRANCH)
226 ( flag -- )
227 skip next 4 bytes if `flag` is not 0, otherwise perform "(BRANCH)".
229 (+0BRANCH)
230 ( num -- )
231 skip next 4 bytes if `num` is positive or 0, otherwise perform "(BRANCH)".
233 (+BRANCH)
234 ( num -- )
235 skip next 4 bytes if `num` is positive (but not 0), otherwise perform "(BRANCH)".
237 (-BRANCH)
238 ( num -- )
239 skip next 4 bytes if `num` is negative, otherwise perform "(BRANCH)".
241 (DATASKIP)
242 ( -- )
243 read next 4 bytes, advance IP. then increment IP by the read number.
244 this is used to tell the decompiler that it should skip some inline
245 data instead of trying to decompile it.
247 EXECUTE
248 ( cfa )
249 pop word CFA address, and execute it.
251 EXECUTE-TAIL
252 ( cfa )
253 pop word CFA address, and execute it. returning from the executed
254 word will return to the upper word. i.e. this performs a tail call.
257 (EXIT)
258 internal compiler word, placed at the end of colon definition.
259 pops a number from return stack, and sets IP to that number.
261 (L-ENTER)
262 this word is used to implement local variables and arguments.
263 it doesn't matter how it works, you should not used it anyway.
264 read the source code, if you're curious.
266 (L-LEAVE)
267 this word is used to implement local variables and arguments.
268 it doesn't matter how it works, you should not used it anyway.
269 read the source code, if you're curious.
271 (LOCAL@)
272 ( idx -- value )
273 read local variable with the given index. indices are 1-based.
275 (LOCAL!)
276 ( value idx -- )
277 write local variable with the given index. indices are 1-based.
280 ( n -- n n )
281 duplicates a number on the data stack.
283 ?DUP
284 ( n -- n n ) | ( 0 -- 0 )
285 duplicates a number on the data stack, but only if that number is not 0.
287 2DUP
288 ( n0 n1 -- n0 n1 n0 n1 )
290 DROP
291 ( n -- )
293 2DROP
294 ( n0 n1 -- )
296 SWAP
297 ( n0 n1 -- n1 n0 )
299 2SWAP
300 ( n0 n1 -- n1 n0 )
302 OVER
303 ( n0 n1 -- n0 n1 n0 )
305 2OVER
306 ( n0 n1 -- n0 n1 n0 )
309 ( n0 n1 n2 -- n1 n2 n0 )
311 NROT
312 ( n0 n1 n2 -- n2 n0 n1 )
315 ( a b -- b )
317 TUCK
318 ( a b -- b a b )
320 RDUP
321 ( n -- n n )
322 the same as "DUP", but for the return stack.
324 RDROP
325 ( n -- )
326 the same as "DROP", but for the return stack.
328 RSWAP
329 ( n0 n1 -- n1 n0 )
330 the same as "SWAP", but for the return stack.
332 ROVER
333 ( n0 n1 -- n0 n1 n0 )
334 the same as "OVER", but for the return stack.
336 RROT
337 ( n0 n1 n2 -- n1 n2 n0 )
338 the same as "ROT", but for the return stack.
340 RNROT
341 ( n0 n1 n2 -- n2 n0 n1 )
342 the same as "NROT", but for the return stack.
345 ( n -- | n )
346 move number from the data stack to the return stack.
349 ( | n -- n )
350 move number from the return stack to the data stack.
353 ( | n -- n | n )
354 copy number from the return stack to the data stack.
356 PICK
357 ( idx -- n )
358 copy n-th element at the data stack. "0 PICK" is the same as "DUP".
360 RPICK
361 ( idx -- n )
362 the same as "PICK", but for the return stack.
364 ROLL
365 ( idx -- n )
366 move n-th element at the data stack to the top. "1 ROLL" is the same as "SWAP".
368 RROLL
369 ( idx -- n )
370 the same as "ROLL", but for the return stack.
372 REFILL
373 ( -- eofflag )
374 read next input line. can cross include boundaries. pushes 0 if
375 there are no more input lines. TIB contents is undefined in this case.
377 REFILL-NOCROSS
378 ( -- eofflag )
379 read next input line. cannot cross include boundaries. pushes 0 if
380 there are no more input lines. TIB contents is undefined in this case.
382 (TIB-IN)
383 ( -- addr )
384 get address of the current TIB position.
385 WARNING! do not try to emulate "TIB-GETCH" and such with this word!
386          TIB usually ends with 0 byte, and if you will advance beyond
387          that 0, Bad Things will happen.
389 TIB-PEEKCH
390 ( -- char )
391 push current TIB char, do not advance >IN.
393 TIB-PEEKCH-OFS
394 ( ofs -- char )
395 peek TIB char with the given offset. "0 TIB-PEEKCH-OFS" is the same as "TIB-PEEKCH".
397 TIB-GETCH
398 ( -- char )
399 push current TIB char, advance >IN. it is safe to call this even
400 when you reached the end of TIB. in this case, returned char code
401 will be 0. i.e. "0" means "end of TIB".
403 TIB-SKIPCH
404 ( -- )
405 skip current TIB char. it is safe to call this even when you reached
406 the end of TIB.
409 (PARSE)
410 ( delim skip-leading-delim? -- addr count TRUE / FALSE )
411 does base TIB parsing; never copies anything.
412 as our reader is line-based, returns FALSE on EOL.
413 EOL is detected after skipping leading delimiters.
414 passing -1 as delimiter skips the whole line, and always returns FALSE.
415 finishing delimiter is always skipped.
417 PARSE-SKIP-BLANKS
418 ( -- )
419 skip all chars with codes <=32.
421 (PARSE-SKIP-COMMENTS)
422 ( allow-multiline? -- )
423 skip all blanks and comments. if multiline skip is not allowed, reaching
424 end of TIB while still waiting for the comment terminator is error.
425 single-line comments are ok, though.
427 PARSE-SKIP-LINE
428 ( -- )
429 advance >IN to the end of TIB.
431 PARSE-NAME
432 ( -- addr count )
433 parse with leading blanks skipping. doesn't copy anything.
434 return empty string on EOL.
436 PARSE
437 ( delim -- addr count TRUE / FALSE )
438 parse without skipping delimiters; never copies anything.
439 as our reader is line-based, returns FALSE on EOL.
440 passing 0 as delimiter skips the whole line, and always returns FALSE.
441 finishing delimiter is always skipped.
443 EMIT
444 ( n -- )
445 print char.
447 XEMIT
448 ( n -- )
449 "safe" char printer. all non-printable chars (including newline and such)
450 will be printed as "?".
452 LASTCR?
453 ( -- bool )
454 was last printed char a newline?
456 LASTCR!
457 ( bool -- )
458 force-set the flag for "LASTCR?" word.
461 ( -- )
462 print newline.
464 SPACE
465 ( -- )
466 print space.
468 SPACES
469 ( n -- )
470 print `n` spaces. if `n` is negative, prints nothing.
472 ENDCR
473 ( -- )
474 prints newline if the last printed char was not a newline.
476 TYPE
477 ( addr count -- )
478 print the string. negative count is ok, in this case the word prints nothing.
480 XTYPE
481 ( addr count -- )
482 the same as "TYPE", but uses "XEMIT".
484 FLUSH-EMIT
485 ( -- )
486 output can be buffered. it usually flushed when newline is printed, but
487 you can flush it manually using this word.
490 ( a b -- a+b )
493 ( a b -- a-b )
496 ( a b -- a*b )
499 ( a b -- a*b )
502 ( a b -- a/b )
505 ( a b -- a/b )
508 ( a b -- a%b )
510 UMOD
511 ( a b -- a%b )
513 /MOD
514 ( a b -- a/b, a%b )
515 note that the results are swaped, contrary to ANS idiocity.
516 i don't fuckin' know why ANS morons decided to make the stack
517 effect that contradicts the word name. "/MOD" clearly indicates
518 that quotient comes first.
520 U/MOD
521 ( a b -- a/b, a%b )
522 note that the results are swaped, contrary to ANS idiocity.
523 i don't fuckin' know why ANS morons decided to make the stack
524 effect that contradicts the word name. "/MOD" clearly indicates
525 that quotient comes first.
528 ( a b c -- a*b/c )
529 this uses 64-bit intermediate value.
532 ( a b c -- a*b/c )
533 this uses 64-bit intermediate value.
535 */MOD
536 ( a b c -- a*b/c a*b%c )
537 this uses 64-bit intermediate value.
538 note that the results are swaped, contrary to ANS idiocity.
539 i don't fuckin' know why ANS morons decided to make the stack
540 effect that contradicts the word name. "/MOD" clearly indicates
541 that quotient comes first.
544 ( a b c -- a*b/c )
545 this uses 64-bit intermediate value.
548 ( a b -- lo(a*b) hi(a*b) )
549 this leaves 64-bit result.
552 ( a b -- lo(a*b) hi(a*b) )
553 this leaves 64-bit result.
555 M/MOD
556 ( alo ahi b -- a/b a%b )
557 note that the results are swaped, contrary to ANS idiocity.
558 i don't fuckin' know why ANS morons decided to make the stack
559 effect that contradicts the word name. "/MOD" clearly indicates
560 that quotient comes first.
562 UM/MOD
563 ( alo ahi b -- a/b a%b )
564 note that the results are swaped, contrary to ANS idiocity.
565 i don't fuckin' know why ANS morons decided to make the stack
566 effect that contradicts the word name. "/MOD" clearly indicates
567 that quotient comes first.
570 ( a b -- a<b )
573 ( a b -- a<b )
576 ( a b -- a>b )
579 ( a b -- a>b )
582 ( a b -- a<=b )
585 ( a b -- a<=b )
588 ( a b -- a>=b )
591 ( a b -- a>=b )
594 ( a b -- a=b )
597 ( a b -- a<>b )
600 ( a -- !a )
602 LAND
603 ( a b -- a&&b )
604 logical "and".
607 ( a b -- a||b )
608 logical "or".
611 ( a b -- a&b )
612 bitwise "and".
615 ( a b -- a|b )
616 bitwise "or".
619 ( a b -- a^b )
620 bitwise "xor".
622 BITNOT
623 ( a -- ~a )
626 ( u -- u*2 )
629 ( u -- u*2 )
632 ( u -- u*4 )
635 ( u -- u*4 )
638 ( n count -- )
639 arithmetic shift; positive `n` shifts to the left.
642 ( n count -- )
643 logical shift; positive `n` shifts to the left.
645 COMPILER:(UNESCAPE)
646 ( addr count -- addr new-count )
647 process string escapes. modifies string in-place. the resulting string is
648 never bigger than the source one. negative counts are allowed.
650 (BASED-NUMBER)
651 ( addr count allowsign? base -- num TRUE / FALSE )
652 tries to convert the given string to the number, using the given
653 default base. if "allowsign?" is non-zero, properly process leading
654 number sign. this words understands numbers in non-default bases too
655 (like "0x29a", for example).
659 switch to interpretation mode.
662 switch to compilation mode.
664 (CREATE-WORD-HEADER)
665 ( addr count word-flags -- )
666 create word header in the dictionary, link word to the current vocabulary.
667 doesn't create CFA.
669 (CREATE-NAMELESS-WORD-HEADER)
670 ( word-flags -- )
671 create nameless word header in the dictionary, link word to the current vocabulary.
672 doesn't create CFA.
674 FIND-WORD
675 ( addr count -- cfa TRUE / FALSE)
676 general word finder. checks wordlist stack, performs colon resolution.
678 (FIND-WORD-IN-VOC)
679 ( addr count vocid allowhidden? -- cfa TRUE / FALSE)
680 find word in the given wordlist. does no name resolution, and
681 doesn't look in parent wordlists.
683 FIND-WORD-IN-VOC
684 ( addr count vocid -- cfa TRUE / FALSE)
685 find word in the given wordlist. does no name resolution, and
686 doesn't look in parent wordlists. skips hidden words.
688 (FIND-WORD-IN-VOC-AND-PARENTS)
689 ( addr count vocid allowhidden? -- cfa TRUE / FALSE)
690 find word in the given wordlist. does no name resolution, but searches
691 parent wordlists if "vocid" is nested.
693 FIND-WORD-IN-VOC-AND-PARENTS
694 ( addr count vocid -- cfa TRUE / FALSE)
695 find word in the given wordlist. does no name resolution, but searches
696 parent wordlists if "vocid" is nested. skips hidden words.
698 COMPILER:?EXEC
699 check if we are in interpretation mode, and throws an error if we aren't.
701 COMPILER:?COMP
702 check if we are in compilation mode, and throws an error if we aren't.
705 string literal.
707 (VSP@)
708 ( -- vsp )
709 this word is used internally to work with wordlist stack.
711 (VSP!)
712 ( vsp -- )
713 this word is used internally to work with wordlist stack.
715 (VSP-AT@)
716 ( idx -- value )
717 this word is used internally to work with wordlist stack.
719 (VSP-AT!)
720 ( value idx -- )
721 this word is used internally to work with wordlist stack.
723 CFA->PFA
724 ( cfa -- pfa )
726 PFA->CFA
727 ( pfa -- cfa )
729 CFA->NFA
730 ( cfa -- nfa )
732 NFA->CFA
733 ( nfa -- cfa )
735 CFA->LFA
736 ( cfa -- lfa )
738 LFA->CFA
739 ( lfa -- cfa )
741 LFA->PFA
742 ( lfa -- pfa )
744 LFA->BFA
745 ( lfa -- bfa )
747 LFA->SFA
748 ( lfa -- sfa )
750 LFA->NFA
751 ( lfa -- nfa )
753 NFA->LFA
754 ( nfa -- lfa )
756 CFA->WEND
757 ( cfa -- wend-addr )
758 convert CFA to word end address.
760 DEBUG:IP->NFA
761 ( ip -- nfa / 0 )
762 convert instruction pointer to NFA. return 0 if cannot.
764 DEBUG:IP->FILE/LINE
765 ( ip -- addr count line TRUE / FALSE )
766 name is at PAD; it is safe to use PAD, because each task has its
767 own temp image.
769 DEBUG:IP->FILE-HASH/LINE
770 ( ip -- len hash line TRUE / FALSE )
771 return unique file hash and name length instead of string name.
772 used in debugger.
774 STRING:=
775 ( a0 c0 a1 c1 -- bool )
777 STRING:=CI
778 ( a0 c0 a1 c1 -- bool )
779 case-insensitive compare (only for ASCII).
781 STRING:HASH
782 ( addr count -- hash )
784 STRING:HASH-CI
785 ( addr count -- hash )
786 case-insensitive hash (only for ASCII).
788 ($DEFINE)
789 ( addr count -- )
790 add new conditional define. case-insensitive (for ASCII).
792 ($UNDEF)
793 ( addr count -- )
794 remove conditional define. case-insensitive (for ASCII).
796 ($DEFINED?)
797 ( addr count -- bool )
798 check if we have a conditional define. case-insensitive (for ASCII).
800 ERROR
801 ( addr count -- )
802 print error message and abort.
804 ?ERROR
805 ( errflag addr count -- )
806 if "errflag" is not zero, print error message and abort.
808 ?NOT-ERROR
809 ( errflag addr count -- )
810 if "errflag" is zero, print error message and abort.
812 (INCLUDE-DEPTH)
813 ( -- depth )
814 return number of items in the include stack.
816 (INCLUDE-FILE-ID)
817 ( isp -- id )
818 isp 0 is current, then 1, etc.
819 each include file has unique non-zero id.
821 (INCLUDE-FILE-LINE)
822 ( isp -- line )
824 (INCLUDE-FILE-NAME)
825 ( isp -- addr count )
826 current file name; at PAD.
828 (INCLUDE)
829 ( addr count soft? system? -- )
830 push current file to the include stack, open a new one. used internally.
832 $INCLUDE "str"
833 immediate word.
835 $INCLUDE-ONCE "str"
836 includes file only once; unreliable on shitdoze, i believe.
837 immediate word.
839 HANDLE:NEW
840 ( typeid -- hx )
841 allocate a new handle with the given typeid. typeid is just a number
842 without any special meaning. any number except "-1" is allowed.
843 new handle size is 0.
845 HANDLE:FREE
846 ( hx -- )
847 deallocate a handle, free all allocated handle memory.
848 0 is allowed.
850 HANDLE:TYPEID@
851 ( hx -- typeid )
853 HANDLE:TYPEID!
854 ( typeid hx -- )
856 HANDLE:SIZE@
857 ( hx -- size )
858 0 is allowed.
860 HANDLE:SIZE!
861 ( size hx -- )
862 resize memory allocated for handle data.
864 HANDLE:USED@
865 ( hx -- used )
866 "used" is just a number, which means nothing for most code.
867 it is used to implement dynamic arrays.
868 0 is allowed.
870 HANDLE:USED!
871 ( size hx -- )
873 HANDLE:C@
874 ( idx hx -- value )
876 HANDLE:W@
877 ( idx hx -- value )
879 HANDLE:@
880 ( idx hx -- value )
882 HANDLE:C!
883 ( value idx hx -- value )
885 HANDLE:W!
886 ( value idx hx -- )
888 HANDLE:!
889 ( value idx hx -- )
891 HANDLE:LOAD-FILE
892 ( addr count -- stx / FALSE )
893 load file with the given name into newly allocated handle.
894 return 0 (FALSE) if there is no such file.
897 ( -- rega )
898 get address register contents.
901 ( rega -- )
902 set address register contents.
904 A-SWAP
905 ( rega -- olda )
906 swap TOS and the address register.
908 +1>A
909 ( -- )
910 increment the address register.
913 ( -- | rega )
914 copy the address register to the return stack.
917 ( | rega -- )
918 restore the address register from the return stack.
921 ( -- byte )
924 ( -- word )
927 ( -- value )
930 ( byte -- )
933 ( word -- )
936 ( value -- )
938 C@A+
939 ( idx -- byte )
940 safe way to access both dictionary memory, and handle memory.
941 "idx" is used as offset from address register contents.
943 W@A+
944 ( idx -- word )
945 safe way to access both dictionary memory, and handle memory.
946 "idx" is used as offset from address register contents.
949 ( idx -- value )
950 safe way to access both dictionary memory, and handle memory.
951 "idx" is used as offset from address register contents.
953 C!A+
954 ( byte idx -- )
955 safe way to access both dictionary memory, and handle memory.
956 "idx" is used as offset from address register contents.
958 W!A+
959 ( word idx -- )
960 safe way to access both dictionary memory, and handle memory.
961 "idx" is used as offset from address register contents.
964 ( value idx -- )
965 safe way to access both dictionary memory, and handle memory.
966 "idx" is used as offset from address register contents.
968 DEBUG:(DECOMPILE-CFA)
969 ( cfa -- )
971 GET-MSECS
972 ( -- u32 )
974 (UFO-INTERPRET-FINISHED-ACTION)
975 ( -- )
976 this is called by main loop when it is out of input stream. internally,
977 it simply sets a flag to tell the VM that it should stop.
979 (UFO-INTERPRET-NEXT-LINE)
980 ( -- continue? )
981 default word used to read next input line. return FALSE to exit from
982 "INTERPRET".
984 (INTERPRET-PARSE-NAME)
985 ( -- addr count / FALSE )
986 called by INTERPRET to read next word from the input stream. calls
987 "(INTERPRET-NEXT-LINE)" to refill lines. return FALSE (without address)
988 to exit from "INTERPRET", or next parsed word.
990 (USER-INTERPRET-NEXT-LINE)
991 user variable, holds address of "get next line" word. default value is
992 CFA of "(UFO-INTERPRET-NEXT-LINE)".
994 (INTERPRET-NEXT-LINE)
995 ( -- continue? )
996 peek "(USER-INTERPRET-NEXT-LINE)" and call read CFA.
998 HERE
999 ( -- dp )
1000 push current dictionary pointer to the data stack.
1001 NOTE: there are actually two DPs -- normal, and temporary. "(DP-TEMP)" is
1002 the temp one, and if it is 0, "(DP)" is used. UrForth has 1MB temp area
1003 (that's where PAD is too), it had different addresses, and vocabularies
1004 created in that area are not linked to the main voclink list. this is used,
1005 for example, in locals engine, to store names of locals. so if you're using
1006 locals in your word, do not use temp area while compiling that word.
1008 LATEST-LFA
1009 ( -- lfa )
1010 push LFA of the latest defined word in the current vocabulary. note that
1011 "smudge" bit doesn't matter here, it is always the last word you created
1012 header for. this includes "nonamed" words (which have empty string as a name).
1014 NOOP
1015 ( -- )
1016 does nothing. at all.
1018 COMPILER:(CTLID-COLON)
1019 ( -- ctlid-colon )
1020 semicolon expects this on the data stack.
1022 ' <name>
1023 ( -- cfa )
1024 find word, push its CFA to the data stack. note that the tick
1025 is NOT immediate. use "[']" if you need to compile next word CFA.
1028 start new word definition.
1031 end new word definition.
1033 ALIAS oldword newword
1034 ( -- )
1035 "newword" will do exactly the same as "oldword". word attributes
1036 will be copied too (hidden, immediate, etc.).
1038 LATEST-CFA
1039 ( -- cfa )
1041 LATEST-PFA
1042 ( -- pfa )
1044 LATEST-NFA
1045 ( -- nfa )
1047 LATEST-SFA
1048 ( -- sfa )
1050 ~AND
1051 ( a b -- a&~b )
1053 SWAP!
1054 ( addr value -- )
1057 ( value addr -- )
1059 ~AND!
1060 ( value addr -- )
1062 XOR!
1063 ( value addr -- )
1065 IMMEDIATE
1066 mark last defined word as immediate (or remove immediate mark if it is already set).
1068 (HIDDEN)
1069 mark last defined word as hidden. DO NOT USE. this is obsolete feature,
1070 and it will be removed. it is here for compatibility with my other Forth system.
1072 (PUBLIC)
1073 the opposite of "(HIDDEN)".
1075 -FIND-REQUIRED
1076 alias for the tick.
1078 PARSE-SKIP-COMMENTS
1079 ( -- )
1080 skip all comments and blanks, multiline mode.
1082 PARSE-SKIP-LINE-COMMENTS
1083 skip all comments and blanks, single line mode.
1085 (SET-DEF-WORD-FLAGS)
1086 ( flg -- )
1087 add (OR) default flag for new words.
1088 word flags are:
1089   (WFLAG-IMMEDIATE)
1090   (WFLAG-SMUDGE)
1091   (WFLAG-NORETURN)
1092   (WFLAG-HIDDEN)
1093   (WFLAG-CBLOCK)
1094   (WFLAG-VOCAB)
1095   (WFLAG-SCOLON)
1096   (WFLAG-PROTECTED)
1098 (RESET-DEF-WORD-FLAGS)
1099 ( flg -- )
1100 remove (~AND) default flag for new words.
1102 <PUBLIC-WORDS>
1103 ( -- )
1104 all following words will be public.
1106 <HIDDEN-WORDS>
1107 ( -- )
1108 all following words will be hidden.
1110 <PROTECTED-WORDS>
1111 ( -- )
1112 all following words will be protected. you cannot redefine
1113 protected words.
1115 <UNPROTECTED-WORDS>
1116 ( -- )
1117 all following words will not be protected.
1119 ONLY
1120 ( -- )
1121 clear the wordlist stack.
1123 ALSO
1124 ( -- )
1125 push context vocabulary onto the wordlist stack.
1127 PREVIOUS
1128 ( -- )
1129 pop vocabulary from the wordlist stack, and make in context.
1131 DEFINITIONS
1132 ( -- )
1133 make context vocabulary also current. "current" is the vocabulary
1134 that will receive new word definitions. "context" is the vocabulary
1135 that will be used to search words.
1138 ( a -- a+1 )
1141 ( a -- a+2 )
1144 ( a -- a+2 )
1147 ( a -- a-1 )
1150 ( a -- a-2 )
1153 ( a -- a-2 )
1156 ( n -- n==0 )
1159 ( n -- n<>0 )
1162 ( n -- n==0 )
1165 ( n -- n==0 )
1168 ( n -- n<>0 )
1171 ( n -- n<>0 )
1173 NOTNOT
1174 ( a -- !!a )
1177 ( a -- |a| )
1179 SIGN?
1180 ( n -- -1|0|1 )
1182 NEGATE
1183 ( n -- -n )
1185 LSHIFT
1186 ( n count -- n )
1188 RSHIFT
1189 ( n count -- n )
1191 ARSHIFT
1192 ( n count -- n )
1195 ( n count -- n )
1198 ( n count -- n )
1201 ( n count -- n )
1204 ( n count -- n )
1206 LO-WORD
1207 ( a -- a&0xffff )
1209 HI-WORD
1210 ( a -- [a>>16]&0xffff )
1212 LO-BYTE
1213 ( a -- a&0xff )
1215 HI-BYTE
1216 ( a -- [a>>8]&0xff )
1219 ( addr -- )
1222 ( addr -- )
1225 ( n addr -- )
1228 ( n addr -- )
1231 ( addr -- )
1234 ( addr -- )
1236 BCOUNT
1237 ( addr -- addr+1 count )
1239 COUNT
1240 ( addr -- addr+4 count )
1243 ( -- )
1245 DECIMAL
1246 ( -- )
1248 OCTAL
1249 ( -- )
1251 BINARY
1252 ( -- )
1254 WITHIN
1255 ( value a b -- value>=a&&value<b )
1257 UWITHIN
1258 ( value a b -- value>=a&&value<b )
1260 BOUNDS?
1261 ( value a b -- value>=a&&value<=b )
1262 numbers are unsigned.
1264 (HANDLE-ADDR?)
1265 ( addr -- )
1266 check if the given addres is actually a handle.
1268 COMPILER:SET-SMUDGE
1269 ( -- )
1270 set "smudge" bit for the latest word.
1272 COMPILER:RESET-SMUDGE
1273 ( -- )
1274 reset "smudge" bit for the latest word.
1276 COMPILER:SET-WARG
1277 ( warg -- )
1278 set argument type for the latest word. each word has "argument type" field,
1279 which inditates word argument type in the compiled code. arguments are:
1280   (WARG-NONE)
1281   (WARG-BRANCH)
1282   (WARG-LIT)
1283   (WARG-C4STRZ)
1284   (WARG-CFA)
1285   (WARG-CBLOCK)
1286   (WARG-VOCID)
1287   (WARG-C1STRZ)
1289 (WARG-MASK)
1290 ( -- mask )
1291 this mask can be used to get only argument type bits from the first NFA cell.
1293 COMPILER:(GET-NEW-WORD-FLAGS)
1294 ( -- flags )
1295 get sanitized new word flags. currently, only "hidden" and "protected" flags
1296 are retained, all other flags will be reset.
1298 COMPILER:(CREATE-HEADER)
1299 ( addr count -- )
1300 create new named word header with the default flags. additionally, sets
1301 "smudge" flag on the new word.
1303 COMPILER:(CREATE-NAMELESS)
1304 ( -- cfa )
1305 create new nameless word header with the default flags. additionally, sets
1306 "smudge" and "hidden" flags on the new word.
1307 return CFA address of the new word. CFA contents is not filled yet.
1309 COMPILER:(MK-CONST-VAR)
1310 ( value cfaidx -- )
1311 don't bother using this.
1313 COMPILER:FORTH-WORD?
1314 ( cfa -- bool )
1315 check if the given word is normal Forth word (i.e. defined with the colon).
1317 COMPILE
1318 ( cfa -- )
1319 compiles CFA to be executed.
1321 use the following words to compile branch destinations. this way your code
1322 will be independent of branch instruction operand format.
1324 ;; usage:
1325 ;;  compile (0branch)
1326 ;;  (mark>)
1327 ;;  ...
1328 ;;  (resolve>)
1330 ;;  (<mark)
1331 ;;  ...
1332 ;;  compile (branch)
1333 ;;  (<resolve)
1335 COMPILER:(BRANCH-ADDR!)
1336 ( destaddr addr -- )
1337 write "branch to destaddr" address to addr.
1339 COMPILER:(BRANCH-ADDR@)
1340 ( addr -- dest )  @ ;
1341 read branch address.
1344 COMPILER:(<J-MARK)
1345 ( -- addr )
1346 return addr suitable for "(<J-RESOLVE)".
1348 COMPILER:(<J-CHAIN)
1349 ( addr -- addr )
1350 use after "(<J-MARK)" to reserve jump and append it to jump chain.
1352 COMPILER:(<J-RESOLVE)
1353 ( addr -- )
1354 patch "forward jump" address to HERE. "addr" is the result of "(<J-MARK)".
1356 COMPILER:(MARK-J>)
1357 reserve room for branch address, return addr suitable for "(RESOLVE-J>)".
1359 COMPILER:(CHAIN-J>)
1360 use after "(MARK-J>)" to reserve jump and append it to jump chain.
1362 COMPILER:(RESOLVE-J>)
1363 ( addr -- )
1364 compile "forward jump" (possibly chain) from address to HERE. addr is the
1365 result of "(MARK-J>)". this resolves the whole "jump chain".
1368 COMPILER:?PAIRS
1369 ( a b -- )
1370 throw error if a <> b.
1372 ?2PAIRS
1373 ( a b c -- )
1374 throw error if a <> b and a <> c.
1376 LITERAL
1377 ( C:n -- )
1378 ( E:n -- n )
1379 compile number from the data stack as literal. NOT IMMEDIATE.
1381 IMM-LITERAL
1382 ( C:n -- )
1383 ( E:n -- n )
1384 immediate version of "LITERAL".
1386 STRLITERAL
1387 ( C:addr count -- )
1388 ( E: -- addr count )
1390 IMM-STRLITERAL
1391 immediate version of the previous word.
1393 CFALITERAL
1394 ( C:cfa -- )
1395 ( E:cfa -- cfa )
1397 IMM-CFALITERAL
1398 ( C:cfa -- )
1399 ( E:cfa -- cfa )
1401 [COMPILE] <wordname>
1402 force the next word to be compiled as normal word, even if it is an immediate one.
1405 compile next word CFA as CFA literal.
1407 COMPILER:(COMPILE-CFA-LITERAL)
1408 ( cfa -- )
1409 compile cfa literal to be compiled. ;-)
1411 COMPILER:END-COMPILE-FORTH-WORD
1412 ( -- )
1413 push colon ctlid and call ";".
1416 COMPILE <wordname>
1417 compile next word to the currently defining word.
1419 [CHAR] <char>
1420 ( -- ch )
1421 push/compile first char of the next word as char code.
1422 note that words with more than one char will cause an error.
1424 RECURSE
1425 recursively call the currently defining word. this is required
1426 due to currently defining word being invisible yet (because it
1427 is not finished).
1429 RECURSE-TAIL
1430 tail-call recursion.
1432 CONSTANT <name>
1433 ( value -- )
1434 create new constant.
1436 VARIABLE <name>
1437 ( value -- )
1438 create new variable.
1440 (CREATE)
1441 ( addr count -- )
1442 this is what "CREATE" is using to create a new word.
1444 CREATE <name>
1445 ( -- )
1446 create new word. when executed, this new word will push its PFA.
1447 note that new word is not smudged.
1449 CREATE;
1450 ( -- )
1451 finish CREATEd word. this is required to correctly set SFA.
1452 note that "DOES>" automatically takes care of SFA, so you don't have
1453 to call this if you're using "DOES>".
1455 (DOES>)
1456 ( doer-addr -- )
1457 patch CREATEd word. put doer address to its CFA, VM will do the rest.
1458 this is used internally by the compiler.
1460 (SET-DOER)
1461 ( doer-pfa cfa -- )
1462 makes CFA word to execute "doer-pfa" as doer.
1463 this is used internally by the compiler. do not try to understand this.
1465 DOES>
1466 ( -- )  ( pfa )
1467 the usual Forth "CREATE" -- "DOES>" support.
1469 4 CONSTANT CELL
1470 ANS idiocity.
1472 ALIAS 4U* CELLS  ( n -- n*cells )
1473 ANS idiocity.
1475 ALIAS 4+  CELL+  ( n -- n+cell )
1476 ANS idiocity.
1478 ALIAS 4-  CELL-  ( n -- n-cell )
1479 ANS idiocity.
1481 +CELLS
1482 ( a n -- a+n*cells )
1483 ANS idiocity.
1485 -CELLS
1486 ( a n -- a+n*cells )
1487 ANS idiocity.
1489 .( text)
1490 immediately print the text.
1492 ." text"
1493 compile text printer.
1495 N-ALLOT
1496 ( n -- stard-addr )
1497 allocate n *bytes* in the current DP, return the address of
1498 the first allocated byte.
1500 ALLOT
1501 ( n -- )
1502 allocate n *bytes* in the current DP.
1504 ALIGN-HERE
1505 ( -- )
1506 align DP to 4-byte boundary.
1508 COMPILER:(NEW-WORDLIST)
1509 ( parentvocid need-hashtable? -- vocid )
1510 create new empty wordlist.
1512 COMPILER:(CREATE-NAMED-VOCAB)
1513 ( vocid addr count -- )
1514 create vocabulary word.
1516 COMPILER:(CREATE-VOCAB) <vocname>
1517 ( vocid -- )
1518 create vocabulary word.
1520 COMPILER:(IS-VOC-WORD?)
1521 ( cfa -- bool )
1522 check if the given CFA defined as a vocabulary header.
1524 COMPILER:(WORD->VOCID)
1525 ( cfa -- vocid )
1526 get vocid from the vocabulary word. doesn't check arguments.
1528 COMPILER:(VOCID-PARENT@)
1529 ( vocid -- vocid )
1530 get vocid parent vocabulary. return 0 if there is no parent.
1531 doesn't check arguments.
1533 COMPILER:(VOCID-PARENT!)
1534 ( parent-vocid vocid -- )
1535 set vocid parent vocabulary. doesn't check arguments.
1537 COMPILER:(VOCID-TYPEID@)
1538 ( vocid -- typeid )
1539 internal helper for STRUCT support.
1541 COMPILER:(VOCID-TYPEID!)
1542 internal helper for STRUCT support.
1544 (VOCABULARY-EX)
1545 ( addr count parent need-hashtbl? -- )
1546 useful low-level words to create vocabs with already parsed names.
1548 (VOCABULARY)
1549 ( addr count -- )
1551 (SIMPLE-VOCABULARY)
1552 ( addr count -- )
1553 creates vocabulary without a hash table.
1555 (NESTED-VOCABULARY)
1556 ( addr count -- )
1558 (SIMPLE-NESTED-VOCABULARY)
1559 ( addr count -- )
1561 VOCABULARY <vocname>
1563 SIMPLE-VOCABULARY <vocname>
1565 NESTED-VOCABULARY <vocname>
1567 SIMPLE-NESTED-VOCABULARY <vocname>
1569 VOCID: <vocname>
1570 ( -- vocid )
1571 return vocid for the given vocabulary. this word is immediate.
1573 VOC-LATEST
1574 ( vocid -- latest )
1575 return latest word LFA for the given vocid.
1577 ALSO-DEFS: <vocname>
1578 ( -- )
1579 this does "ALSO <vocname> DEFINITIONS"
1581 PREV-DEFS
1582 ( -- )
1583 this does "PREVIOUS DEFINITIONS".
1585 VOCAB-IF-NONE <vocname>
1586 create vocabulary if we don't have such word yet.
1588 NESTED-VOCAB-IF-NONE <vocname>
1589 create nested vocabulary if we don't have such word yet.
1591 SIMPLE-VOCAB-IF-NONE <vocname>
1592 create vocabulary if we don't have such word yet.
1594 SIMPLE-NESTED-VOCAB-IF-NONE <vocname>
1595 create nested vocabulary if we don't have such word yet.
1597 -TO  ( n -- )  \ name
1598 decrement value by n.
1600 +TO  ( n -- )  \ name
1601 increment value by n.
1603 -1-TO  ( -- )  \ name
1604 decrement value by 1.
1606 +1-TO  ( -- )  \ name
1607 increment value by 1.
1609 0-TO  ( -- )  \ name
1610 write 0 to value.
1612 ... FORTH:(TO-EXTENDER) ...
1613 ( addr count FALSE -- addr count FALSE / TRUE )
1614 "TO" can be extended to support things it doesn't know about yet.
1615 after parsing a name, "(TO-EXTENDER)" will be called (this is
1616 scattered colon word). note that due to how scattered colon works,
1617 you'd better DON'T use "EXIT", but pass a flag if you need to stop
1618 further processing. also, do not forget to check the flag at the
1619 start of your extender, because some other extender may already
1620 did its work before yours.
1622 ... FORTH:(EXIT-EXTENDER) ...
1623 ( -- )
1624 this scattered colon word allows you to extend "EXIT". "EXIT" is
1625 the immediate word that compiles word leaving instructions. you
1626 can compile your cleanup code before the standard cleanup.
1628 ... FORTH:(INTERPRET-CHECK-WORD) ...
1629 ( addr count FALSE -- addr count FALSE / TRUE )
1630 this is called by INTERPRET before the standard word processing.
1632 ... FORTH:(INTERPRET-WORD-NOT-FOUND) ...
1633 ( addr count FALSE -- addr count FALSE / TRUE )
1634 this is called by INTERPRET when word resolution failed.
1637 UrForth supports cooperative multitasking. it is also used to implement
1638 interactive debugger. tasks are called "execution states", or simply
1639 "states".
1641 MTASK:NEW-STATE
1642 ( cfa -- stid )
1643 create new state, return state id.
1645 MTASK:FREE-STATE
1646 ( stid -- )
1647 free state. state id should be valid, and should not be an active state.
1649 MTASK:STATE-NAME@
1650 ( stid -- addr count )
1651 copy state name to PAD.
1653 MTASK:STATE-NAME!
1654 ( addr count stid -- )
1655 set new state name. maximum name length is 127 chars. state name
1656 should not include char with code 0.
1658 MTASK:STATE-FIRST
1659 ( -- stid )
1660 get first state in the list of all created states. this is used to
1661 iterate over all states.
1662 WARNING! do not mutate state list while iterating! result will be UB.
1664 MTASK:STATE-NEXT
1665 ( stid -- stid / 0 )
1666 get next state id. used to iterate over all states.
1667 WARNING! do not mutate state list while iterating! result will be UB.
1669 MTASK:YIELD-TO
1670 ( ... argc stid -- )
1671 yield to another state. move argc numbers from the current state data
1672 stack to the new state data stack. push args to the new state data
1673 stack, and then push current state id. i.e. new state data stack will
1674 look like this:
1675   ( ... argc old-stid )
1676 it is ok to swith to the currently active state (it is a no-op).
1678 MTASK:SET-SELF-AS-DEBUGGER
1679 ( -- )
1680 register current task as system debugger. you can yeild from the debugger
1681 after this.
1683 DEBUG:(BP)
1684 ( -- )
1685 breakpoint. debugger task receives debugge stid on the data stack,
1686 and `-1` as yield argument count. i.e. debugger stack will be:
1687   ( -1 old-stid )
1689 MTASK:DEBUGGER-RESUME
1690 ( stid -- )
1691 resume debugee execution.
1693 MTASK:DEBUGGER-SINGLE-STEP
1694 ( stid -- )
1695 execute one debuggee instruction, and return to debugger.
1696 this is basically "YIELD", but to use in the debugger
1697 (and it doesn't pass any arguments). debugger stack will be:
1698   ( -2 old-stid )
1700 MTASK:STATE-IP@
1701 ( stid -- ip )
1702 get state instruction pointer.
1704 MTASK:STATE-IP!
1705 ( ip stid -- )
1706 set state instruction pointer.
1708 MTASK:STATE-A>
1709 ( stid -- regA )
1710 get address register contents.
1712 MTASK:STATE->A
1713 ( rega stid -- )
1714 set address register contents.
1716 MTASK:STATE-USER@
1717 ( addr stid -- valie )
1718 get other state user area cell.
1720 MTASK:STATE-USER!
1721 ( value addr stid -- )
1722 set other state user area cell.
1724 MTASK:STATE-RPOPCFA@
1725 ( -- flag )
1726 VM has special mode when it gets next CFA from the return stack
1727 instead of the address pointed by IP. this is used to implement
1728 "EXECUTE", for example. use this word to retrieve that flag.
1730 MTASK:STATE-RPOPCFA!
1731 ( flag -- )
1732 VM has special mode when it gets next CFA from the return stack
1733 instead of the address pointed by IP. this is used to implement
1734 "EXECUTE", for example. use this word to set that flag.
1736 MTASK:ACTIVE-STATE
1737 ( -- stid )
1738 return state id of the currently executing state.
1740 MTASK:YIELDED-FROM
1741 ( -- stid / 0 )
1742 return state which called "MTASK:YIELD-TO" last.
1744 MTASK:STATE-SP@
1745 ( stid -- depth )
1746 get the data stack depth for the given state.
1748 MTASK:STATE-RP@
1749 ( stid -- depth )
1750 get the return stack depth for the given state.
1752 MTASK:STATE-LP@
1753 ( stid -- lp )
1754 get local stack ptr.
1756 MTASK:STATE-LBP@
1757 ( stid -- lbp )
1758 get local stack base ptr.
1760 MTASK:STATE-SP!
1761 ( depth stid -- )
1762 set the data stack depth for the given state.
1764 MTASK:STATE-RP!
1765 ( stid -- depth )
1766 set the return stack depth for the given state.
1768 MTASK:STATE-LP!
1769 ( lp stid -- )
1770 set local stack ptr.
1772 MTASK:STATE-LBP!
1773 ( lbp stid -- )
1774 set local stack base ptr.
1776 MTASK:STATE-DS@
1777 ( idx stid -- value )
1778 read the data stack of the given state. note that the index is bound-checked.
1780 MTASK:STATE-RS@
1781 ( idx stid -- value )
1782 read the return stack of the given state. note that the index is bound-checked.
1784 MTASK:STATE-LS@
1785 ( idx stid -- value )
1786 read the locals stack of the given state. note that the index is bound-checked.
1788 MTASK:STATE-DS!
1789 ( value idx stid -- )
1790 write the data stack of the given state. note that the index is bound-checked.
1791 i.e. if you want to push some value, increase stack depth first.
1793 MTASK:STATE-RS!
1794 ( value idx stid -- )
1795 write the return stack of the given state. note that the index is bound-checked.
1796 i.e. if you want to push some value, increase stack depth first.
1798 MTASK:STATE-LS!
1799 ( value idx stid -- )
1800 write the locals stack of the given state. note that the index is bound-checked.
1801 i.e. if you want to push some value, increase stack depth first.
1804 there are some words to work with TTY (only GNU/Linux).
1806 TTY:TTY?
1807 ( -- bool )
1808 check if input and output are valid TTY(s).
1810 TTY:RAW?
1811 ( -- bool )
1812 check if current TTY mode is raw.
1814 TTY:SIZE
1815 ( -- width height )
1816 get TTY size. for non-TTYs retur default 80x24.
1818 TTY:SET-RAW
1819 ( -- success-bool )
1820 switch TTY to raw mode.
1822 TTY:SET-COOKED
1823 ( -- success-bool )
1824 switch TTY to cooked mode.
1826 TTY:RAW-EMIT
1827 ( n -- )
1828 type char without any filtering or safety nets.
1830 TTY:RAW-TYPE
1831 ( addr count -- )
1832 type string without any filtering or safety nets.
1834 TTY:RAW-FLUSH
1835 ( -- )
1836 the output of the two words above is buffered. this words flushes
1837 the buffer. buffering is done because raw TTY is mostly used to
1838 build user interfaces, and sending accumulated terminal commands
1839 in one big chunk looks much better (most terminal emulators will
1840 process the whole chunk before refreshing their windows).
1842 TTY:RAW-READCH
1843 ( -- ch / -1 )
1844 -1 returned on error, or on EOF.
1845 read one char (without any interpretation) if TTY is in raw mode.
1846 note that 0 is a valid char (it is used to send Ctrl+Space in some
1847 terminal emulators). also note that there is no way to tell if we
1848 hit a EOF, or some error occured. in practice, it doesn't matter,
1849 because in both cases it means that TTY is unusable anymore.
1851 TTY:RAW-READY?
1852 ( -- bool )
1853 check if raw TTY has some data to read.
1856 file i/o words.
1858 FILES:ERRNO
1859 ( -- errno )
1860 last libc `errno`. can be used after failure to inspect error code.
1862 FILES:UNLINK
1863 ( addr count -- success? )
1864 delete file.
1866 FILES:OPEN-R/O
1867 ( addr count -- handle TRUE / FALSE )
1868 open file for reading. `handle` is always positive.
1870 FILES:OPEN-R/W
1871 ( addr count -- handle TRUE / FALSE )
1872 open file for writing. `handle` is always positive.
1874 FILES:CREATE
1875 ( addr count -- handle TRUE / FALSE )
1876 create new file, or truncate existing. `handle` can be any number, including
1877 `0` and negative numbers.
1879 FILES:CLOSE
1880 ( handle -- success? )
1881 close opened file.
1883 FILES:TELL
1884 ( handle -- ofs TRUE / FALSE )
1885 get current file position.
1887 FILES:SEEK-EX
1888 ( ofs whence handle -- TRUE / FALSE )
1889 set current file position. `whence` can be one of "FILES:SEEK-SET",
1890 "FILES:SEEK-CUR", "FILES:SEEK-END".
1892 FILES:SEEK
1893 ( ofs handle -- TRUE / FALSE )
1894 set current file position. the same as calling "SEEK-EX" with `whence`
1895 equal to "SEEK-SET".
1897 FILES:SIZE
1898 ( handle -- size TRUE / FALSE )
1899 get file size. `handle` cannot be 0.
1900 WARNING! on failure on valid handle, file position for that handle is undefined.
1902 FILES:READ
1903 ( addr count handle -- rdsize TRUE / FALSE )
1904 read bytes from file. this word can read less bytes than requirested. `count`
1905 can be 0 (in this case the function always succeeds). note that this function
1906 can read 0 bytes, and this is success too.
1908 FILES:READ-EXACT
1909 ( addr count handle -- TRUE / FALSE )
1910 read bytes from file. reading less then requested number of bytes is error.
1911 `count` can be 0 (in this case the function always succeeds).
1913 FILES:WRITE
1914 ( addr count handle -- TRUE / FALSE )
1915 write bytes from file. writing less bytes than requested is error. `count`
1916 can be 0 (in this case the function always succeeds).