Annotation of gforth/gforth.texi, revision 1.6

1.1       anton       1: \input texinfo   @c -*-texinfo-*-
                      2: @comment %**start of header (This is for running Texinfo on a region.)
                      3: @setfilename gforth-info
                      4: @settitle GNU Forth Manual
                      5: @setchapternewpage odd
                      6: @comment %**end of header (This is for running Texinfo on a region.)
                      7: 
                      8: @ifinfo
                      9: This file documents GNU Forth 0.0
                     10: 
                     11: Copyright @copyright{} 1994 GNU Forth Development Group
                     12: 
                     13:      Permission is granted to make and distribute verbatim copies of
                     14:      this manual provided the copyright notice and this permission notice
                     15:      are preserved on all copies.
                     16:      
                     17:      @ignore
                     18:      Permission is granted to process this file through TeX and print the
                     19:      results, provided the printed document carries a copying permission
                     20:      notice identical to this one except for the removal of this paragraph
                     21:      (this paragraph not being relevant to the printed manual).
                     22:      
                     23:      @end ignore
                     24:      Permission is granted to copy and distribute modified versions of this
                     25:      manual under the conditions for verbatim copying, provided also that the
                     26:      sections entitled "Distribution" and "General Public License" are
                     27:      included exactly as in the original, and provided that the entire
                     28:      resulting derived work is distributed under the terms of a permission
                     29:      notice identical to this one.
                     30:      
                     31:      Permission is granted to copy and distribute translations of this manual
                     32:      into another language, under the above conditions for modified versions,
                     33:      except that the sections entitled "Distribution" and "General Public
                     34:      License" may be included in a translation approved by the author instead
                     35:      of in the original English.
                     36: @end ifinfo
                     37: 
                     38: @titlepage
                     39: @sp 10
                     40: @center @titlefont{GNU Forth Manual}
                     41: @sp 2
                     42: @center for version 0.0
                     43: @sp 2
                     44: @center Anton Ertl
                     45: 
                     46: @comment  The following two commands start the copyright page.
                     47: @page
                     48: @vskip 0pt plus 1filll
                     49: Copyright @copyright{} 1994 GNU Forth Development Group
                     50: 
                     51: @comment !! Published by ... or You can get a copy of this manual ...
                     52: 
                     53:      Permission is granted to make and distribute verbatim copies of
                     54:      this manual provided the copyright notice and this permission notice
                     55:      are preserved on all copies.
                     56:      
                     57:      Permission is granted to copy and distribute modified versions of this
                     58:      manual under the conditions for verbatim copying, provided also that the
                     59:      sections entitled "Distribution" and "General Public License" are
                     60:      included exactly as in the original, and provided that the entire
                     61:      resulting derived work is distributed under the terms of a permission
                     62:      notice identical to this one.
                     63:      
                     64:      Permission is granted to copy and distribute translations of this manual
                     65:      into another language, under the above conditions for modified versions,
                     66:      except that the sections entitled "Distribution" and "General Public
                     67:      License" may be included in a translation approved by the author instead
                     68:      of in the original English.
                     69: @end titlepage
                     70: 
                     71: 
                     72: @node Top, License, (dir), (dir)
                     73: @ifinfo
                     74: GNU Forth is a free implementation of ANS Forth available on many
                     75: personal machines. This manual corresponds to version 0.0.
                     76: @end ifinfo
                     77: 
                     78: @menu
                     79: * License::             
                     80: * Goals::               About the GNU Forth Project
                     81: * Other Books::         Things you might want to read
                     82: * Invocation::          Starting GNU Forth
                     83: * Words::               Forth words available in GNU Forth
                     84: * ANS conformance::     Implementation-defined options etc.
                     85: * Model::               The abstract machine of GNU Forth
                     86: @comment * Emacs and GForth::    The GForth Mode
                     87: * Internals::           Implementation details
                     88: * Bugs::                How to report them
                     89: * Pedigree::            Ancestors of GNU Forth
                     90: * Word Index::          An item for each Forth word
                     91: * Node Index::          An item for each node
                     92: @end menu
                     93: 
                     94: @node License, Goals, Top, Top
                     95: @unnumbered License
                     96: !! Insert GPL here
                     97: 
                     98: @iftex
                     99: @unnumbered Preface
                    100: This manual documents GNU Forth. The reader is expected to know
                    101: Forth. This manual is primarily a reference manual. @xref{Other Books}
                    102: for introductory material.
                    103: @end iftex
                    104: 
                    105: @node    Goals, Other Books, License, Top
                    106: @comment node-name,     next,           previous, up
                    107: @chapter Goals of GNU Forth
                    108: @cindex Goals
1.5       anton     109: The goal of the GNU Forth Project is to develop a standard model for
                    110: ANSI Forth. This can be split into several subgoals:
1.1       anton     111: 
1.5       anton     112: @itemize @bullet
                    113: @item
                    114: GNU Forth should conform to the ANSI Forth standard.
                    115: @item
                    116: It should be a model, i.e. it should define all the
                    117: implementation-dependent things.
                    118: @item
                    119: It should become standard, i.e. widely accepted and used. This goal
                    120: is the most difficult one.
                    121: @end itemize
                    122: 
                    123: To achieve these goals GNU Forth should be
                    124: @itemize @bullet
                    125: @item
                    126: Similar to previous models (fig-Forth, F83)
                    127: @item
                    128: Powerful. It should provide for all the things that are considered
                    129: necessary today and even some that are not yet considered necessary.
                    130: @item
                    131: Efficient. It should not get the reputation of being exceptionally
                    132: slow.
                    133: @item
                    134: Free.
                    135: @item
                    136: Available on many machines/easy to port.
                    137: @end itemize
                    138: 
                    139: Have we achieved these goals? GNU Forth conforms to the ANS Forth
                    140: standard; it may be considered a model, but we have not yet documented
                    141: which parts of the model are stable and which parts we are likely to
                    142: change; it certainly has not yet become a de facto standard. It has some
                    143: similarities and some differences to previous models; It has some
                    144: powerful features, but not yet everything that we envisioned; on RISCs
                    145: it is as fast as interpreters programmed in assembly, on
                    146: register-starved machines it is not so fast, but still faster than any
                    147: other C-based interpretive implementation; it is free and available on
                    148: many machines.
                    149: 
1.1       anton     150: @node Other Books, Invocation, Goals, Top
                    151: @chapter Other books on ANS Forth
                    152: 
                    153: As the standard is relatively new, there are not many books out yet. It
                    154: is not recommended to learn Forth by using GNU Forth and a book that is
                    155: not written for ANS Forth, as you will not know your mistakes from the
                    156: deviations of the book.
                    157: 
                    158: There is, of course, the standard, the definite reference if you want to
                    159: write ANS Forth programs. It will be available in printed form from
1.6     ! anton     160: Global Engineering Documents !! somtime in spring or summer 1994. If you
        !           161: are lucky, you can still get dpANS6 (the draft that was approved as
        !           162: standard) by aftp from ftp.uu.net:/vendor/minerva/x3j14.
        !           163: 
        !           164: @cite{Forth: The new model} by Jack Woehr (!! Publisher) is an
        !           165: introductory book based on a draft version of the standard. It does not
        !           166: cover the whole standard. It also contains interesting background
        !           167: information (Jack Woehr was in the ANS Forth Technical Committe). It is
        !           168: not appropriate for complete newbies, but programmers experienced in
        !           169: other languages should find it ok.
1.1       anton     170: 
                    171: @node Invocation, Words, Other Books, Top
                    172: @chapter Invocation
                    173: 
                    174: You will usually just say @code{gforth}. More generally, the default GNU
                    175: Forth image can be invoked like this
                    176: 
                    177: @example
                    178: gforth [--batch] [files] [-e forth-code]
                    179: @end example
                    180: 
                    181: The @code{--batch} option makes @code{gforth} exit after processing the
                    182: command line. Also, the startup message is suppressed. @file{files} are
                    183: Forth source files that are executed in the order in which they
                    184: appear. The @code{-e @samp{forth-code}} or @code{--evaluate
                    185: @samp{forth-code}} option evaluates the forth code; it can be freely
                    186: mixed with the files. This option takes only one argument; if you want
                    187: to evaluate more Forth words, you have to quote them or use several
                    188: @code{-e}s. !! option for suppressing default loading.
                    189: 
                    190: You can use the command line option @code{-i @samp{file}} or
                    191: @code{--image-file @samp{file}} to specify a different image file. Note
                    192: that this option must be the first in the command line. The rest of the
                    193: command line is processed by the image file.
                    194: 
                    195: If the @code{--image-file} option is not used, GNU Forth searches for a
                    196: file named @file{gforth.fi} in the path specified by the environment
                    197: variable @code{GFORTHPATH}; if this does not exist, in
                    198: @file{/usr/local/lib/gforth} and in @file{/usr/lib/gforth}.
                    199: 
                    200: @node Words,  , Invocation, Top
                    201: @chapter Forth Words
                    202: 
                    203: @menu
                    204: * Notation::
                    205: * Arithmetic::
                    206: * Stack Manipulation::
                    207: * Memory access::
                    208: * Control Structures::
                    209: * Local Variables::
                    210: * Defining Words::
                    211: * Vocabularies::
                    212: * Files::
                    213: * Blocks::
                    214: * Other I/O::
                    215: * Programming Tools::
                    216: @end menu
                    217: 
                    218: @node Notation, Arithmetic, Words, Words
                    219: @section Notation
                    220: 
1.3       anton     221: The Forth words are described in this section in the glossary notation
1.1       anton     222: that has become a de-facto standard for Forth texts, i.e.
                    223: 
                    224: @quotation
                    225: @samp{word}     @samp{Stack effect}     @samp{pronunciation}   @samp{wordset}
                    226: @samp{Description}
                    227: @end quotation
                    228: 
                    229: @table @samp
                    230: @item word
                    231: The name of the word. BTW, GNU Forth is case insensitive, so you can
                    232: type the words in in lower case.
                    233: 
                    234: @item Stack effect
                    235: The stack effect is written in the notation @code{@samp{before} --
                    236: @samp{after}}, where @samp{before} and @samp{after} describe the top of
                    237: stack entries before and after the execution of the word. The rest of
                    238: the stack is not touched by the word. The top of stack is rightmost,
                    239: i.e., a stack sequence is written as it is typed in. Note that GNU Forth
                    240: uses a separate floating point stack, but a unified stack
                    241: notation. Also, return stack effects are not shown in @samp{stack
                    242: effect}, but in @samp{Description}. The name of a stack item describes
                    243: the type and/or the function of the item. See below for a discussion of
                    244: the types.
                    245: 
                    246: @item pronunciation
                    247: How the word is pronounced
                    248: 
                    249: @item wordset
                    250: The ANS Forth standard is divided into several wordsets. A standard
                    251: system need not support all of them. So, the fewer wordsets your program
                    252: uses the more portable it will be in theory. However, we suspect that
                    253: most ANS Forth systems on personal machines will feature all
                    254: wordsets. Words that are not defined in the ANS standard have
                    255: @code{gforth} as wordset.
                    256: 
                    257: @item Description
                    258: A description of the behaviour of the word.
                    259: @end table
                    260: 
                    261: The name of a stack item corresponds in the following way with its type:
                    262: 
                    263: @table @code
                    264: @item name starts with
                    265: Type
                    266: @item f
1.5       anton     267: Bool, i.e. @code{false} or @code{true}.
1.1       anton     268: @item c
                    269: Char
                    270: @item w
                    271: Cell, can contain an integer or an address
                    272: @item n
                    273: signed integer
                    274: @item u
                    275: unsigned integer
                    276: @item d
                    277: double sized signed integer
                    278: @item ud
                    279: double sized unsigned integer
                    280: @item r
                    281: Float
                    282: @item a_
                    283: Cell-aligned address
                    284: @item c_
                    285: Char-aligned address (note that a Char is two bytes in Windows NT)
                    286: @item f_
                    287: Float-aligned address
                    288: @item df_
                    289: Address aligned for IEEE double precision float
                    290: @item sf_
                    291: Address aligned for IEEE single precision float
                    292: @item xt
                    293: Execution token, same size as Cell
                    294: @item wid
                    295: Wordlist ID, same size as Cell
                    296: @item f83name
                    297: Pointer to a name structure
                    298: @end table
                    299: 
                    300: @node Arithmetic,  , Notation, Words
                    301: @section Arithmetic
                    302: Forth arithmetic is not checked, i.e., you will not hear about integer
                    303: overflow on addition or multiplication, you may hear about division by
                    304: zero if you are lucky. The operator is written after the operands, but
                    305: the operands are still in the original order. I.e., the infix @code{2-1}
                    306: corresponds to @code{2 1 -}. Forth offers a variety of division
                    307: operators. If you perform division with potentially negative operands,
                    308: you do not want to use @code{/} or @code{/mod} with its undefined
                    309: behaviour, but rather @code{fm/mod} or @code{sm/mod} (probably the
                    310: former).
                    311: 
                    312: @subsection Single precision
                    313: +
                    314: -
                    315: *
                    316: /
                    317: mod
                    318: /mod
                    319: negate
                    320: abs
                    321: min
                    322: max
                    323: 
                    324: @subsection Bitwise operations
                    325: and
                    326: or
                    327: xor
                    328: invert
                    329: 2*
                    330: 2/
                    331: 
                    332: @subsection Mixed precision
                    333: m+
                    334: */
                    335: */mod
                    336: m*
                    337: um*
                    338: m*/
                    339: um/mod
                    340: fm/mod
                    341: sm/rem
                    342: 
                    343: @subsection Double precision
                    344: d+
                    345: d-
                    346: dnegate
                    347: dabs
                    348: dmin
                    349: dmax
                    350: 
                    351: @node Stack Manipulation,,,
                    352: @section Stack Manipulation
                    353: 
                    354: gforth has a data stack (aka parameter stack) for characters, cells,
                    355: addresses, and double cells, a floating point stack for floating point
                    356: numbers, a return stack for storing the return addresses of colon
                    357: definitions and other data, and a locals stack for storing local
                    358: variables. Note that while every sane Forth has a separate floating
                    359: point stack, this is not strictly required; an ANS Forth system could
                    360: theoretically keep floating point numbers on the data stack. As an
                    361: additional difficulty, you don't know how many cells a floating point
1.6     ! anton     362: number takes. It is reportedly possible to write words in a way that
1.1       anton     363: they work also for a unified stack model, but we do not recommend trying
1.3       anton     364: it. Also, a Forth system is allowed to keep the local variables on the
                    365: return stack. This is reasonable, as local variables usually eliminate
1.6     ! anton     366: the need to use the return stack explicitly. So, if you want to produce
1.3       anton     367: a standard complying program and if you are using local variables in a
1.1       anton     368: word, forget about return stack manipulations in that word (see the
                    369: standard document for the exact rules).
                    370: 
1.2       pazsan    371: @subsection Data stack
1.1       anton     372: drop
                    373: nip
                    374: dup
                    375: over
                    376: tuck
                    377: swap
                    378: rot
                    379: -rot
                    380: ?dup
                    381: pick
                    382: roll
                    383: 2drop
                    384: 2nip
                    385: 2dup
                    386: 2over
                    387: 2tuck
                    388: 2swap
                    389: 2rot
                    390: 
                    391: @subsection Floating point stack
                    392: fdrop
                    393: fnip
                    394: fdup
                    395: fover
                    396: ftuck
                    397: fswap
                    398: frot
                    399: 
                    400: @subsection Return stack
                    401: >r
                    402: r>
                    403: r@
                    404: rdrop
                    405: 2>r
                    406: 2r>
1.6     ! anton     407: 2r@
        !           408: 2rdrop
1.1       anton     409: 
                    410: @subsection Locals stack
                    411: 
                    412: @subsection Stack pointer manipulation
                    413: sp@
                    414: sp!
                    415: fp@
                    416: fp!
                    417: rp@
                    418: rp!
                    419: lp@
                    420: lp!
                    421: 
                    422: @node Memory access
                    423: @section Memory access
                    424: 
                    425: @subsection Stack-Memory transfers
                    426: @
                    427: !
                    428: +!
                    429: c@
                    430: c!
                    431: 2@
                    432: 2!
                    433: f@
                    434: f!
                    435: sf@
                    436: sf!
                    437: df@
                    438: df!
                    439: 
                    440: @subsection Memory block access
                    441: 
                    442: move
1.5       anton     443: erase
                    444: 
                    445: While the previous words work on address units, the rest works on
                    446: characters.
                    447: 
                    448: cmove
                    449: cmove>
1.1       anton     450: fill
1.5       anton     451: blank
1.1       anton     452: 
                    453: @node Control Structures
                    454: @section Control Structures
                    455: 
                    456: Control structures in Forth cannot be used in interpret state, only in
                    457: compile state, i.e., in a colon definition. We do not like this
                    458: limitation, but have not seen a satisfying way around it yet, although
                    459: many schemes have been proposed.
                    460: 
                    461: @subsection Selection
                    462: 
                    463: @example
                    464: @var{flag}
                    465: IF
                    466:   @var{code}
                    467: ENDIF
                    468: @end example
1.3       anton     469: or
1.1       anton     470: @example
                    471: @var{flag}
                    472: IF
                    473:   @var{code1}
                    474: ELSE
                    475:   @var{code2}
                    476: ENDIF
                    477: @end example
                    478: 
                    479: You can use @code{THEN} instead of {ENDIF}. Indeed, @code{THEN} is
                    480: standard, and @code{ENDIF} is not, although it is quite popular. We
                    481: recommend using @code{ENDIF}, because it is less confusing for people
                    482: who also know other languages (and is not prone to reinforcing negative
                    483: prejudices against Forth in these people). Adding @code{ENDIF} to a
                    484: system that only supplies @code{THEN} is simple:
                    485: @example
                    486: : endif   POSTPONE then ; immediate
                    487: @end example
                    488: 
1.5       anton     489: [According to @cite{Webster's New Encyclopedic Dictionary}, @dfn{then
                    490: (adv.)}  has the following meanings:
                    491: @quotation
                    492: ... 2b: following next after in order ... 3d: as a necessary consequence
                    493: (if you were there, then you saw them).
                    494: @end quotation
                    495: Forth's @code{THEN} has the meaning 2b, @code{THEN} in Pascal
                    496: and many other programming languages has the meaning 3d.]
1.4       anton     497: 
1.5       anton     498: We also provide the words @code{?dup-if} and @code{?dup-0=-if}, so you
1.1       anton     499: can avoid using @code{?dup}.
                    500: 
                    501: @example
                    502: @var{n}
                    503: CASE
                    504:   @var{n1} OF @var{code1} ENDOF
                    505:   @var{n2} OF @var{code2} ENDOF
                    506:   @dots
                    507: ENDCASE
                    508: @end example
                    509: 
                    510: Executes the first @var{codei}, where the @var{ni} is equal to
                    511: @var{n}. A default case can be added by simply writing the code after
                    512: the last @code{ENDOF}. It may use @var{n}, which is on top of the stack,
                    513: but must not consume it.
                    514: 
                    515: @subsection Simple Loops
                    516: 
                    517: @example
                    518: BEGIN
                    519:   @var{code1}
                    520:   @var{flag}
                    521: WHILE
                    522:   @var{code2}
                    523: REPEAT
                    524: @end example
                    525: 
                    526: @var{code1} is executed and @var{flag} is computed. If it is true,
                    527: @var{code2} is executed and the loop is restarted; If @var{flag} is false, execution continues after the @code{REPEAT}.
                    528: 
                    529: @example
                    530: BEGIN
                    531:   @var{code}
                    532:   @var{flag}
                    533: UNTIL
                    534: @end example
                    535: 
                    536: @var{code} is executed. The loop is restarted if @code{flag} is false.
                    537: 
                    538: @example
                    539: BEGIN
                    540:   @var{code}
                    541: AGAIN
                    542: @end example
                    543: 
                    544: This is an endless loop.
                    545: 
                    546: @subsection Counted Loops
                    547: 
                    548: The basic counted loop is:
                    549: @example
                    550: @var{limit} @var{start}
                    551: ?DO
                    552:   @var{body}
                    553: LOOP
                    554: @end example
                    555: 
                    556: This performs one iteration for every integer, starting from @var{start}
                    557: and up to, but excluding @var{limit}. The counter, aka index, can be
                    558: accessed with @code{i}. E.g., the loop
                    559: @example
                    560: 10 0 ?DO
                    561:   i .
                    562: LOOP
                    563: @end example
                    564: prints
                    565: @example
                    566: 0 1 2 3 4 5 6 7 8 9
                    567: @end example
                    568: The index of the innermost loop can be accessed with @code{i}, the index
                    569: of the next loop with @code{j}, and the index of the third loop with
                    570: @code{k}.
                    571: 
                    572: The loop control data are kept on the return stack, so there are some
                    573: restrictions on mixing return stack accesses and counted loop
                    574: words. E.g., if you put values on the return stack outside the loop, you
                    575: cannot read them inside the loop. If you put values on the return stack
                    576: within a loop, you have to remove them before the end of the loop and
                    577: before accessing the index of the loop.
                    578: 
                    579: There are several variations on the counted loop:
                    580: 
                    581: @code{LEAVE} leaves the innermost counted loop immediately.
                    582: 
                    583: @code{LOOP} can be replaced with @code{@var{n} +LOOP}; this updates the
                    584: index by @var{n} instead of by 1. The loop is terminated when the border
                    585: between @var{limit-1} and @var{limit} is crossed. E.g.:
                    586: 
                    587: 4 0 ?DO  i .  2 +LOOP   prints 0 2
1.3       anton     588: 
1.1       anton     589: 4 1 ?DO  i .  2 +LOOP   prints 1 3
                    590: 
                    591: The behaviour of @code{@var{n} +LOOP} is peculiar when @var{n} is negative:
                    592: 
                    593: -1 0 ?DO  i .  -1 +LOOP  prints 0 -1
1.3       anton     594: 
1.1       anton     595:  0 0 ?DO  i .  -1 +LOOP  prints nothing
                    596: 
                    597: Therefore we recommend avoiding using @code{@var{n} +LOOP} with negative
                    598: @var{n}. One alternative is @code{@var{n} S+LOOP}, where the negative
                    599: case behaves symmetrical to the positive case:
                    600: 
                    601: -2 0 ?DO  i .  -1 +LOOP  prints 0 -1
1.3       anton     602: 
1.1       anton     603: -1 0 ?DO  i .  -1 +LOOP  prints 0
1.3       anton     604: 
1.1       anton     605:  0 0 ?DO  i .  -1 +LOOP  prints nothing
                    606: 
                    607: The loop is terminated when the border between @var{limit-sgn(n)} and
                    608: @var{limit} is crossed. However, @code{S+LOOP} is not part of the ANS
                    609: Forth standard.
                    610: 
1.4       anton     611: @code{?DO} can be replaced by @code{DO}. @code{DO} enters the loop even
                    612: when the start and the limit value are equal. We do not recommend using
                    613: @code{DO}. It will just give you maintenance troubles.
1.1       anton     614: 
1.5       anton     615: @code{UNLOOP} is used to prepare for an abnormal loop exit, e.g., via
                    616: @code{EXIT}. @code{UNLOOP} removes the loop control parameters from the
                    617: return stack so @code{EXIT} can get to its return address.
                    618: 
                    619: Another counted loop is
                    620: @example
                    621: @var{n}
                    622: FOR
                    623:   @var{body}
                    624: NEXT
                    625: @end example
                    626: This is the preferred loop of native code compiler writers who are too
                    627: lazy to optimize @code{?DO} loops properly. In GNU Forth, this loop
                    628: iterates @var{n+1} times; @code{i} produces values starting with @var{n}
                    629: and ending with 0. Other Forth systems may differently, even if they
                    630: support @code{FOR} loops.
                    631: 
1.1       anton     632: 
                    633: @contents
                    634: @bye
                    635: 

FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>