**** alloc-mem.f: A simple memory allocator. Currently, memory must be freed in the reverse order in which it was allocated. init-malloc ( -- ) Must be called before the first call to alloc-mem. Subsequent calls to init-malloc after the first are ignored, so it is okay to call it "just to make sure". alloc-mem ( nbytes -- address ) Allocates nbytes of memory, returning the address of the allocated memory. free-mem ( address nbytes -- ) Frees memory that has been allocated by alloc-mem. Address is the starting address of a buffer "nbytes" long, which be the most recently allocated buffer from alloc-mem. **** sift.f: Defines the word "sift", which prints the names of all dictionary entries whose names contain a given substring. substring? ( str1 str2 -- flag ) Flag is true if str1 is a substring of str2. sindex ( addr1 len1 addr2 len2 -- n ) Finds the position within string 2 where string 1 first occurs. If string 2 doesn't contain string 1, returns -1. For example, if string 1 is "foo" and string 2 is "xyzfoobar", sindex would return 3. sift ( str -- ) Given a packed string, checks the entire dictionary for entries whose name contains that string as a substring. Prints all such names. sifting \ string ( -- ) Like sift but takes the search string from the input stream **** bitfields.f: A package implementing structure which may contain bitfields. Automatically does the shifting and masking necessary to extract and store into such fields. See forth/doc/bitfields.ms for a paper describing the use of this package. bstruct ( -- ) Initiates the definition of a structure containing bitfields. bfield ( offset size -- newoffset ) ( Input stream: field-name ) ( Later: structure-base -- structure-member-address ) Defines a field in a structure. The field should be an integral number of bytes (size) long. It will be allocated starting on the next byte boundary. resbits ( offset #bits -- newoffset ) "Reserves" some bits within a bitfield. Primarily used to skip unused bits. bits ( offset #bits -- newoffset ) ( Input stream: field-name ) ( Later: structure-base -- byte-address bit# #bits ) Defines a bitfield containing #bits within a structure. Later, when that bitfield name is executed, it will translate a structure base address into the address of the byte which contains that bit field, the bit number of the field within that byte, and the number of bits in the field. Bit@ or bit! may then be used to access that bitfield. bit@ ( byte_addr. bit# #bits -- n ) Fetch the value of a bit field. The input arguments are as left by a bitfield word (a word defined by "bits"). Automatically do the shifting and masking necessary to place that bitfield's value on the stack (as "n") so that it is in the least-significant position within the stack item. bit! ( n byte_addr. bit# #bits -- ) Store the stack item "n" into a bitfield. The input arguments byte_addr, bit#, and #bits are as left by a bitfield word (a word defined by "bits"). Automatically do the shifting and masking necessary to store the least-significant portion of the stack item into the bitfield. **** iftrue.f: Conditionals that work both when interpreting and when compiling. May be used for conditionally-compiling source code. Completely nestable. iftrue ( [ flag ] -- ) I Begin an IFTRUE ... OTHERWISE ... IFEND conditional sequence. These conditional words operate like IF ... ELSE ... THEN except that they may be used during interpretation. They may be used within a colon definition to control compilation, but the flag that is tested by IFTRUE has to be left on the stack at at compile time, so the code that generates the flag should be enclosed in brackets ( [ and ] ). In this implementation, these words are completely nestable. otherwise ( -- ) Used within in an IFTRUE ... OTHERWISE ... IFEND conditional sequence. The OTHERWISE is optional. See: IFTRUE ifend ( -- ) Terminate an IFTRUE ... OTHERWISE ... IFEND conditional sequence. See: IFTRUE **** callfinder.f: Finds all places in the system where a particular word is used. Also prints a formatted trace of the contents of the return stack. rstrace ( -- ) ( Return stack backtrace) Prints a formatted trace of the contents of the return stack. First checks for return stack underflow so the printout won't go off into Never-Never Land. .calls ( cfa -- ) Given the compilation address of some Forth word, finds all places in the dictionary where that word is used, and prints the names of the words which use it. **** compare.f: compare ( addr0 addr1 cnt --- diff-addr0 diff-addr1 cnt' | 0 ) **** cutil.f: Some numeric operators which are nice to have available. lnot ( lnum -- ~lnum ) Logical inversion (one's complement) for 32-bit numbers. cnot ( char -- ~char ) Logical inversion (one's complement) for bytes. Affects only the least-significant byte of the operand. << ( num cnt -- num<> ( num cnt -- num>>cnt ) Logical right shift num by cnt places. Zeroes are shifted into the most-significant bits. <>a ( num cnt -- num>>cnt ) Arithmetic right shift num by cnt places. The sign bit is shifted into the most-significant bits. l<< ( d cnt -- d<> ( d cnt -- d>>cnt ) Same as >>. The operand is explicitly a 32-bit number, but since the stack size in Sun Forth is 32-bits anyway, this is the same as >>. l<>a ( d cnt -- d>>cnt ) Same as >>a. The operand is explicitly a 32-bit number, but since the stack size in Sun Forth is 32-bits anyway, this is the same as >>a. **** decompiler.f: Reconstructs Forth source code from already-compiled forth binary code. Works on high-level Forth code only - can't reconstruct assembler source code. Doesn't do a perfect job, especially for words defined by other "create does>" words, but is pretty good. ((see ( cfa -- ) Decompiles the word whose cfa is on the stack. see ( -- ) ( Input stream: name-of-word ) Decompiles the word whose name is next in the input stream. **** dump83.f: Formatted hex/ascii memory dump. dump ( addr len -- ) Dumps memory locations starting at addr and extending for len bytes. The dump always starts on a 16-byte boundary, so up to 15 extra bytes than called-for may be dumped. The output is formatted nicely. The first byte asked for (addr) is indicated by a "\/" in the heading column above that byte. The right-hand side of the dump shows the values of the bytes in hex. The right-hand side of the dump shows the values of the bytes in ascii. Non-printing ascii characters display as "." du ( addr -- addr+64 ) Like dump, but assumes a length of 64. Also leaves the next address after the dump on the stack, so successive du's will scan through memory. **** emacs-line-edit.f: A powerful editor for editing Forth command lines as they are typed. The semantics and key bindings are patterned after Gosling's Emacs. This is not configured into the normal Unix version of Forth, but may be loaded if desired. Look at the Makefile entry for lineedit.exe in forth/kernel.dir. It is normally configured into the stand-alone version of Forth. For more information, there is a paper about this editor in forth/doc/cmd-cpl.ms The editor is extensible and user-configurable. forward-character ^F Advance the cursor to the next character in the line. backward-character ^B Move the cursor back to the previous character in the line. erase-next-character ^D Delete the character under the cursor. erase-previous-character ^H Delete the character to the left of the cursor. insert-character all printing characters Insert the character into the line at the cursor position, moving the rest of the line over to make room. beginning-of-line ^A Move the cursor to the beginning of the line. end-of-line ^E Move the cursor to the end of the line. finish-line ^M (carriage return) Finished with editing the line. Give the line to the Forth interpreter. kill-to-end-of-line ^K Delete all the characters from the cursor position to the end of the line. grab-last-line ESC-= ^P Insert a copy of the previously-typed line into the current line at the cursor position. In some versions, only works at the first of the line before any other characters are typed. retype-line ^L Retypes the current line on the screen. Useful if the line gets garbled for some reason. erase-previous-word ESC-h Erases the word immediately to the left of the cursor position. A word is a sequence of non-blank characters. erase-next-word ESC-d Erases the word immediately to the right of the cursor position. A word is a sequence of non-blank characters. forward-word ESC-f Moves the cursor to the beginning of the word to the right of the cursor position. backward-word ESC-b Moves the cursor to the beginning of the word to the left of the cursor position. quote-next-character ^Q Turns off any special meaning for the next character typed, and inserts it into the line. vocabulary keys-forth Vocabulary where keys are bound to functions. A key may be bound simply by including a definition in keys-forth like: : ^U beginning-of-line kill-to-end-of-line ; In the definition, the name ^U is typed a two characters -- a circumflex (^) and an upper case U. Escape may be typed as ^[. Already-bound keys may be rebound in the same fashion. The most recent definition takes precedence. Instead of using the full function name, it is okay to use the keystroke name, as in: : ^X ^E ^[ ; nuser keys ' keys-forth keys ! A variable which contains the compilation address of the vocabulary to be used as the key-binding vocabulary. The system sets it's initial value to keys-forth. The entire key map may be changed by changing this variable to some other vocabulary. defer not-found ' beep is not-found Deferred word which is executed when a control character or escape sequence is typed, but is not defined in the keys vocabulary. Normally set to beep the terminal. defer printable-char ' insert-character is printable-char Deferred word which is executed when a printable character is typed. Normally set to "insert-cahracter", which puts the character into the line being typed. (newexpect (s adr len -- ) Replacement for the normal Forth "expect" routine. (newexpect implements the line editor. The normal expect has only a very limited editing capability, basically just "erase-previous-character" and "erase-entire-line". Default Bindings: only forth also keys-forth definitions ^F forward-character ; ^B backward-character ; ^A beginning-of-line ; ^E end-of-line ; ^D erase-next-character ; ^H erase-previous-character ; ^K kill-to-end-of-line ; ^M finish-line ; ^J finish-line ; ^Q quote-next-character ; ^L retype-line ; ^[ key lastchar c! do-command ; ^[h erase-previous-word ; ^[d erase-next-word ; ^[f forward-word ; ^[b backward-word ; ^[= grab-last-line ; emacs-edit ( -- ) Starts the line editor by replacing the normal expect routine with (newexpect, and setting some terminal modes appropriately (no echo, wakeup on all characters, etc) **** cmd-cpl.f: Implements a Tenex-style command completion package, whereby the user doesn't have to type all of a word. He just types the first few characters and the system completes the word for him if the system can figure out which word he meant. See forth/doc/cmd-cpl.ms for a paper describing the system. expand-word ( -- ) Executing this (it is usually bound to a control character like control J) causes the system to try to complete the word just to the left of the cursor. If the word can be completed, the entire word is printed on the command line followed by a space. If the word can't be completed, the system completes it as far as possible (until it is ambiguous which word was meant) and then beeps. This should only be called from within the keyboard processing code. do-show ( max-len bufstart current-cnt char -- ... ) The system prints the names of all words which are possible expansions of the word to the left of the cursor. This is useful if you tried to do an "expand-word" and the system beeped at you. ^J expand-word ; Control J is the usual binding for "expand-word". ^_ do-show ; Control _ is the usual binding for "do-show". On some terminals, you may have to type control ? to get this character. **** exceptions.f: An exception-handling package similar to that provided by Ada. Any number of named exceptions may be created. An exception handler for any exception may be installed at any place in the code. Exception handlers may be nested. When a routine that has installed an exception handler exits, that handler is deactivated, which restores control of that exception to a handler that was installed at a higher level. An exception may be "raised" at any point, triggering the handler for that exception which is currently in control. If no handler has been installed, the program aborts. exception: \ name ( -- ) \ Child: ( -- exception ) Used in the form: EXCEPTION: Creates a new named exception. When name is later executed, a number which identifies that exception is left on the stack. raise ( exception -- ) Triggers the current handler for the indicated exception. create uncaught ( exception -- ) If an exception is raised, but no handler is there to catch it, uncaught gets executed. It prints the message: Exception raised then quits to the interpreter. catch? ( exception -- f) Installs a handler for the indicated exception. This word returns false when it is called, but if the exception is subsequently raised, control will be returned to a point just after this word, with a true on the stack. This is called "catching the exception", and does not remove this handler. uncatch ( exception -- ) Explicitly removes an exception frame (handler). Since exception frames are automatically removed when the word which installed them exits, this is usually not necessary. However, sometimes a handler might want to also propagate the exception to the next higher handler. This may be done by 'uncatch'ing the exception then raising it. An example showing how to use exceptions may be found in forth/test.dir/test-exceptions.f **** ext-add.f: Words for writing forth programs which execute identically on machines with different word sizes (16 bit or 32 bit) and possibly different address sizes (16 bit or 32 bit). The following notation is used: n means the size of an entry on the parameter stack c means an 8 bit byte w means a 16 bit word l means a 32 bit longword For more information, see pi:/usr/wmb/forth/ext-add.ms This particular file is appropriate for a Forth system with 16 bit stacks and 16 bit addresses. These words have already been built-in to the 32 bit kernel, so there is no need for a corresponding file for the 32 bit Forth system. Words for accessing different size memory items: c@ ( addr -- byte ) w@ ( addr -- wnum ) l@ ( addr -- lnum ) c! ( byte addr -- ) w! ( wnum addr -- ) l! ( lnum addr -- ) Words for accessing memory items using 32 bit addresses: c@l ( laddr -- byte ) w@l ( laddr -- wnum ) l@l ( laddr -- lnum ) c!l ( byte laddr -- ) w!l ( wnum laddr -- ) l!l ( lnum laddr -- ) Words for accessing memory items using 16 bit addresses: c@w c@ ; w@w w@ ; l@w l@ ; c!w c! ; w!w w! ; l!w l! ; Variables and constants with explicit sizes: lvariable create 4 allot ; lconstant create , , wvariable create 2 allot ; wconstant create , Constants leaving the number of bytes in a particular type: 1 constant /c 2 constant /w 4 constant /l 2 constant /n Words for indexing into arrays composed of particular types: na+ ( addr index -- addr ' ) ca+ ( addr index -- addr' ) wa+ ( addr index -- addr' ) la+ ( addr index -- addr' ) Words for incrementing a pointer to a particular type: na1+ ( addr -- addr' ) ca1+ ( addr -- addr' ) wa1+ ( addr -- addr' ) la1+ ( addr -- addr' ) 32-bit ( -- ) I Verify the system is 32 bits 16-bit ( -- ) I Verify the system is 16 bits (aborts) 32\ ( -- ) I Ignore line if not a 32-bit system 16\ ( -- ) I Ignore line if not a 16-bit system l+! ( l addr -- ) Increment a longword variable lnover ( l n -- l n l ) Copy a longword over a "normal" nlover ( n l -- n l n ) Copy a "normal" over a longword lswap ( l1 l2 -- l2 l1 ) Swap longwords l= ( l1 l2 -- flag ) Compare longwords for equality l< ( l1 l2 -- flag ) Compare longwords l>= ( l1 l2 -- flag ) Compare longwords lbetween ( l1 l2 l3 -- flag ) Longword range check lwithin ( l1 l2 l3 -- flag ) Longword range check lliteral ( l1 -- ) ( Later: -- l1 ) Compile longword literal land ( l1 l2 -- l3 ) Longword logical and w->l ( w -- l ) Convert word to longword **** format.f: Some words for formatting nice printouts. These are used by the decompiler 'see' and may be used by other programs which desire to use them. variable lmargin 0 lmargin ! variable rmargin 60 rmargin ! Variables which set the left and right margins. ?line (s n -- ) If adding n more characters to the current output line would go past the right margin, does a carriage return and spaces over to the left margin. Otherwise does nothing. ?cr (s -- ) Equivalent to "0 ?line". Checks to see if the right margin has already been exceeded, and if so, does a carriage return and spaces over to the left margin. to-column (s column -- ) Moves over to the indicated column. If the current line is already at or past that column, just adds 1 space. **** init.f: cold-hook ( -- ) Deferred Executed when Forth starts up (cold-hook Default system startup code There is a deferred word "cold-hook" which is executed during the initial startup of the forth system. Packages which require initialization may do so by defining a word to do the initialization, then installing that word in cold-hook. The new word should execute the existing (cold-hook first, so that the initialization that was already being done still gets done. This can be used to automatically execute an application when Forth starts up. This particular (cold-hook initializes the search order. **** io.f: Forth interfaces to some Unix system calls. For many programs, the portable Forth file system calls should be used instead, but programs which need to can use these. 0644 constant default-mode u_open ( mode str -- fd ) u_creat ( mode str -- fd ) u_close ( fd -- ) u_read ( n buf fd -- nread ) u_write ( n buf fd -- nwritten ) u_ioctl ( addr l.command fd -- errf ) **** getenv.f: For getting the value of a Unix environment variable. getenv ( str -- str' | 0 ) Given the address of a packed string containing the name of the desired environment variable, return the address of a packed string which is the value of that environment variable, or 0 if the environment variable doesn't exist. If getenv is going to be called several times, the returned strings should be moved to some safe place between calls, as each call overwrites the previous string. **** cstrings.f: For converting between C-style strings (null-byte terminated) and Forth style strings. There are two kinds of Forth-style strings: packed, with a length byte in memory followed by the data bytes. Packed strings are represented on on the Forth stack by the address of the length byte. unpacked, with the address of the data bytes and the number of bytes both on the stack. cstrlen ( l.c-str -- len ) Returns the number of bytes in the C-style string whose address is the argument. The null byte is not counted. Thus cstrlen would return 4 for the C-string 'help'. cscount ( l.c-string -- addr len ) Returns an unpacked Forth string given a C-string. fstr ( l.c-string where -- where) Converts a C-string into a packed Forth string, putting the Forth string at where. cstr ( forth_string -- c_string ) Converts a packed Forth string into a C-string, leaving the address of the C-string on top of the stack. Currently the C-string is put in a fixed place, so the C-string should be used immediately, lest it be overwritten by some other operation. **** argv.f: Provides the ability to read the Unix command-line arguments. arg ( arg# -- argument-string ) Returns the address of a packed string containing the arg#'th Unix command line argument. Argument numbers are relative to the argument that is currently the Forth interpreter input stream. For instance, if the command line was: forth files.exe test.f foobar.f and arg were called from within test.f, then "0 arg" would return the string "test.f". "1 arg" would return the string "foobar.f". Returns 0 if there is no arg#'th argument. nextarg ( -- argument-string ) Returns the address of a packed string which is the command-line argument after the name of the current input stream file. In the example above, if "nextarg" were called from within test.f, it would return the string "foobar.f". When nextarg is called, an internal argument pointer is advanced, so that successive calls to nextarg return successive command-line arguments. Furthermore, command line arguments gotten with nextarg will not be seen by the C program that is scanning the command line and preparing the input stream. Returns 0 if there are no more command line arguments. **** clink.f: For loading C-language (or Fortran or Pascal or whatever) object files into an executing Forth program. Any external subroutines defined in that object file may then be executed from Forth, and external data structures may be accessed. base-syms ( -- str ) Str is the address of a packed string which is the name of the 'a.out' format file to use as the initial symbol table for loading the object file. The first time that CLINK is called, BASE-SYMS returns the name of the forth program (usually /usr/local/forth). Subsequent times, it returns the name of a file whose symbol table also has the symbols defined in all previous CLINK's. clink ( object-file -- ) Given a packed string which is the name of a Unix object (".o") file, loads that object file into the Forth system. For every external symbol in the file, an Forth word of the same name is created in the Forth dictionary. When that Forth word is executed, the behavior depends on what kind of symbol it was. If it was a text symbol, the corresponding subroutine is executed. If it was a data or bss symbol, executing the Forth word just leaves the address of the data structure on the stack. Arguments may be passed to the procedure simply by putting them on the Forth stack. The top of the stack corresponds to the leftmost subroutine argument. To get the return value from a function, use the Forth word "ret". Since Unix procedures depend on the caller to clean up the stack, any arguments that are passed to the procedure will still be on the stack after the procedure returns. **** cload.f: Words for dealing with "a.out" Unix loader format files. nuser (fret ( -- addr ) The address of a user variable which contains the 64-bit floating point value returned by the most-recently-called C function. If that function did not return a floating point value, the value contained in the user variable is undefined. nuser (ret ( -- addr ) The address of a user variable which contains the 32-bit value returned by the most-recently-called C function. If that function did not return a value, the value contained in the user variable is undefined. ret ( -- last-function-return-value ) Puts the 32-bit value returned by the last C function called on the stack. This is equivalent to "(RET L@" cload ( name -- ) :ccall ( addr name -- ) **** spawn.f For executing other Unix programs from within Forth. This implementation is sort of hokey. It needs a better way of allocating strings. argv-strings ( -- old-here ) Should be done before the argument strings for the program are prepared. carg ( str -- ) Adds the indicated string as the next string argument to the program. spawn ( old-here program-name -- successflag ) Executes the program whose filename is program-name (must be a complete pathname). Returns zero if the program failed to run. Otherwise returns nonzero after the program finishes. Example: to execute "ls -l" argv-strings " ls" carg " -l" carg " /bin/ls" spawn system ( str -- ) Str is the address of a packed string. That string is a Unix command line which is executed in a subshell. This uses the Unix "system()" routine, so unfortunately you always get the Bourne shell. sh ( -- ) The rest of the input line after SH is executed as a Unix command line in a subshell (Bourne shell only). For instance, sh ls -l *.f causes a long listing of all files in the current directory whose names end in .f . **** path-open.f Allows you to define a list of Unix directories to be searched when you open a file. If the file is not found in the first directory, the second one is searched, etc. The list of paths is taken from the environment variable EPATH. path-open ( name list-of-paths -- fp | 0 ) Attempts to open the named file. Each directory in the search list is searched until the file is found. Returns a file pointer or 0 if the file could not be found. **** path-scan.f Used in path-load to parse the EPATH string into a list of strings. path-scan ( str array max-entries -- ) Str is the address of a packed string containing a path list. Array is the address of storage area containing space for max-entries pointers. The array is filled with pointers to each of the directories mentioned in the path list. The last pointer in the array is 0. A path list looks like, for example, .:/usr/wmb/forth:/usr/local/forth **** path-load.f: path-load ( filename -- ) Attempts to load the named file. Each directory in the search list is searched until the file is found. requires ( -- ) ( Input stream: filename ) If there is not a word in the dictionary whose name is filename, a path-load using that filename is performed. This is useful for loading a package if it is not already loaded. The file should create a word with the name of the file, so that subsequent calls to requires will see that the package is already loaded. **** keyboard.f: A package that allows a Forth program to change the keyboard mapping for the Sun-2 keyboard. The mapping is done inside the kernel and is global, so if you change it, it will stay that way until you change it back, even if the Forth program exits. Constants for some magic numbers. From /usr/include/mon/keyboard.h 0b0 constant STRING 8010.6b01 lconstant SETKEY 0.80 lconstant SHIFTKEYS 0.0 lconstant CAPSLOCK 0.0001 lconstant CAPSMASK 0.1 lconstant SHIFTLOCK 0.2 lconstant LEFTSHIFT 0.3 lconstant RIGHTSHIFT 0.000e lconstant SHIFTMASK 0.4 lconstant LEFTCTRL 0.5 lconstant RIGHTCTRL 0.0030 lconstant CTRLMASK 0.0080 lconstant UPMASK 0.0100 lconstant CTLSMASK a0 constant NOP Key position numbers for function keys. 1 constant L1 3 constant L2 25 constant L3 26 constant L4 49 constant L5 51 constant L6 72 constant L7 73 constant L8 95 constant L9 97 constant L10 5 constant F1 6 constant F2 8 constant F3 10 constant F4 12 constant F5 14 constant F6 16 constant F7 17 constant F8 18 constant F9 setkey ( ascii station -- ) Sets the key whose number is station so that typing it yields the character ascii. setstring ( string station s# -- ) Sets the key whose number is station so that typing it yields the string. S# is the number of the kernel string table entry to use. There is only space for 16 strings in the kernel string table. **** many.f: Allows a Forth command line to be easily executed several times. This is slower than a compiled loop, because the line is re-interpreted each time. This only works from the keyboard, not from inside files. variable #times The number of times that the command line has been performed. times ( n -- ) Re-executes the current input line n times. Everything between the start of the line and "times" will be re-executed. If n is a constant, it works the obvious way. If n changes as a result of executing the line, the line will continue to execute until the number of times that it has been executed is >= the current value of n. many ( -- ) Continues to execute the current input line until a key is typed. When running under Unix, the best key to use is return, since other keys may not be seen by Forth until you type a return. **** menus2.f: A package for conveniently making menu-driven interfaces. menu-start Start defining a new menu. item ( cfa string -- ) Adds an item to the menu being defined. The cfa is the word to execute if the menu item is selected, the string is the description that is displayed as part of the menu. menu: ( -- ) ( Input stream: menu-name ) ( Later: -- ) Defines a new menu word. When that word is later executed, it displays the menu and prompts for and executes a selection from that menu. The menu items are specified before menu:. Menus may be trivially nested; since a menu is an executable forth word, a menu may be included within another menu. Example: fword ( -- ) ." Forth code to execute: " query interpret ; up ( -- ) menu-stack pop drop 0 menu-stack push ; up-item ( -- ) ['] up ["] Exit this menu" item ; f-item ( -- ) ['] fword ["] Execute some forth code" item ; redisplay ( -- ) ['] .menu ["] Redisplay the menu" item ; \ Collects a string, allocates space for it, and leaves its address m" ( -- string ) ( Input stream: string" ) here ," ; menu-start redisplay f-item up-item ' + m" Add the top two stack items" item ' - m" Subtract the top two stack items" item ' * m" Multiply the top two stack items" item menu: arithmetic menu-start redisplay f-item up-item ' .s m" Print the stack" item ' dup m" Duplicate the top of the stack" item ' drop m" Get rid of the top of the stack" item ' swap m" Exchange the top two stack elements" item ' arithmetic m" Perform arithmetic" item menu: stack **** number.f: This is Klaus Schliesiek's structured number input package. It does for numeric input what the pictured numeric output words ( <# # # #> etc ) do for numeric output. Right now this is broken because I don't implement -roll. <$ ( addr len -- sign end addr ud true ) Begin pictured numeric input. The input arguments addr len represent the string to be parsed. $ ( end addr ud1 f1 -- end addr+1 ud2 true | end ud1 false ) Scan ofalse a digit and accumulate it into the number being generated. If the character isn't a digit, leave the false group. $s ( end addr ud1 f1 -- end addr+1 ud2 true | end ud1 false ) Scan ofalse and accumulate digits until a non-numeric character is encountered. $> ( sign end addr ud f -- d true | false ) Terminate pictured numeric input, leaving the converted number and true, or false if the parse failed. required ( end addr ud f -- 0 addr ud false | end addr ud true ) If the flag on top of the stack is false, replace the end address with 0 so the input parsing will stop. (ascii? ( end addr ud f ch -- end addr+1 ud true | end addr ud false ) Tests the next input character to see if it matches the character on top of the stack. If so, eat the input character and leave true. If not, don't eat the input character and leave false. ?dpl ( f -- f ) If the flag is true, store 0 in the variable dpl. ?sign ( f -- f ) If the flag is true, sets the sign word on the stack frame. more? ( end addr ud f -- end addr ud f f ) Tests to see if there are any more characters left in the input number. If so, leaves true. -sign? ( sign end addr ud f -- sign' end addr ud f ) If the next character in the input number is a minus sign, sets the sign item on the stack and eats the minus. Heres an implementation of number? using these primitives. Klaus claims this is better than the standard implementation. It is certainly different. number? ( addr len - d true | false ) <$ ( sign end addr ud true ) -sign? ascii . (ascii? ?dpl $ required begin $s more? while ascii . (ascii? ?dpl required repeat $> ; **** order.f: The implementation of vocabulary search order. This is already loaded into the system, so you don't have to load this file again. The only reason this is in a separate file that it isn't officially a part of the 83 standard (it's a "proposal") and the implementors of the F83 model chose not to wire it into the kernel. I haven't gotten around to wiring it in. vocabulary root The base vocabulary that contains just those words necessary to extend the search order. also ( -- ) Duplicate the context vocabulary in the search order so that it stays in the search order even if another vocabulary becomes current. only Pare down the search order to include only the root vocabulary. seal ( -- ) ( Input stream: vocabulary-name ) Make the named vocabulary the only one in the search order. This can be used to make a turnkey system where only selected words are visible. If the vocabulary that is sealed doesn't contain words which modify the search order (like other vocabularies or only), then the user can't get out of this vocabulary. previous ( -- ) Removes the top vocabulary from the search order. order ( -- ) Displays the current search order. vocs ( -- ) Displays the names of all the vocabularies in the system. **** over-voc.f: over-vocabulary ( action-word-cfa voc-pfa -- ) For every word in the vocabulary whose cfa is voc-cfa, executes the action word. When the action word executes, the link field address of the word in the vocabulary is on the stack. The action word must remove the lfa from the stack. word-hook ( lfa -- ) An action word which makes over-vocabulary duplicate the effect of "words", which is to print the names of all the words in the vocabulary. Examples: ' word-hook ' assembler over-vocabulary Prints the names of all the words in the assembler vocabulary. ' . ' assembler over-vocabulary Prints their link field addresses instead of their names. **** patch.f: Allows you to zap an already-compiled word by replacing a word in it with some other word. csearch ( c start end -- loc true | false ) Search for the first occurrence of the character c in the range of addresses between start and end. Returns the address where it was found and true, or false if not found. wsearch ( w start end -- loc true | false ) Search for the first occurrence of the 16 bit word w in the range of addresses between start and end. Returns the address where it was found and true, or false if not found. tsearch ( cfa start end -- loc true | false ) Search for the first compiled occurrence of the cfa in the range of addresses between start and end. Returns the address where it was found and true, or false if not found. search ( n start end -- loc true | false ) Search for the first occurrence of the number n in the range of addresses between start and end. Returns the address where it was found and true, or false if not found. (patch ( new old cfa -- ) In the word "cfa", replace the first occurrence of the number "old" with the number "new". (wpatch ( new old cfa -- ) In the word "cfa", replace the first occurrence of the 16 bit number "old" with the 16 bit number "new". npatch ( new old -- ) ( Input stream: name-of-word-to-zap ) In the named word, replace the first occurrence of the number "old" with the number "new". wpatch ( new old --name ) ( Input stream: name-of-word-to-zap ) In the named word, replace the first occurrence of the 16 bit number "old" with the 16 bit number "new". patch ( -- ) ( Input stream: new-word old-word word-to-zap ) By example, suppose foo is defined as: : foo ( n -- ) decimal . ; Then you do: patch hex decimal foo Now foo does "hex ." instead of "decimal .". **** pokearound.f: A version of the interpreter that may be used to inspect the state of the machine without clearing the return stack. poke-around ( -- ) Executing poke-around invokes an interpreter that doesn't destroy the state of the stack or the input buffer. done Done exits the poke-around interpreter and restores the state of the input buffer. **** saveforth.f: Allows forth applications to be precompiled and written out as a binary image. This is already loaded in the normal files.exe system. save-forth ( filename -- ) Snapshots the current state of the dictionary and writes it to a file which may later be the starting dictionary for another invocation of the forth system. The filename should end in ".exe". **** showdefer.f For printing the name of the word which a deferred word actually executes. (showdefer ( deferred-cfa -- ) Given the compilation address of a deferred word, prints the name of the word that it executes. showdefer ( -- ) ( Input stream: name-of-deferred-word ) Given the name of a deferred word, prints the name of the word that it executes. **** sieve.f: Several Forth implementations of the Sieve of Erasthothenes algorithm. The first version is the one that was published in Byte and was used to compare several languages. It is not a fair comparison of Forth to other languages, since it is very poorly coded (the code for the other languages was somewhat better). The second version is more representative of good Forth code. The third version illustrates the ease of tuning Forth programs by judiciously writing a critical word in assembly language. do-prime ( -- ) one iteration of the Byte sieve 10-times ( -- ) Ten iterations of the Byte sieve do-prime.hi ( -- ) One iteration of the Colburn sieve 10-times.hi ( -- ) Ten iterations of the Colburn sieve do-prime.lo ( -- ) One iteration of the optimized Colburn sieve 10-times.lo ( -- ) Ten iterations of the optimized Colburn sieve **** split-scroll.f: Words to define scrolling regions on a terminal screen. scroller: ( top-row# bottom-row# -- ) ( Input stream: scroller-name ) Defines a scrolling region. The word defined may be installed in the deferred word cr, so that scrolling only occurs between the top-row# and the bottom-row#. 1 17 scroller: top-scroller A scroller for the top half of a 34-line screen (like a Sun screen or a default-sized Sun window). top-scroll ( -- ) Select the top scrolling region so that the next text written to the screen will appear in it. 18 34 scroller: bottom-scroller A scroller for the bottom half of a 34-line screen (like a Sun screen or a default-sized Sun window). bottom-scroll ( -- ) ['] bottom-scroller ['] cr (is ; Select the bottom scrolling region so that the next text written to the screen will appear in it. **** strings.f: A simple string package. Does not have a string stack. Operates on packed strings whose addresses are kept on the parameter stack. "copy ( fromaddr toaddr -- ) Copies a packed string from "fromaddr" to "toaddr". "cat ( startstr endstr -- ) Append startstr to the end of endstr. There must already be enough space at the end of endstr to accept startstr. "" ( -- str ) ( Input stream: string ) Grabs a sequence of non-blank characters out of the input stream and makes it a string, leaving the address. This is the MOST useful string input primitive, since the vast majority of the time you don't want imbedded blanks in the string. This word guarantees that the string it gets has no blanks in it, either in front, in the middle, or at the end. It doesn't need a delimiter, because the string in the input stream is surrounded by blanks. [""] ( -- ) ( Input stream: string ) ( Run time: -- str ) Grab a string without blanks in it. Compile that string into the dictionary so that it's address is left on the stack at run time. " ( -- str ) ( Input stream: string" ) Grab characters from the input stream up to a " and make them into a string. The string may contain blanks anywhere in it. " -- string strings Used in definitions of the form: " string..." The characters between but not including the necessary leading space and the trailing double-quote character are collected from the input stream and stored as a counted string. The address of the string is left on the stack. Implementation Note: All such strings are stored in the same place, so repeated uses of " will overwrite the previous string. If several such strings are needed at the same time, each string must be explicitly copied to some safe place before the next one is collected. See: "COPY ["] ( -- ) ( Input stream: string" ) ( Run time: -- str ) Grab characters from the input stream up to a " and make them into a string. The string may contain blanks anywhere in it. Compile the string into the dictionary so that it's address is left on the stack at run time. ". ( str -- ) Print the string. Equivalent to count type. ", ( string -- ) Emplace the string into the dictionary and allocate space for it. ," ( -- ) ( Input stream: string" ) ( Run time: -- str ) Emplace the string from the input stream into the dictionary and allocate space for it. **** th.f: th ( -- ? ) Immediate Temporarily set base to hex and interpret next word. The next word may either be a number or an executable word. td ( -- ? ) Immediate Same as th but temporarily sets base to decimal. **** time.f: For accessing the time-of-day and date from Forth. today ( -- day month year) Returns the day [1-31], month[1-12], and year[e.g. 1985]. now ( -- secs mins hours ) Returns the local time in hours, minutes, and seconds since midnight. dst? ( -- f) Returns true if daylight savings time is in effect. time-zone ( -- minutes-west-of-GMT) Returns the time-zone in minutes west of GMT. PST is 8*60 = 480. .time-zone ( -- ) Prints a string representing the time zone (e.g. PST). .month ( index -- ) Given a number from 1 to 12, print the name of the corresponding month. .date ( day month year -- ) Print the data given the day, month, and year numbers. For example, "5 3 1985 .date" prints March 5, 1985 .time ( secs mins hours -- ) Print the time given by the stack arguments. For example, "37 7 10 .time" prints "10:07:37 PST" .now ( -- ) Prints the current time. Equivalent to "now .time" .today ( -- ) Prints the current date. Equivalent to "today .date" **** util.f: Some miscellaneous things. interactive Turns on prompting (the system prompts with "ok "). batch Turns off prompting (the system does not prompt). ( ( -- ) ( Input stream: comment-terminated-with-')' ) An alternate style of comment usually signifying a stack diagram. If this style of comment were used consistently for stack diagrams, it would be easy to automatically extract stack comments from source files. Also, if pigs had wings, they could fly. immediate? ( cfa -- f ) Returns true if the word whose compilation address is on the stack is immediate. printable? ( char -- f ) Returns true if n represents a printable character. Printable characters are those between hex 40 and hex 7e inclusive. c.id ( cfa -- ) Prints the name of the word whose compilation address is on the stack. The other such word, ".id", takes a name field address instead of a compilation address. >user# ( cfa -- user# ) Returns the user number (which is a byte offset into the User area) of the word whose compilation address is on the stack. Assumes that the word really is a user variable. If not, the result is undefined. 'user# ( -- user# ) ( Input stream: user-variable-name ) Returns the user number (which is a byte offset into the User area) of the word whose name is taken from the input stream. Assumes that the word really is a user variable. If not, the result is undefined. #! ( -- ) Ignores the rest of the input line. It is possible to make files containing forth commands/programs executable by Unix. All you have to do is make the first line in the file "#! /usr/local/forth" (without the quotes), and put the forth program after it. The file should have execute permissions set. The word "#!" is defined in forth so that the first line of the file (which specifies the interpreter to execute) will be ignored by forth. **** words.f: For showing the names of all the words in the context vocabulary. Used to be called "vlist" in the old days. words ( -- ) Prints the names of all the words in the context vocabulary. **** xprint.f: Prints numbers in a specified base, regardless of what the base is right now. 2 constant two The number two, regardless of the current base. 8 constant eight The number eight, regardless of the current base. 10 constant ten The number ten, regardless of the current base. 16 constant sixteen The number sixteen, regardless of the current base. n. ( n base -- ) Prints n in the base specified by the number "base". Does not permanently affect the current base. For instance, "sixteen ten n." always prints decimal "16". ln. ( l base -- ) Prints n (a 32 bit number) in the base specified by the number "base". Does not permanently affect the current base. x. ( u -- ) Prints the number u in unsigned hex. **** terminals.f: variable terminal-type Contains a number which refers to the terminal type that is currently selected. termctl: ( offset -- new-offset ) ( Input stream: function-name ) Defines a terminal control function. Each of the so-defined functions may be executed to perform their action. The particular code that must be executed to perform that function for a particular terminal is defined in a separate file for each type of terminal. termctl: #lines ( -- #lines ) Leaves the number on screen lines for the selected terminal type. termctl: #columns ( -- #columns ) Leaves the number on screen columns for the selected terminal type. termctl: beep ( -- ) Rings the bell. termctl: left ( -- ) Moves the cursor one position to the left, without erasing any characters. Behavior at left edge is undefined. termctl: right ( -- ) Moves the cursor one position to the right, without erasing any characters. Behavior at right edge is undefined. termctl: set-position ( line column -- ) Moves the cursor to the indicated line and column. Line and column numbers start at 0. termctl: insert-char ( char -- ) Inserts the character at the cursor position, moving over the rest of the line to make room. The character at the end of the line is pushed off the screen. termctl: delete-char ( -- ) Deletes the character at the cursor position, moving over the rest of the line to fill in the space. termctl: kill-line ( -- ) Deletes the character at the cursor position and all characters to the right of it on the line. termctl: kill-screen ( -- ) Deletes the character at the cursor position and all characters after it on the screen. termctl: insert-line ( -- ) Opens a new line on the screen. The line that the cursor was on and all lines after it are moved down one line. The last line on the screen is pushed off the screen. termctl: delete-line Deletes the line that the cursor is on from the screen. Lines below it move up to fill the space. termctl: erase-screen Erases the entire screen and leaves the cursor at the upper left corner. termctl: save-position Remembers the cursor position in some magic place. termctl: restore-position Moves the cursor to the place where it was when save-position was last executed. cursor-to-row-column ( row column-- ) Like set-position, but also takes care of setting the #line and #out variables (which keep track of where the cursor is). cursor-forward ( -- ) Like right, but also takes care of updating the #out variable (which keeps track of where the cursor is). cursor-backward ( -- ) Like left, but also takes care of updating the #out variable (which keeps track of where the cursor is). clear-screen ( -- ) Like erase-screen, but also takes care of updating the #line and #out variables (which keep track of where the cursor is). vocabulary terminals Vocabulary where terminal control definitions are kept. variable saved-x variable saved-y For use in simulating the effect of save-position and restore-positon on terminals that can't do it by themselves. variable saved-pause It is usually a bad idea to do a task switch between a save-position and it's matching restore-position, since the new task could also do a save-position and clobber the variable. The solution is to save the current value of the deferred word pause, turn off pausing, and restore it when the task is done updating the screen. This whole save/restore scheme doesn't work very well with multiple tasks writing to the screen. Some words to make it easy to specify common terminal command sequences: td 27 constant escape The ascii escape character. getlit ( -- ) ( Literal: character ) Gets a literal character out of the code stream. outlit ( -- ) ( Literal: character ) Prints a literal character which is taken from the code stream. ctl ( -- ) ( Input stream: arg ) Gets an ascii character out of the input stream and converts it to a control character by stripping off the top bits. If interpreting, emits the control char. If compiling, arranges for that character to be emit at run time. (esc ( -- ) ( Literal: character ) Outputs an escape character followed by a character taken from the code stream. esc ( -- ) ( Input stream: char ) Gets an ascii character out of the input stream. If interpreting, emits an escape character and then the character from the input stream. If compiling, arranges for escape and that character to be emit at run time. (esc[ ( -- ) ( Literal: character ) Like (esc, but emits escape then [ then the literal character. For ansi terminals. esc[ ( -- ) ( Input stream: char ) Like esc, but emits escape then [ then the character. For ansi terminals. for ( -- ) ( Input stream: termctl-name ) When writing the code for a particular terminal, selects the terminal control function to which the following code applies. clear-termctl ( -- ) Initializes the current terminal control table to all no-ops. terminal: ( -- ) ( Input stream: terminal-name ) ( Later: -- ) Defines a word for a new terminal type and starts the definition of the code to implement the terminal control functions. When the terminal-name is executed, that terminal's control functions will be installed so that they get executed when the generic terminal control functions are executed. end-terminal ( -- ) Terminates the definition of terminal control functions. prototype ( -- ) ( Input stream: name ) If you are defining a new terminal which is almost like one that you already have, you can use prototype to initialize all the terminal control functions for the new terminal to those of the old terminal. Then just the functions that are different may be re-specified. terminal: dumb Terminal control definition for a dumb terminal. 24 lines x 80 columns, can ring the bell with ctl G, backspace with ctl H, and not much else. You know, a teletype model 33. **** ansi.f: Terminal control definitions for ansi-standard terminals, such as the Sun Workstation terminal emulator. See also "terminals.f" sun-save ( -- ) Save the current cursor position in some magic place. Since the Sun terminal emulator doesn't faithfully implement the save-cursor-position function, a kludgy substitute is provided. This substitute function only works when running stand-alone under the Sun PROM monitor. sun-restore ( -- ) Restore the cursor to the previously-saved position. See "sun-save". terminal: ansi ( -- ) Executing "ansi" sets up the forth system to use ansi-standard terminal control sequences. sun ( -- ) Synonym for "ansi". **** heath.f: Terminal control definitions for Heath H-19 terminals in "Heath Mode". This includes Heath/Zenith Z-16 terminals and H/Z-89 and H/Z-90 computers. These will probably work for DEC VT-52 terminals too. The Heath/Zenith terminals can also be put into "ansi mode", in which case the ansi terminal control definitions may be used. Heath mode is more efficient than ansi mode, since the ansi escape sequences are longer than the heath ones. terminal: h19 Executing "heath" sets up the forth system to use heath terminal control sequences. heath h19 ; Synonym for "h19". **** televideo.f: Terminal control definitions for Televideo 926 terminals. terminal: t925 ( -- ) Executing "t925" sets up the forth system to use ansi-standard terminal control sequences. televideo t925 ; tvi t925 ; Synonyms for "t925".