Home to Futurlogics


Below is James Hall's introduction to FORTH as he sees it.


						James N. Hall
						West Jordan, Utah
						84084

	Beginners find Forth difficult to learn, Some say that the peculiar  
postfix syntax is the cause.  The postfix notation can cause the novice to be 
frustrated with an initially awkward syntax protocol.  Admittedly, postfixed
expressions are not exactly english; but, what do you expect, English is for
humans to communicate with humans.  Incidently some human languages are more
or less postfix in some degree.  Forth is a language for humans to talk or
communicate with computers.  The Forth philosopy is first simplity for the
machine; then make it readable for the programmer through judicious choice
of tokens for words and then comments written in actual english.  If a
non programmer needs to understand the code, then more explanations
and help files  are required. 

        Reading a computer language is essential to learning and understanding
it, Especially for the new recruit who needs to see many samples with a
good library for reference.  Forth has been accused of being a write only 
language.  If Forth is a write only langauge (word names can use the full
ascii code set except for 'space' 'tab' or white space in general) , it is 
not really caused by the postfix notation.  This is true because Forth is not
totally postfixed.  Actually it is only partially postfixed.  Since Forth has
both postfixed and prefixed notation, Forth is really what I term as MIXFIXED. 
There are good and purposeful reasons why Forth is mixfixed.  However for the
novice who may not have the stamina to continue with the up front confusion, 
the belief exists that computers are to make life easier.  Therefore the computer
language should reflect this expectation and not demand from the programmer what
the compiler can do for the programmer.  Yet, until the rest of the story is
known, the mixfixed notation of postfix and prefix words is a source of
confusion to those new to FORTH.  

Examples of the Forth mixfix syntax:

1 1 +                                                    \ postfix
variable newvar                                          \ prefix
: nameword words words ;                                 \ mixfix
: functionword create structurewords does> actionwords ; \ mixfix
12 34 functionword newdefiningword                       \ mixfix
' oldword is newword                                     \ mixfix

   . . . any number of mixed syntax combinations right.

	The Postfix syntax is ok, if Forth were consistently postfix for
those new to Forth but Forth is a mixture of Prefix and Postfix syntax!
Why is Forth not totally postfix at least for the new forth neophyte! 

	The switching between postfix and prefix is and was long term problem
with the writer who never seems to learn Forth.  For those who have not yet
gotten used to Forth mixfix notation, Please consider another look at postfix
notation and perhaps possible solutions to this problem with the confusing
MIXFIX syntax: The stack necessitates postfix operatives, stack pictures, 
and the input stream cause the prefix attribues of Forth.  Selecting the
right combination prefix and postfix can build an apparently INFIX notational
syntax.

        Stacks make postfix notation and syntax.  Input streams make prefix
notation.  Mixing postfix and prefix words make for MIXFIX notation.  Because
Forth uses both the input stream and a stack both notations are possible. 

        Setup a name stack so the outer interpreter 'sees' any "thing" that is
not found a 'word', then not a 'number' should be a <name> for the create word
to make a header.  'bl word' could be used also to load this name stack.  You
can type:

        1 2 34 55 66666 <ret> to load the data stack! 

        Why not type:

        SETSTRINGSTACK a b2 777 4c dd efgay newname <ret>

to load the name stack! 

Then a word like POP_STRINGSTACK could be part of CREATE instead of BL WORD. 
(the actual forth word used in the code below is BL_WORD for POP_STRINSTACK).

Then Syntax could be maintained consistent.  

Examples of nearly all postfix Forth:

1 1 +                                                \ postfix
newvar variable 12 newvar !                          \ postfix
13 newconst constant                                 \ postfix
new_colon_word       : ( a b n d -- f )
   forthwords moreforthwords anywords ; immediate    \ postfix
new_defining_word    : ( a n name --  )
   create structuring_words
   does>  ( addr -- f ) action_words ;               \ postfix
12 34 next_new_objectword new_defining_word          \ postfix
no_execute  oldword ' newword is                     \ postfix
forget unwanted_word(s)                              \ prefix *
                       or 
no_execute unwanted_word(s) forget                   \ postfix
newvar1 newvar2 newvar3 newvar4 newvar5  variables   \ postfix
newcon1 newcon2 newcon3 newcon4 newcon5  constants   \ postfix

*  forget due to effient code probably should be prefixed

All postfix and readably consistent.

	A variable called _POSTFIX could be used to switch between
postfix and mixed forth for backward compatability.  Or 
_POSTFIX ON or _POSTFIX OFF etc. 

        Another method is to use vectored execution as below coded.
and the switch between postfix notation and mixfixed notation can
be accomplished by executing the words MIX_FIX or POST_FIX  to go
between the to notational syntaxes.

 	Here is the code to to be inserted in F-PC by Tom Zimmer
source for the Kernel3.seq.

/*****************************************************************/
/***********************POSTFIX FORTH*****************************/
/*****************************************************************/

\ \ \ \ \ here is postfix forth inserted code
\ \ \ \ \ custom post fix params and vars by james n. hall 01-15-94

\ VARIABLE POST_FIX        (  post fix input of strings ) \ no longer used.
32 CONSTANT TOKEN                            \ max length of a word name 
288 CONSTANT SIZE_OF_SHOVEL                  \ any one who has used a shovel
                                             \ knows it is postfix in action.
VARIABLE SHOVEL  SIZE_OF_SHOVEL    ALLOT     \ array structure size
VARIABLE 0SHOVEL                             \ begining of the structure
VARIABLE TOP_SHOVEL                          \ end of the structure
VARIABLE ^SHOVEL                             \ pointer to current name
: INIT_SHOVEL   ( -- )                       \ initialize the structure
                SHOVEL ^SHOVEL !
                SHOVEL 0SHOVEL !
                SHOVEL SIZE_OF_SHOVEL + TOKEN - TOP_SHOVEL !
                SHOVEL SIZE_OF_SHOVEL BLANK ;

: SHOVEL_FULL?  ( -- )                       \ too many names
               ^SHOVEL @ TOP_SHOVEL @  U>
               ^SHOVEL @ TOP_SHOVEL @  = OR IF
                ABORT" NAMES FULL" THEN ;

: NAMES?        ( -- f )                      \ any names?
               ^SHOVEL @ TOP_SHOVEL @  U>
               ^SHOVEL @ TOP_SHOVEL @  = OR IF
                ." NAMES STACK FULL" 0
               ELSE  TRUE
               THEN ;

: SHOVEL_NULL?  ( -- )                      \ empty of names?
              ^SHOVEL @ 0SHOVEL @   U<
              ^SHOVEL @ 0SHOVEL @ = OR IF
              INIT_SHOVEL ABORT" NAMES EMPTY" THEN ;

: SHOVEL?     ( -- )                        \ status of shovel structure?
              SHOVEL_FULL? SHOVEL_NULL? ;

: SHOVEL++    ( -- )                        \ increment shovel pointer 
              SHOVEL_FULL? ^SHOVEL @  DUP TOP_SHOVEL @ U<  IF
                                        TOKEN + ^SHOVEL !  THEN  ;
: SHOVEL--    ( -- )                        \ decrement shovel pointer 
              SHOVEL_NULL? ^SHOVEL @  DUP 0SHOVEL @    U>  IF
                          TOKEN - ^SHOVEL  THEN !  ;

\  OLDER VERSION
\ : BL_WORD     ( -- )
\              POST_FIX @ IF SHOVEL-- ^SHOVEL  @
\                         ELSE BL WORD THEN ;

: (BL_WORD)   ( -- ) BL WORD ;

: (SHOVEL)    ( -- ) SHOVEL-- ^SHOVEL @ ;     \ pop name off shovel

DEFER BL_WORD ' (BL_WORD) IS BL_WORD          \ vector in prefix here

: SHVDEPTH    ( -- depth )                    \ name stack depth
              ^SHOVEL @ DUP TOP_SHOVEL @ U> IF TOP_SHOVEL @ THEN
              0SHOVEL @ - TOKEN / ;

\ the above is inserted just before INTERP in the fpc kernel3.seq

: INTERP        ( -- )
                BEGIN   ?STACK DEFINED
                        IF     EXECUTE
                        ELSE   NUMBER  DOUBLE? NOT IF  DROP  THEN
                        THEN   FALSE DONE?
                UNTIL   ;

\ \ \ \ Also Add the following  where ?MISSING is coded
\ \ \ \ to make the POSTFIX forth work maybe just before ?MISSING

: ?MISSING?      ( f -- )                      \ another version of ?MISSING
                 IF
                     SPACE HERE COUNT TYPE
                     TRUE ABORT"  <- What? "
                 THEN    ;

: ?MISSING!      ( f -- )  \ \ \ \ / / / / here is where all the work is done
                IF HERE C@ TOKEN U< IF
                            NAMES? IF
                            ^SHOVEL @  32 BLANK
                            HERE C@ ^SHOVEL @ C!
                            HERE  COUNT ^SHOVEL @ 1+ SWAP CMOVE DROP
                            ELSE ."  Name litter" drop
                            THEN SHOVEL++
                         ELSE ."  Name litter too long" drop
                         THEN
                THEN    ;

: FORGET        ( -- )                     \ prefix is still the most effient
                BL WORD ?UPPERCASE DUP CURRENT @ HASH @
                (FIND) 0=  ?MISSING? DUP >VIEW (FRGET) ;

\ \ \ \ all of the above is found in kernel3.seq in Tom Zimmers F-PC

\ \ \ \	The changes needed in STATUS.SEQ for a visual of the name stack

: <.STAT>       ( --- )
                PRINTING @ ?EXIT        \ NO status if printing
                SAVECURSOR
                BASE @ >R DECIMAL
                0 0 AT >ATTRIB1
                ."  C - " SP@ HERE - 0 1000 UM/MOD NIP (U.) TYPE ." k : - "
                #LISTSEGS XHERE DROP XSEG @ - - 16 *D
                1000 UM/MOD NIP (U.) TYPE ." k"
                2 SPACES DEPTH
                IF      >ATTRIB4 ." P" DEPTH (U.) DUP>R TYPE
                        4 R> - SPACES >ATTRIB1
                ELSE    ." P0" THEN 2 SPACES SHVDEPTH
                IF >ATTRIB3 ." N" SHVDEPTH (U.) DUP>R TYPE
                        4 R> - SPACES >ATTRIB1
                ELSE    ." N0" THEN
                2 SPACES SEQHANDLE >HNDLE @ -1 =
                IF      SEQHANDLE DUP CLR-HCB PATHSET DROP
                        -2 SEQHANDLE >HNDLE !
                THEN    .SEQHANDLE COLS #OUT @ - SPACES
                VOCV                            \ if vocabulary showing is on
                IF      COLS 11 - 1 AT >ATTRIB3
                        CURRENT @ BODY> >NAME SPACE %.ID EEOl
                        >ATTRIB1
                        #VOCS 1- CONTEXT OVER 0
                        DO      DUP @ ?DUP 0= IF NIP I SWAP LEAVE THEN
                                COLS 11 - I 2+ AT
                                BODY> >NAME SPACE %.ID EEOL 2+
                        LOOP    DROP
                        COLS 11 - OVER 2+ AT SPACE
                        ['] ROOT >NAME %.ID EEOL >NORM
                        1+ #VOCS OVER - BOUNDS OVER MIN
                        ?DO     COLS 11 - I 2+ AT 11 SPACES
                        LOOP
                THEN    >ATTRIB1
                COLS 7 - 0 AT SPACE
                DTBUF OFF
                GETTIME DROP BUILD-HM DTBUF COUNT TYPE SPACE >NORM
                R> BASE !
                RESTCURSOR ;

: .STATUS       ( -- )
                DEFERS STATUS
                ?STACK
                STATV @
                if      <.STAT>
                THEN    ;


\ \ \ \  Below is a file to be fload after metacompiling and extending the
\ \ \ \  above code to a full FPC with postfix capabilities
 
\  post_fix on              \ no longer used.

INIT_SHOVEL

: POST_FIX ( -- )                            \ vector postfix forth
       ['] (SHOVEL) IS BL_WORD
       ['] ?MISSING! IS ?MISSING  ;

: MIX_FIX  ( -- )                            \ vector mixfix forth
       ['] (BL_WORD) IS BL_WORD
       ['] ?MISSING? IS ?MISSING   ;

' POST_FIX ALIAS DEFINE                      \ suggestions for readability
' MIX_FIX  ALIAS END.

' POST_FIX ALIAS PRESENT
' MIX_FIX  ALIAS END.

' POST_FIX ALIAS MAKE
' MIX_FIX  ALIAS END.

' POST_FIX ALIAS LET
' MIX_FIX  ALIAS END.

POST_FIX

VARIABLES : SHVDEPTH DUP 0= IF ABORT" Names Stack Empty" THEN
            0 ?DO VARIABLE LOOP ;

DD : SHOVEL 288 DUMP ;                         \ disp shovel structure

.SHV : SHVDEPTH U. ;
CLEAR_STACK : DEPTH 0 DO DROP LOOP ." Stack Cleared " ;
\ post_fix off
.NAMES :   ( -- )
    0SHOVEL @   SHVDEPTH 0 ?DO  CR
                          DUP I TOKEN * + COUNT TYPE
                          LOOP DROP ;
AS :   ( -- )          \ present <name>
                        BL WORD
                        HERE C@ TOKEN U< IF
                            NAMES? IF
                            ^SHOVEL @  32 BLANK
                            HERE C@ ^SHOVEL @ C!
                            HERE  COUNT ^SHOVEL @ 1+ SWAP CMOVE DROP
                            ELSE ."  Name litter" drop
                            THEN SHOVEL++
                         ELSE ."  Name litter too long" drop
                         THEN ;