Jump to content
IGNORED

Machine Forth OMG


TheBF

Recommended Posts

And more proof that it's best to remove code from the inner loop.

 

Just changing OVER + SWAP  to the optimized word BOUNDS dropped the time to 22 seconds.


DECIMAL
: FIB
     0 #  1 #
     ROT 0 #
     DO
       \ OVER + SWAP
       BOUNDS
     LOOP
     DROP
;

PROG: MAIN
     1000 # 0 #
     DO
        I FIB DROP
     LOOP
     NEXT,      \ Return to Forth
END.

The difference in the code inside the loop is:

 

OVER + SWAP 

       TOS DPUSH,  
2 (SP) TOS MOV,
  *SP+ TOS ADD,
    TOS R0 MOV,  
  *SP  TOS MOV,  
    R0 *SP MOV,

BOUNDS 

  *SP R1 MOV, 
 TOS *SP ADD, 
  R1 TOS MOV,

Chuck's machine Forth does not have SWAP. 

 

  • Like 2
Link to comment
Share on other sites

Tail Call Optimization Oversight

 

I have been working on making some solid VDP library routines in this weird language and when I started applying my fancy new tail call optimization I discovered something I completely missed.

 

Example Sub-routine with tail-call optimized

: PAGE   ( -- )  0 # 768 # 32 # VFILL -;

This code clears the screen in 32 column mode.  It is just a wrapper for VFILL and three parameters to fill VDP RAM at address 0 with 768,  ASCII 32 characters.

Notice we end with -;  and not the normal ;   

 

This is how you end a sub-routine when you know the last word is another sub-routine and so you can eliminate the "return from sub-routine" code.

 

-;  looks back in the code and  removes the normal BL @VFILL  and replaces it with  B @VFILL.  Still blows my mind that this works. :)

 

BUT!   every sub-routine in this system has a preamble of two instructions to save R11 on the return stack like this:

DECT R7
MOV R11,*R7

Since we are not "calling VFILL" but using Branch we don't need to make room on the stack and save R11. 

This means we don't want to enter at the normal entry address but 2 CELLS after.  (CELL is Forth speak for an integer memory location) 

 

So the definition for  -;   has been changed to the code below and it seems to work perfectly now. (at least until I find the next bug) :)

\ tail call optimizing semi-colon
H: -; ( --  )
    LOOKBACK   ( addr )   \ get entry address of sub-routine
    2 CELLS +  ( addr' )  \ move past sub-routine RPUSH instructions
    -04 TALLOT            \ erase BL @addr
    ( addr')  @@ B,       \ compile a branch to the NEW sub-routine
;H

Edit: 

The next thing I should do is look back before the sub-routine address and make sure there is BL instruction.

This could error out  if not or I could make tail-call removal automatic.

 

  • Like 2
  • Thanks 1
Link to comment
Share on other sites

How to choose the best addressing mode with a very "dumb" compiler

 

I have been struggling with keeping the Machine Forth as "normal" as possible because my old brain needs that.

So as mentioned I decided that data like variables and constants simple pushed themselves onto the data stack.

This keeps it normal but consumes three instructions for each argument. ( two for the push and one for LI instruction) 

9900 has that wonderful symbolic mode where you can move things memory to memory. So how best to write that when compiler is too stupid to figure it out?

Constants are a not issue because at the moment they only generate code when you use them in the program.

Variables are a real memory address in your program with the data held there. I made this word to retrieve the DATA field of a variable (the address) 

: DATAFLD@  ( <NAME> -- addr)  ' >BODY @  REL>TARG ;

It looks up the variable, fetches the contents and converts the address from relative to the real target address in the program image.

 

Then we can create 

: LET   DATAFLD@  ; \ get address of a variable
: :=    DATAFLD@  ( addr1 addr2) SWAP @@ ROT @@ MOV, ;

Using these words we can create:

VARIABLE X
VARIABLE Y

LET X := Y   \ :-))) 

LOL.  This compiles  to:

 

MOV @X,@Y 

 

Not very Forthy but it's the best I can come up with.   :) 

 

  • Like 4
Link to comment
Share on other sites

Changed my mind on syntax for symbolic addressing.

 

To stay more in the Forth syntax I am re-purposing ' (tick) when you are in the TARGET compiler mode. 

 

In machine Forth tick will just be an alias for DATAFLD@ and return the data field address of a variable in the program image. 

This is the common factor.

 

EDIT:   Changed  :=   to '!    Seems more consistent.

: '!    ( addr1 addr2) SWAP @@ ROT @@ MOV, ;

 

When I want to do a memory to memory move  the syntax becomes:

VARIABLE X
VARIABLE Y

' X ' Y  '! 

 

It becomes very clear why compilers use types for data so the compiler can decide how to handle things. 

I will avoid going there for now to see what can be accomplished this way.

  • Like 4
Link to comment
Share on other sites

1 hour ago, Lee Stewart said:

 

Aha! So back to FigForth’s definition of tick.

 

...lee

lol.  Yes indeed. I hadn't thought of that.   :)

Great catch.  

 

This thing is remarkably hard to get everything working right.  As you know well, I have a unique ability to miss the details in my enthusiasm ... ?

@Tursi is my saviour because I can open 2 Classic99 windows. One has the compiler running in over-drive and the other opens the binary programs.

Two debugger windows lets me see the Code generated and size of code generated under different conditions and the other debugger lets me step through the code.

I can't imagine how much longer this would take on real iron.

 

I have written a simple VDP driver to test the optimizer and the tail-call optimizer.  It's starting to feel stable.  I found a bunch of minutia that I had not considered over the last few days.

I am trying to use Machine Forth rather than ALC when the code generated is the same but ALC gives nice things like accessing the 2nd item on the stack seamlessly so I use that stuff in the primitives where is simply better.

 

Here is what seems to be a solid VDP driver. It is light-weight  with no scroll or safety net and I have not done a VMBR yet. 

It compiles with 384 bytes.  The POP/PUSH optimizer has not impact because there are no big interfaces to other words.

However anything that ends with DROP will be optimized in a program that calls something that starts with DUP. 

I am slowly getting used to this coding style but it is not any easier however the speed it fun.

 

Using the tail-call optimization makes you try and organize things so that words end with another word and not inline code.  That's another new thing to think about.

 

Spoiler

\ VDPDRVR.FTH

TARGET                 \ Use TARGET wordlist (to compile code)

HEX
8800 EQU VDPRD
8802 EQU VDPSTS
8C00 EQU VDPWD
8C02 EQU VDPWA

: VDPA! ( Vaddr -- ) \ set vdp address (read mode)
          0 LIMI,
          TOS SWPB,
          TOS VDPWA @@ MOVB,
          TOS SWPB,
          TOS VDPWA @@ MOVB,
          DROP
;

: VC@    ( addr -- c)
          VDPA!
          VDPRD @@ TOS MOVB,
          TOS 8 SRL,
;

: VC! ( c Vaddr -- )  4000 #OR VDPA!  VDPWD #C!  ;

HEX
\ * VDP write to register. Kept the TI name
: VWTR   ( c reg -- ) \ Usage: 5 7 VWTR
           ><              \ register goes to left side
          *SP+ TOS ADD,
           8000 #OR VDPA!
           DROP
;

: VFILL ( Vaddr cnt char -- ) \ Mixing ASM & machine forth
           TOS SWPB,
           TOS R1 MOV,
           R0  DPOP,
           DROP               \ Vaddr now in TOS
           4000 #OR VDPA!     \ set the write address and DROP TOS. (clean up)
           R3 VDPWD LI,       \ VDP port faster in a register
           BEGIN
              R1 R3 ** MOVB,
              R0 DEC,
           -UNTIL
;

HEX
: TYPE+  ( addr len ) \ Common factor:
\ ** Set VDP address (VDPA!) which disables interrupts BEFORE use
         *SP+ AREG MOV,
          R3 8C00 LI,    \ 12% faster to use a register
          BEGIN
            *AREG+  R3 ** MOVB,
            1-
         -UNTIL
          DROP ;

: VWRITE ( addr Vaddr len -- ) SWAP 4000 #OR VDPA! TYPE+ -;

\ ____( Simple Screen I/O)_______
\ *There is no protection for running off the screen! :-)
DECIMAL
   VARIABLE C/L     \ characters per line
   VARIABLE COL
   VARIABLE ROW
32 CONSTANT BL      \ space character

HEX
: AT-XY  ( x y --) ' COL #!  ' ROW #! ;  \ 2 instructions MOV TOS,@COL etc.
: CR     ( -- ) ' C/L  ' ROW  '+!  ;     \ 1 instruction. ADD @C/L,@ROW

\ COMPUTE video screen address from ROW & COL
: VPOS   ( -- Vaddr)  ROW @  C/L @ *  COL @  +  ;

HEX
: TYPE   ( addr len -- ) VPOS  OVER  ' COL #+!  4000 #OR VDPA! TYPE+ -;
: EMIT   ( char -- ) VPOS  COL 1+!  VC!  -;
: SPACE  ( -- )      BL EMIT -;

DECIMAL
\ Graphic mode clear screen
: PAGE   ( -- )
     COL OFF   ROW OFF
     VPOS  768 # 32 # VFILL -;

 

 

Here is a little test program used to debug the VDP driver

\ hello world in machine Forth Demo     Sept 23 2021  Fox
\ compiles to 128 bytes

COMPILER              \ Use compiler wordlist (for interpreted words)
   NEW.
   HEX A000 ORIGIN.
   OPT-OFF

   INCLUDE DSK2.VDPDRVR

TARGET
\ --------
CREATE TXT  S" Hello World! " S,

PROG: MAIN
HEX
      8300 WORKSPACE    \ Fast ram for registers
      83BE RSTACK       \ and return stack
      83FC DSTACK       \ and Data stack
      17 # 7 # VWTR

DECIMAL
      32 # C/L !        \ init chars/line
      BEGIN
        PAGE
        CHAR 1 # DUP EMIT 1+ DUP EMIT 1+  EMIT

        3 # 0 # AT-XY
        9 # FOR
            TXT COUNT TYPE  SPACE
        NEXT

        13 # 13 # AT-XY
        TXT 1+ VPOS 5 # VWRITE
     AGAIN
END.

COMPILER SAVE DSK2.HELLO5

The video shows the program running.

 

 

If you have nothing else to do here is the current Compiler.

Spoiler

\ MACHINE FORTH COMPILER     Dec 14, 2020  Brian Fox, Kilworth Ontario
\ This file compiles with Camel99 Forth V2.6x in DSK1.

\ *** ADDED PENDING DROP   ?DROP   concept to optimizer ***

\ The Machine Forth disk should be in DSK2. 
\ To build the cross compiler your need Editor/Assembler Cartridge
\ 1.  Select menu option 5 "Run Program File"
\ 2.  At the prompt type: DSK1.CAMEL99 
\ 3.  When Camel Forth is loaded type:  INCLUDE DSK2.MACHFORTH
\ 4.  The machine forth compiler is ready when the black screen appears 

\ *To cross-compile a program
\  With the MACHFORTH ready type: INCLUDE <DSK2.MYPROGRAM>

\ 4.  See the demo programs provided for examples
\ 5.  After your program compiles type SAVE <DSK1.PROGNAME>
\              -OR-
\     You can place the SAVE command at the bottom of your
\     program to save it automatically after compiling.
\
\ 6.  Type FORTH BYE to return to TI-99 Title screen
\ 7.  Use E/A menu 5 and RUN your saved program.
\ ________________________________________________________

NEEDS LOAD-FILE FROM DSK1.LOADSAVE
NEEDS .S        FROM DSK1.TOOLS
NEEDS DEFER     FROM DSK1.DEFER
NEEDS ELAPSE    FROM DSK1.ELAPSE
NEEDS U.R       FROM DSK1.UDOTR

NEEDS FORTH     FROM DSK1.WORDLISTS
NEEDS ORG       FROM DSK2.MFORTHASM

CR .( Machine Forth special registers & modes...)
ONLY FORTH ALSO XASSEMBLER DEFINITIONS
4 CONSTANT TOS
: (TOS)  TOS () ;
: *TOS   TOS ** ;
: *TOS+  TOS *+ ;

6 CONSTANT SP
: (SP)   SP () ;
: *SP    SP ** ;
: *SP+   SP *+ ;

7 CONSTANT RP
: (RP)   RP () ;
: *RP    RP ** ;
: *RP+   RP *+ ;

8 CONSTANT I  \ loop index register
: (I)    I ()  ;
: *I     I **  ;
: *I+    I *+  ;

9 CONSTANT AREG  ( "address register")
: (AREG)   AREG () ;
: *AREG    AREG ** ;
: *AREG+   AREG *+ ;

: *R10      R10 ** ; \ Forth NEXT while testing. Scratch in binary program
: *R11      R11 ** ; \ sub-routine linkage

\ PUSH & POP macros for DATA stack
: DPUSH,   ( src -- )  SP DECT,  *SP  MOV, ;
: DPOP,    ( dst -- )  *SP+      SWAP MOV, ;

\ PUSH & POP macros for RETURN stack
: RPUSH,  ( src -- ) RP DECT,  *RP   MOV, ;
: RPOP,   ( dst -- ) *RP+      SWAP  MOV, ;

\ _________________________________________________
CR .( CROSS-COMPILER Name Spaces)
FORTH DEFINITIONS
VOCABULARY MFORTH     \ for mforth compiler words
VOCABULARY TARGETS   \ for words in the compiled program

: HOST     ONLY FORTH DEFINITIONS ;

: COMPILER
      ONLY FORTH ALSO XASSEMBLER
      ALSO MFORTH DEFINITIONS ;

: TARGET
      ONLY XASSEMBLER ALSO MFORTH
      ALSO TARGETS ALSO TARGETS DEFINITIONS ;


\ __________________[ pop/push optimizer ]____________________
COMPILER
HEX
 C136 CONSTANT 'DROP'  \ machine code for DROP
VARIABLE DROPS         \ count when DROP, is executed
                       \ means TOS has been refilled ie: in USE
VARIABLE DUPS          \ # of DUPS made
VARIABLE OPTS          \ # of optimizations made

: DUP,     ( n -- n n)  TOS DPUSH, DUPS 1+! ;  \ normal dup
: DROP,    TOS DPOP,  DROPS 1+! ; \ count each drop

: LOOKBACK ( -- u)  THERE 2- @ ; \ fetch previous instruction code

: OPT-DUP, ( n -- n ?n)   \ SMART dup
  LOOKBACK 'DROP' =     \ look back for DROP
  IF -2 TALLOT          \ move target dictionary back 1 cell
      OPTS 1+!          \ count the optimization
   ELSE
        DUP,            \ we must DUP,
   THEN ;

\ SMARTDUP,
\ At the end of many words there is a DROP to refill the TOS register
\ This is one 9900 instruction. (>C136)
\ SMARTDUP uses this instruction as a cue that TOS register is free to use
\ and entire DROP/DUP code can be omitted.
\ *Where possible end your code with DROP rather than putting it earlier
\ so that SMARTDUP can take advantage of it.

DEFER SMARTDUP,     ' DUP, IS SMARTDUP,   \ default is unoptimized

\ _______________________________________________
\ SWAP BYTE optimizer
: ?SWPB,  ( n -- n)
         LOOKBACK 0984 =   \ look back for "SRL R4,8"
         IF -2 TALLOT      \ remove SRL
         ELSE  TOS SWPB,   \ we need SWPB
         THEN
;

\ _______________________________________________
COMPILER
\ Rename HOST FORTH version of colon/semi-colon.
\ This let's us create Assembler macros as Forth words
\ and later to define target compiler colon & semi-colon.
: ;H    POSTPONE ;  ;  IMMEDIATE
: H:    :  ;H

\ tail call optimizing semi-colon
H: -; ( --  )
    LOOKBACK   ( addr )   \ get entry address of sub-routine
    2 CELLS +  ( addr' )  \ move past sub-routine RPUSH instructions
    -04 TALLOT            \ erase BL @addr
    ( addr')  @@ B,       \ compile a branch to the NEW sub-routine
;H

\ Here we steal Words from Forth so the Mforth COMPILER has them also, like
\ comments etc.  When we invoke TARGET we are cut-off from Forth VOCABULARY.
H: \    1 PARSE 2DROP ; IMMEDIATE
H: (    POSTPONE (  ;H  IMMEDIATE  ( borrowed from Forth )
H: COMPILER   COMPILER  ;H
H: HOST       HOST      ;H
H: TARGET     TARGET    ;
H: [HC]       HOST   ;H  IMMEDIATE
H: [TC]       TARGET ;H  IMMEDIATE
H: [CC]       COMPILER ;H IMMEDIATE
H: >R         >R ;H
H: R>         R> ;H
H: CR         CR ;H
H: HEX        HEX ;H
H: DECIMAL    DECIMAL ;H
H: SWAP       SWAP ;H
H: THERE      THERE ;H
H: INCLUDE    INCLUDE  ;H

\ COMPILER  COLON is the just the Host forth's colon
H: ;    POSTPONE ;  ;H  IMMEDIATE
H: :    :  ;H

\ Cross-compiler variables and constants
HOST HEX
VARIABLE LORG     2000 LORG !   \ LORG is TI-99 load address
VARIABLE XSTATE

       2000 CONSTANT CDATA  \ CODE compiles to this buffer
CDATA CELL+ CONSTANT 'BOOT  \ holds program boot address

\ compute diff. between actual load-address and image buffer
: OFFSET   ( -- n)  LORG @ CDATA -  ;
: REL>TARG  ( relocated -- target)  OFFSET - ;

\ run the program at target memory
CODE (RUN)  ( addr -- ) 0454 ,  NEXT,  ENDCODE \  *TOS B, DROP,

COMPILER
: RUN   ( addr --)
       DUP 3FFE 2004 WITHIN ABORT" ORG not in Low RAM"
      (RUN) DROP ;

\ cross-compiler directives
: NEW.
   1000  2000  0 VFILL     \ erase VDP RAM 8K block
   CDATA 2000 FF FILL      \ fill 8K program space with FFFF
   CDATA  ORG              \ program begins after the intial branch & address
   FFFF @@ B,              \ Compile 1ST instruction. branch to bad address
  ['] TARGETS >BODY OFF    \ erase words in TARGETS wordlist
   DROPS OFF  OPTS OFF
   DUPS  OFF
;

.( .)
: ORIGIN.   ( addr ) DUP 2000 U< ABORT" ORG < 2000"  LORG ! ;

: EVEN.   TDP @ ALIGNED TDP ! ;

\ target image fetch and store take relocated addresses and convert them
: T!      ( n relocated -- ) REL>TARG ! ;
: T@      ( relocated -- n)  REL>TARG @ ;

: DATAFLD@ ( <NAME> -- addr)  ' >BODY @  REL>TARG ;

\ NEEDS SAVE FROM DSK2.MFORTHSAVE
\ ______________________________________________________________
\ data structure creation
COMPILER
\ optimizing this DUP is hard. Many times you must free up the TOS.
: LIT,  ( n -- )
         DUP,  TOS SWAP LI,  ;

\ Label creator returns relocated TARGET address when executed
: L:    THERE REL>TARG  CONSTANT ;   ( this Host Forth CONSTANT)

: EQU   ( n -- <NAME>) CONSTANT ;  \ just give the compiler the value

: CONSTANT ( n -- n)  \ create the compiler's constant
      CREATE   ,              \ remember the value
      DOES> ( pfa )
           @  LIT, ; \ compile constant as a literal no.

\ *IDEA*  make a TAG variable with coded values for data types.
: CREATE ( -- addr)
        CREATE THERE ,     \ remember the target address
        DOES> @  REL>TARG  LIT,  ;   \ pushes address onto stack

: ADDR ( n -- n)  \ Special kind of constant goes into AREG
      CREATE   ,
      DOES> ( pfa ) @   AREG SWAP LI,  ;

\ mforth data structure words
: VARIABLE  ( -- addr) CREATE  0000 T, ;

: ALLOT    ( n --) TALLOT ;

\ compile text into the TARGET program image. Use THERE
: S, ( c-addr u -- ) THERE OVER 1+ TALLOT PLACE  EVEN. ;
: S"  ( -- addr len)  [CHAR] " PARSE ;

\ ______________________________________________________________
\ colon definitions
COMPILER
\ Machine Forth colon/semi-colon (creates nestable sub-routines)
: M:
\ compile time action
   CREATE  !CSP
           THERE ,       \ remember the relocated address
           R11 RPUSH,   \ compile "enter sub-routine" code

 \ Runtime action: (when we invoke this word)
         DOES> @  REL>TARG ( addr) @@ BL, ; \ fetch address, compile BL to address

: ;M      R11 RPOP,  RT,  ;  \ compile exit sub-routine code

\ ______________________________________________________________
\ Forth virtual machine setup directives
: WORKSPACE ( addr --) LWPI, ;       \ Forth workspace
: DSTACK    ( addr --) SP SWAP LI, ; \ data stack
: RSTACK    ( addr --) RP SWAP LI, ; \ return stack

: PROG: ( <label> -- taddr)
  CREATE !CSP
     THERE REL>TARG DUP ,  \ record program entry in this word and...
     'BOOT !               \ store relocated address in program header
     XSTATE ON
  DOES> @
;

: END.  ?CSP
        TDP @ 3FFF > ABORT" Prog > 8K"
        XSTATE OFF ;

\ _________________________________________________
HOST CR .( Structured branching and looping )
COMPILER
\ compile an offset byte into the 2nd byte of a JUMP instruction
: OFFSET, ( byte --)  2- 2/ SWAP 1+ C! ;
: <BACK   ( addr addr' -- ) TUCK -  OFFSET, ;

: -IF    ( -- $$)   THERE 0 JLE, ; \ goto THEN if TOS>0
: IF     ( -- $$)   THERE 0 JEQ, ; \ goto THEN if TOS=0
: THEN   ( addr --) THERE OVER -  OFFSET, ;
: ELSE   ( -- $$ )  THERE 0 JMP,  SWAP THEN ;

COMPILER
: BEGIN   THERE ;  \ REMEMBER: THERE is the relocated address
: WHILE    IF SWAP ;  \ loop while TOS <> 0
: -WHILE  -IF SWAP ;  \ loop while TOS = 0
: AGAIN  ( addr --) THERE  0 JMP, <BACK ;
: UNTIL  ( addr --) THERE  0 JEQ, <BACK ; \ jump back until TRUE
: -UNTIL ( addr --) THERE  0 JNE, <BACK ; \ jump back until FALSE
: REPEAT ( addr -- ) AGAIN THEN ;

\ ______________________________________________________________
HOST CR .( Forth Intrinics)
\ These inline code generators are in the actual compiler
COMPILER
HEX
\  Moore's Machine Forth + a few extras
: DROP  ( n -- )  DROP,  ;
: DUP             SMARTDUP,  ;

: OPT-OFF   ['] DUP,     IS SMARTDUP, ;
: OPT-ON    ['] OPT-DUP, IS SMARTDUP, ;

: #     ( n -- )  DUP  TOS SWAP LI, ;
: #@    ( addr -- n)    DUP  @@ TOS MOV, ;
: @     ( TOSaddr -- n) *TOS TOS MOV, ;
: (@)   ( ndx addr)     (TOS) TOS MOV, ;

\ added byte operations: BFox
: #C@   ( addr -- c)   DUP  @@ TOS MOVB,  TOS 8 SRL, ;
: C@    ( TOSaddr -- c) *TOS TOS MOVB,  TOS 8 SRL, ;

: #!    ( n variable -- ) TOS SWAP @@ MOV,  DROP ; \ 6 bytes
: !     ( n TOSaddr --)  *SP+ *TOS MOV, DROP ;

: #C!   ( c addr --) TOS SWPB,  TOS SWAP @@ MOVB, DROP ; \ symbolic addressing
: C!    ( c addr --) 1 (SP) *TOS MOVB,  SP INCT,  DROP ;

[CC] .( .)
: 2*    ( n -- n ) TOS TOS ADD, ;
: 2/    ( n -- n)  TOS 1 SRA, ;
: INVERT ( n -- )  TOS INV, ;  ( ANS Forth name )
: AND,  ( n mask -- n) *SP INV, *SP+ TOS SZC, ; \ and stack values
: #AND  ( n n -- n ) TOS SWAP ANDI, ;  \ and TOS with literal number
: XOR   ( n n -- n)  *SP+ TOS XOR, ;   \ (option 1)
: +     ( n n -- n)  *SP+ TOS ADD, ;   \ (option 1) add on stack
: #+    ( n n -- )    TOS SWAP AI, DROP ;  \ (option 2) TOS + literal number

\ Naming convention for A register has been changed so it
\ uses the features of the TMS9900 CPU. It's dumb not to.

\ These Forth conventions are kept: @ means fetch and ! means store.
\ '*' suffix indicates the source register (A I or R) are indirect
\ memory access.
\ The A register can also be post-incremented after fetching natively
\ We have added indexed addressing as well with (A)@

\ @-A Dpush(T) A=A-cell T=[A]
\ !-A A=A-cell [A]=T Dpop(T)

: A@    ( -- n)  SMARTDUP,   AREG  TOS MOV, ;  \ Dpush(T) T=A
: *A@   ( -- n)  SMARTDUP,  *AREG  TOS MOV, ;  \ Dpush(T) T=*A
: *A@+  ( -- n)  SMARTDUP,  *AREG+ TOS MOV, ;  \ Dpush(T) T=*A  A=A+cell
: (A)@  ( u --)  SMARTDUP,  (AREG) TOS MOV, ;  \ Dpush(T) T=u@(A)

: #A!   ( addr --)  AREG SWAP LI, ; \ load A with literal number BF addition
: A!    ( addr -- ) TOS  AREG  MOV, DROP ;  \ A!   A=T  Dpop(T)
: *A!   ( addr)     TOS *AREG  MOV, DROP ;  \ !A  [A]=T Dpop(T)
: *A!+  ( n --)     TOS *AREG+ MOV, DROP ;  \ !A+ [A]=T A=A+cell Dpop(T)
: (A)!  ( n --)     TOS  SWAP (AREG) MOV, DROP ;

\ More optimal 9900 instructions for A register BFox
: A+!   ( n -- )  TOS AREG ADD,  DROP ;
: A1+!  ( -- )    AREG INC, ;
: A2+!  ( -- )    AREG INCT, ;
: A1-!  ( -- )    AREG DEC, ;
: A2-!  ( -- )    AREG DECT, ;

\ added byte operations. BFox
: *AC@   ( -- 0c00) SMARTDUP,  *AREG  TOS MOVB, TOS 8 SRL, ;
: *AC@+  ( -- 0c00) SMARTDUP,  *AREG+ TOS MOVB, TOS 8 SRL, ;
: *AC!   ( 0c00 --)  1 (TOS) *AREG MOVB,  DROP ;
: *AC!+  ( 0c00 --)  1 (TOS) *AREG+ MOVB, DROP ;

.( .)
\ return stack operators ........................
\ Names changed to better reflect 9900 Assembler
\ * Indicates indirect addressing mode
\ @ means fetch to TOS register
\ ! means store TOS register to Return stack
: R@    ( -- n )  SMARTDUP, *RP TOS MOV, ;  \ G*Dpush(T) T=[R] C
\ post incrementing
: R@+   ( -- n )  R@  *RP INCT, ;   \ G*  Dpush(T) T=[R] R=R+cell
\ pre decrementing
: -R@   ( -- n )  R@  *RP DECT, ;   \ G*  Dpush(T) R=R-cell T=[R]

: R!   ( n -- )  TOS *RP MOV,  DROP ;   \  *R->T  DROP(T)
\ post incrementing
: R!+  ( n -- )  R!   *RP INCT, ;      \ !R+ [R]=T R=R+cell Dpop(T)
\ pre decrementing
: -R!  ( n -- )  *RP DECT, R!   ;      \ R=R-cell [R]=T Dpop(T)

\ Single instructions on 9900. No brainer optimizing
: RDROP ( -- )    RP INCT, ;
: DUP>R ( n -- n) TOS *RP MOV, ;

: >R    ( n -- )  TOS *RP MOV,  DROP  ;        \ G*  Rpush(R) R=T Dpop(T)
: R>    ( -- n)   SMARTDUP,   *RP+ TOS MOV, ;  \ G*  Dpush(T) T=R Rpop(R)

\ For/next loop uses return stack for index. Counts down only.
\ Use A register for other indices.
: I@   ( -- n)  SMARTDUP,  I TOS MOV, ;   \ I@ Dpush(T) T=I
: I!   ( n --)  TOS I MOV, DROP ;        \ I=T  Dpop(T)
: I+!  ( n --)  TOS I ADD, DROP ;        \ BFox word
: I1-! ( -- )   I DEC, ;

\ now we can define the FOR NEXT LOOP
: FOR  ( n --)  I RPUSH,   I!  BEGIN ;
: NEXT ( -- )   I1-!  THERE 0 JOC, <BACK  I RPOP, ;

: CALL  ( addr --)  *TOS BL, DROP ;
: RET     *R11 BL, ;

\ _____________[ Chuck Moore Machine Forth Ends ]____________

\ ********* ANS/ISO Forth, 9900 Specific operators *********
: OVER  ( n1 n2 -- n1 n2 n1) TOS DPUSH,  2 (SP) TOS MOV, ;
: NIP   ( n1 n2 -- n2)  SP INCT, ;

\ ___________________________________________________________________
\ __[ Unique TMS9900 primitives ]__
: 1+   ( n -- n')   TOS INC, ;
: 2+   ( n -- n')   TOS INCT, ;
: 1-   ( n -- n')   TOS DEC, ;
: 2-   ( n -- n')   TOS DECT, ;
: 4*   ( n -- n')   TOS 2 SLA, ;
: 8*   ( n -- n')   TOS 3 SLA, ;

\ X -> Y    takes var from TOS to symbolic address
\ Less optimized
: ->  ( var1 -- )   DATAFLD@  *TOS SWAP @@ MOV, DROP  ;  \ assign var1 to var2

\ Accessing MEM2MEM feature of 9900 CPU saves memory big-time
: '     DATAFLD@  ;
\ X @ Y !  is 10 instructions, 14 bytes
\ ' X ' Y '!  is 1 instruction, 6 bytes. WINNER!
: '!    ( addr1 addr2) SWAP @@ ROT @@ MOV, ;
: '+!   ( addr1 addr2) SWAP @@ ROT @@ ADD, ;

: LSHIFT ( n -- n)  TOS SWAP SLA, ;
: RSHIFT ( n -- n)  TOS SWAP SRL, ;

\ inc/dec variables with direct addressing
: 1+! ( addr -- ) *TOS  INC,  DROP ;
: 2+! ( addr -- ) *TOS INCT,  DROP ;
: 1-! ( addr -- ) *TOS  DEC,  DROP ;
: 2-! ( addr -- ) *TOS DECT,  DROP ;
: +!  ( n addr --) *SP+ *TOS ADD,  DROP ; \ 6 bytes  \ 5 # X +!
: #+! ( n [addr] -- )  TOS SWAP @@ ADD,  DROP ;

: NOP    ( -- )     0 JMP, ;
: ABS    ( n -- n') TOS ABS, ;
: NEGATE ( n --n')  TOS NEG, ;
: OR     ( w w -- w ) *SP+ TOS SOC, ;
: #OR    ( -- )    TOS SWAP ORI, ;

\ 2 and 3 instruction words for ANS/ISO compatibility
: -     ( n n -- n') *SP+ TOS SUB, TOS NEG, ;
: UM*   ( n n -- d)  *SP  TOS MPY, R5  *SP MOV, ;
: *     ( n n -- n)  *SP+ R3 MOV,  TOS R3 MPY, ;
: ALIGNED ( n -- n)   TOS INC,  TOS -2 ANDI, ;
: AND   ( w w -- w ) *SP INV,  *SP+ TOS SZC, ;
: 2@    ( addr -- d) 2 (TOS) DPUSH,   *TOS TOS MOV, ; \ fetch double integer
: EXIT  ( -- )       R11 RPOP,  RT, ;

\ _______________________________________________________________
\ hi-level Forth additions for people less pure than Chuck Moore
: NOT  ( -- )  R1 STST,  R1 2000 ANDI, ;  \ invert EQ flag status
: ON   ( variable --) *TOS SETO, DROP ;
: OFF  ( variable --) *TOS CLR,  DROP ;
: ><   ( n -- )  TOS SWPB, ;

: BOUNDS ( adr len -- adr2 adr1) *SP R1 MOV, TOS *SP ADD, R1 TOS MOV, ;
: SWAP   ( n1 n2 -- n2 n1)      TOS R0 MOV,  *SP  TOS MOV,  R0 *SP MOV, ;

\ CUT n characters from left side of STRING (addr,len)
: /STRING ( addr len n -- addr' len' ) TOS *SP SUB,  TOS 2 (SP) ADD,  DROP ;
: ?TERMINAL ( -- ?)  DUP  0020 @@ BL,  NOT ; \ TI-99 ROM sub-routine

: COUNT  ( Caddr -- addr len )
         DUP               \ make a copy of addr
        *SP INC,           \ inc. past the count byte
        *TOS TOS MOVB,     \ put C@ inline to save space
         TOS 8 SRL, ;

\ Rename target number compilers to normal forth names
: ,     T, ;
: C,    TC, ;

\ Last definitions make the TARGET compiler.
\ Alias mforth compiler colon/semi-colon words into TARGET vocabulary
\ so they look like ':' ';' by using Camel Forth's H: and ;H
\ Yes it's confusing. Welcome to Forth cross-compilers.
COMPILER
H: :    M:  ;H
H: ;   ;M   ;H

HOST NEEDS SAVE  FROM DSK2.SAVEIMG

HEX
: COLD  PAGE
       ." Machine Forth Compiler V2  BFox"
       E1 7 VWTR
       COMPILER
       ABORT  ;

COLD

 

 

 

  • Like 3
Link to comment
Share on other sites

  • 4 weeks later...

One day, MACHFORTH will be a thing 

 

I have been doing some tail chasing with this project since I started out just trying to make it compile runnable code.

However now I want it to be a useable Forth programming system for TI-99. 

There is no standard way for cross-compiled Forth to operate so I am feeling my way along. 

 

I spent some time (ok a lot of time) re-thinking how to make this Machine Forth look more like normal Forth.

The problem is mostly about interpreting literal numbers correctly during interpretation and  during compilation.

In version 1, I used the # operator to compile the code to put a literal into the code.  I think Chuck Moore resorted to this as well.

(But it looks kind of ugly)

 

The solution was to create a "state" variable for the cross-compiler as Forth does internally. (DUH!) 

The thing that needed changing in the Forth REPL was the code that compiles a literal number.

Since Forth interprets and compiles it needs to either:

  1. Compile some code into the program image that safely puts a number onto the top of the Forth data stack when the program is running.
  2. Interpret the number which for Forth means put in onto the top of compiler's data stack and just leave it there.  

The determining control is the state variable.  In Camel99 Forth I have vectored the REPL  (read evaluate print loop) to use the LISPer's term.

So I re-wrote the REPL loop and changed one line that deals with compiling the literal number. 

VARIABLE XSTATE  \ CROSS-COMPILER state variable

: LIT,  ( n -- )
    XSTATE @ IF      \ IF we are compiling machine Forth code
       TOS DPUSH,    \ *SmartDUP does not work here.
       TOS SWAP LI,  \ compile n as a literal number into R4.
    THEN  ;

: <MFINTERP> ( i*x c-addr u -- j*x ) \ machforth compiler interpret loop
         'SOURCE 2!  >IN OFF
          BEGIN
              BL WORD DUP C@ ( -- addr len)
          WHILE
              FIND ?DUP
              IF ( it's a word)
                   1+ STATE @ 0= OR
                   IF   EXECUTE
                   ELSE COMPILE,
                   THEN
              ELSE ( it's a number)
                   COUNT NUMBER? ABORT" MF: Not recognized"
                   LIT,  ( This is the only real difference )
              THEN
              DEPTH 0< ABORT" MF: Compiler stack underflow"
          REPEAT
          DROP ;

I can vector the REPL loop from normal Forth numbers or  for cross-compiling numbers.

The place to do that is in the directives  COMPILER which needs normal Forth numbers and TARGET which is used when we are compiling to the "target" image. 

 

But of course that leads to a minor complication when writing Assembly language inside a colon definition because Forth assembler is interpreted. (No it really is) :) 

This is easily remedied with the [   ]   operators which turn off  and turn on the compiler like this:

: BYE
      [ 0 LIMI,
        83C4 @@ CLR,
        0000 @@ BLWP, ]
;

So that's not too hard to endure.

 

Another issue that came up is when I want to create Assembler macros but I think have a solution since I now have a command FORTH-REPL  so I can over-ride the MACHFORTH-REPL anytime I need to. 

 

So here is what a test program looks like now.

Spoiler

\ MACHFORTH DEMO #1B
\ On Classic99 debugger you will see R4 counting up and rolling over

\ This demo shows how to:
\  1. compile to 2000 origin
\  2. set NEW workspace and stacks in 16bit scratch-pad RAM
\  3. how to exit program to TI-99 title PAGE
\  4. save a finished program that can RUN from E/A Option 5
\  *PRESS FCTN 4 to return to title screen

COMPILER
   HEX
   NEW.
   2000 ORIGIN.

TARGET
: BYE ( -- )              \ make a sub-routine
      [ 0 LIMI,           \ use inline assembler
        83C4 @@ CLR,
        0000 @@ BLWP, ]
;

PROG: DEMO1B
\ assembler setup commands must run in the interpreter
    [  HEX          \ switch off compiler
       0 LIMI,
       8300 WORKSPACE
       83FE DSTACK
       83BE RSTACK
    ]               \ turn on the compiler
       0BEEF        \ >BEEF -> DATA stack
     [ DECIMAL ]    \ change radix in interpreter mode 
       BEGIN
          22 - 7 *   \ do some math with literal numbers 
         ?TERMINAL  \ test for Break key
       UNTIL        \ MACHFORTH UNTIL does not consume the stack parameter
       DROP         \ clean up the stack
       BYE          \ Go home

COMPILER
SAVE DSK2.DEMO1B

 

 

 

 

 

 

 

 

 

 

 

 

  • Like 2
Link to comment
Share on other sites

Here is an example where you really see the impact of the extra work the 9900 has to do to maintain a stack.

Using the stack to transfer a register to a variable takes a lot of extra time using the Forth stack.

 

Having inline Assembler is the solution is so handy.

 

Spoiler

\ MACHFORTH DEMO #1E   FOR NEXT loop index test

\ I is R8 renamed, used as the loop index for FOR NEXT loops
\ I@  (I fetch) pushes R8 (loop index) onto Forth data stack

COMPILER
   HEX
   NEW.
   2000 ORIGIN.

   VARIABLE X

TARGET
\ FORTH fetch and store 5 seconds
\ ASM   using 9900 mem2mem  1.5 seconds
PROG: DEMO1E
        FFFF FOR
\          I@  X !           \ loop index -> X
         [ I  X @@ MOV, ]    \ Assembler  R8 -> X
        NEXT

      NEXT,      \ Return to Forth
END.

 

 

 

 

  • Like 3
Link to comment
Share on other sites

The code is beginning to look a little more like normal Forth.

It still needs a few magic incantations but it's getting closer to normal Forth

(if there is such a thing)  :) 

\ fibonacci benchmark in Camel Forth

COMPILER \ Set up environment
   NEW.
   HEX 2000 ORIGIN.
   OPT-OFF

\ Machine Forth does not have DO LOOP so we use a library
INCLUDE DSK2.DOLOOP

\ Machine Forth doesn't normally have ROTate, we have to create one.
TARGET
: ROT  ( n1 n2 n3 --  n2 n3 n1)
     [  2 (SP)   R0 MOV,
       *SP   2 (SP) MOV,
        TOS     *SP MOV,
        R0      TOS MOV, ]
;

: FIB ( n -- )
     0  1
     ROT 0
     DO
        OVER + SWAP
     LOOP
     DROP
;

\ 42.6 seconds using Expansion RAM stacks
\ 35.7 SECONDS using FAST RAM stacks
\ 174 bytes
PROG: MAIN
\ Assembler instructions and directives must be interpreted
[   0 LIMI,
HEX 8300 WORKSPACE
    83EA RSTACK
    8400 DSTACK

DECIMAL
]  \ turn compiler back on
     1000 0
     DO
       I FIB DROP
     LOOP
     [ 0 @@ BLWP, ]
END.

COMPILER
SAVE DSK2.FIBONACCI

 

  • Like 2
  • Thanks 2
Link to comment
Share on other sites

Out of curiosity I wanted to see if I could write a VDP driver in MachForth using mostly MachForth.

It makes sense to use ALC inside loops because it can really slow things down with the extra stack instructions.

 

Some of the code is similar to what you would hand code yourself.

Like this:

: VDPA! ( Vaddr -- )   \ set vdp address (read mode)
        [ 0 LIMI, ]
        VDPWA (C!)
        VDPWA (C!)
        DROP ;

Compiled to this:

2004  0647  dect R7           * enter nested sub-routine   
2006  C5CB  mov  R11,*R7        

2008  0300  limi >0000        
200C  06C4  swpb R4           
200E  D804  movb R4,@>8c02             
2012  06C4  swpb R4                    
2014  D804  movb R4,@>8c02             
2018  C136  mov  *R6+,R4      * DROP (refill R4 from stack memory)

201A  C2F7  mov  *R7+,R11     * exit nested sub-routine          
201C  045B  b    *R11              

Where things are not as efficient are when we have the arguments in the wrong order for optimal Forth.

I opted to use >R and R>  for these cases but registers would be faster and arguably I could just change the argument order for these functions but that would confuse me too much.

 

We can look at  VWRITE which has the least Rstack pushing and popping.

: VWRITE ( addr Vaddr len -- )
          >R
          4000 OR VDPA!
          R> 1- FOR   [ *TOS+ VDPWD @@ MOVB, ]  NEXT
        [ 2 LIMI, ]
          DROP ;
\ VWRITE 
20EE  0647  dect R7          * enter nested sub-routine  
20F0  C5CB  mov  R11,*R7    

20F2  0647  dect R7          * >R
20F4  C5C4  mov  R4,*R7      
20F6  C136  mov  *R6+,R4     * DROP
20F8  0646  dect R6          * DUP 
20FA  C584  mov  R4,*R6                
20FC  0204  li   R4,>4000    * LITERAL NO.          
2100  E136  soc  *R6+,R4     * 4000 OR    
2102  06A0  bl   @>2004      * CALL VDPA!
2106  0646  dect R6          * DUP  
2108  C584  mov  R4,*R6      
210A  C137  mov  *R7+,R4     * R> 
210C  0604  dec  R4          * 1-
210E  0647  dect R7          * FOR  
2110  C5C8  mov  R8,*R7      * save loop counter register to rstack           
2112  C204  mov  R4,R8       * Load loop counter from data stack           
2114  C136  mov  *R6+,R4     * DROP           
2116  D834  movb *R4+,@>8c00 * write byte to VDP port           
211A  0608  dec  R8          * dec loop counter 
211C  18FC  joc  >2116       * NEXT           
211E  C237  mov  *R7+,R8     * restore Loop counter register           
2120  0300  limi >0002                 
2124  C136  mov  *R6+,R4               

2126  C2F7  mov  *R7+,R11              
2128  045B  b    *R11        * exit nested sub-routine                  

Clearly this can be optimized. I can see one spot where my simple optimizer would remove  6 bytes at >20F6.

But it is still reasonably quick however I will re-write these in tighter ALC.

This was interesting to try.

 

The entire driver and the test program.

Spoiler

\ VDP DRIVER in MACHFORTH

COMPILER  \ Preamble
  NEW.
  HEX 2000 ORIGIN.

\ TINYVDP.FTH library for MACHFORTH V2.1
COMPILER
HEX
8800 EQU VDPRD
8802 EQU VDPSTS
8C00 EQU VDPWD
8C02 EQU VDPWA

TARGET
: VDPA! ( Vaddr -- )   \ set vdp address (read mode)
        [ 0 LIMI, ]
        VDPWA (C!)
        VDPWA (C!)
        DROP ;

: VC@    ( addr -- )
          VDPA!
          VDPRD C@
        [ 2 LIMI, ]  ;

: VC! ( c Vaddr -- )
        [ 4000 ] #OR VDPA!
          VDPWD (C!)
        [ 2 LIMI, ]
          DROP  ;

HEX
\ * VDP write to register. Kept the TI name
: VWTR   ( c reg -- )   \ Usage: 5 7 VWTR
           ><           \ TOS SWPB,
           +            \ SP+ TOS ADD,
          [ 8000 ] #OR VDPA!
          [ 2 LIMI, ] ;

: VFILL ( Vaddr cnt char -- )
           >< SWAP >R >R  ( r: cnt char)
         [ 4000 ] #OR VDPA!
           R> ( -- char)
           R> 1- FOR  [ TOS VDPWD @@ MOVB, ]  NEXT
         [ 2 LIMI, ]
           DROP ;

: VREAD ( Vaddr addr n --)
           >R >R  ( r: n addr)
           VDPA!
           R> R>  ( -- addr n)
           1- FOR  [ VDPRD @@  *TOS+ MOVB, ]  NEXT
         [ 2 LIMI, ]
           DROP ;

: VWRITE ( addr Vaddr len -- )
          >R
          4000 OR VDPA!
          R> 1- FOR   [ *TOS+ VDPWD @@ MOVB, ]  NEXT
        [ 2 LIMI, ]
          DROP ;

: PAGE    0 3C0 BL VFILL ;

CREATE A$  S" VDP Routines in MachForth" S,

PROG: DEMOVDP
       PAGE
       18 7 VWTR
       A$ COUNT 0 SWAP VWRITE
       0 3000 20 VREAD  \ read VDP screen in VDP RAM 
       NEXT,            \ return to Camel99 Forth
END.

 

 

  • Like 2
Link to comment
Share on other sites

3 hours ago, GDMike said:

Good, I'll use this sometime

My hope is that somebody else might be able to use it sometime.

What has amazed me is how you can go around in circles when you are creating a language. There is always another way to implement things that might be better. 

So you make a change. Then all the library code is wrong. So you fix that and realize you didn't think about some other thing and around you go again...

 

This is starting to feel stable now so I have two big todos:

1. Write a manual

2. Figure out how to save a complete binary program that uses wordlists/vocabularies. 

(I was going to procrastinate on that problem, but I put it off) :)

 

  • Like 2
Link to comment
Share on other sites

  • 3 months later...

ASMForth is the simplest Machine Forth I can think of that still uses the features of the 9900.

At it's simplest it literally renames some instructions to Forth vernacular.

There is a bit of a challlenge with literal numbers and addresses. My cheap and dirty solution is to preface some Forth operators with the # symbol.

This indicates a literal number or address is the required parameter.

 

I have added nestable sub-routines and a nestable FOR/NEXT loop just to show how easy it is.

It does not have tail-call optimization like MACHFORTH or any other form of optimization.

It's an Assembler that uses Forth style mnemonics. 

 

Willsy had expressed some interest in what I was doing here so this could be easily ported to another Forth I think.

EDIT: Updated with some bug fixes 

Spoiler

\ Experimental 9900 Assembler using Forth syntax elements  Sept 11, 2021

\ Syntax conventions:
\ 1. Words that end with a comma are raw 9900 instructions
\    They use 9900 parameters
\ 2. Forth words assume TOS is in R4. You DUP and DROP as needed.
\ 3. Store ! +! 1+! 2+! 1-! 2-!  use symbolic addressing with variables

\ /////////// REGISTER USAGE \\\\\\\\\\\
\ R0   temp
\ R1   temp
\ R2   temp
\ AR   R3  is a general purpose address register
\ TOS  R4 is top of stack cache (you need to manage it)
\ R5   temp
\ SP   data stack pointer
\ RP   return stack pointer
\ R10  holds NEXT address
\ R11  sub-routine linkage
\ R12  CRU I/O
\ R13  for BWLP
\ R14  for BWLP
\ R15  for BWLP


\ NEEDS DUMP FROM DSK1.TOOLS
\ NEEDS MARKER FROM DSK1.MARKER
\ NEEDS WORDSLIST FROM DSK1.WORDLISTS
INCLUDE DSK1.SUPERTOOLS \ this gets all the above files into Cartidge Space


ONLY FORTH DEFINITIONS
VOCABULARY MFORTH

HERE
ONLY FORTH ALSO ASSEMBLER ALSO MFORTH

MFORTH DEFINITIONS
DECIMAL
: ?REGARG ( n --) 16 0  WITHIN ABORT" Register expected" ;
HEX
: ?ADDR   ( n --) 2000 < ABORT" Invalid memory address" ;

\
\ Register names
\ Unlike normal Forth we can get at some registers directly by name with MOV,
\   NOS TOS MOV,
\ : OVER ( a b -- a b a)  DUP  3RD TOS MOV, ;
\ : 2PICK ( a b c -- a b c c)  DUP  4TH TOS MOV, ;

\ Named stack items in memory...
: NOS     *SP  ;    \ Next on Stack
: NOS+    *SP+ ;    \ pop next on stack to another register
: 3RD   2 (SP)  ;
: 4TH   3 (SP)  ;
: 5TH   4 (SP)  ;

3 CONSTANT AR  ( Chuck's 'A' register,  "address register")
: (AR)   AR () ;
: *AR    AR ** ;
: *AR+   AR *+ ;

CR .( Forth Intrinics)
\ These inline code generators are in the actual compiler
HEX
\  Moore's Machine Forth + a few extras
: DROP  ( n -- ) NOS+ TOS MOV,  ;
: DUP            SP DECT,  TOS NOS MOV, ;

.( .)
: 2*     ( n -- n ) TOS TOS ADD, ;
: 2/     ( n -- n)  TOS 1 SRA, ;
: INVERT ( n -- )   TOS INV, ;
: AND    ( n mask -- n) NOS INV,  NOS+ TOS SZC, ;
: MASK   ( n n -- n ) TOS SWAP ANDI, ;  \ AND TOS with literal number
: XOR    ( n n -- n)  NOS+ TOS XOR, ;
: +      ( n n -- n)  NOS+ TOS ADD, ;   \ (option 1) add on stack
: #+     ( n n -- )    TOS SWAP AI, ;   \ (option 2) TOS + literal number

\ ___________________________________________________________________
CR .( A register. C. Moore idea for Machine Forth )
\ We used the features of the TMS9900 CPU. It's dumb not to.

\ These Forth conventions are kept: @ means fetch and ! means store.
\ '*' suffix means indirect memory access like TI Assembler

\  Fetch to TOS always saves TOS before operation
: A@    ( -- n) DUP   AR  TOS MOV, ;  \ Dpush(T) T=A
: *A@   ( -- n) DUP  *AR  TOS MOV, ;  \ Dpush(T) T=*A
: *A@+  ( -- n) DUP  *AR+ TOS MOV, ;  \ Dpush(T) T=*A  A=A+cell

\ Store from TOS always refills TOS after operation
: A!    ( addr -- ) TOS  AR  MOV, DROP ;  \ A=T  Dpop(T)
: A+!   ( n -- )    TOS  AR  ADD, DROP ;
: *A!   ( addr)     TOS *AR  MOV, DROP ;  \ [A]=T Dpop(T)
: *A!+  ( n --)     TOS *AR+ MOV, DROP ;  \ [A]=T A=A+cell Dpop(T)

\ indexed addressing fetch/store on A register to/from TOS
: (A)@  ( u --)   DUP  (AR) TOS MOV, ;    \ Dpush(T) T=u@(A)
: (A)!  ( n --)   TOS  SWAP (AR) MOV, DROP ;

\ Using more 9900 instructions on A register
: A1+!  ( -- )    AR INC,  ;
: A2+!  ( -- )    AR INCT, ;
: A1-!  ( -- )    AR DEC,  ;
: A2-!  ( -- )    AR DECT, ;

\ byte operations manage reversing the byte in the in TOS register
: *AC@   ( -- 0c00)  DUP  *AR  TOS MOVB, TOS 8 SRL, ;
: *AC@+  ( -- 0c00)  DUP  *AR+ TOS MOVB, TOS 8 SRL, ;
: *AC!   ( 0c00 --)  1 (TOS) *AR  MOVB,  DROP ;
: *AC!+  ( 0c00 --)  1 (TOS) *AR+ MOVB,  DROP ;

.(  return stack operators .)
\ Chuck Moore's CMForth used PUSH & POP for rstack
\ BF kept them familiar
: DUP>R ( n -- n) TOS RPUSH, ;
: >R    ( n -- )  DUP>R DROP ;
: R>    ( -- n)   DUP  TOS POP, ;

: R@    ( -- n )  DUP  *RP TOS MOV, ;
: R!    ( n -- )  TOS  *RP MOV,  DROP ;
: R!    ( n --)  TOS *RP MOV,  DROP ;
: R+!   ( n --)  TOS *RP ADD, DROP ;

\ /\/\/\/\/\/\/\[ Chuck Moore Machine Forth Ends ]/\/\/\/\/\/\/\/\

\ no-brainer 9900 optimizations
: R1-! ( -- )    *RP DEC, ;
: RDROP ( -- )    RP INCT, ;

: 1+     TOS INC, ;
: 2+     TOS INCT, ;
: 1-     TOS DEC, ;
: 2-     TOS DECT, ;
: 4*   ( reg -- n') TOS  2 SLA, ;
: 8*   ( reg -- n') TOS  3 SLA, ;

: LSHIFT ( n -- n)  TOS SWAP SLA, ;
: RSHIFT ( n -- n)  TOS SWAP SRL, ;

\ inc/dec variables with symbolic addressing
: 1+! ( addr -- )  @@ INC, ;
: 2+! ( addr -- )  @@ INCT, ;
: 1-! ( addr -- )  @@ DEC, ;
: 2-! ( addr -- )  @@ DECT, ;

: +!   ( n addr --) TOS SWAP @@ ADD,  DROP ; \ 6 bytes  \ 5 # X +!

: NOP    ( -- )     0 JMP, ;
: ABS    ( n -- n') TOS ABS, ;
: NEGATE ( n --n')  TOS NEG, ;
: OR     ( w w -- w ) NOS+ TOS SOC, ;
: #OR    ( -- )    TOS SWAP ORI, ;

\  2 and 3 instruction words for ANS/ISO compatibility
: -     ( n n -- n') NOS+ TOS SUB, TOS NEG, ;
: UM*   ( n n -- d)  NOS  TOS MPY, R5  NOS MOV, ;
: *     ( n n -- n)  NOS+ R3 MOV,  TOS R3 MPY, ;

: ALIGNED ( n -- n)   TOS INC,  TOS -2 ANDI, ;
: AND   ( w w -- w ) NOS INV,  NOS+ TOS SZC, ;
: 2@    ( addr -- d) 2 (TOS) PUSH,   *TOS TOS MOV, ; \ fetch double integer
: ON        ( variable --) @@ SETO, ;
: OFF       ( variable --) @@ CLR,  ;
: ><        ( n -- )  TOS SWPB, ;

CR .( MFORTH jump tokens)
HEX                  \ Action if TRUE
 01 CONSTANT >       \ JLT to ENDIF, *signed
 02 CONSTANT U>      \ JLE to ENDIF,
 03 CONSTANT 0<>     \ JEQ to ENDIF,
 04 CONSTANT U<      \ JHE to ENDIF,
 05 CONSTANT <=      \ JGT to ENDIF, *signed
 06 CONSTANT 0=      \ JNE to ENDIF,
 07 CONSTANT .OC.    \ JNC to ENDIF,
 08 CONSTANT .NC.    \ JOC to ENDIF,
 09 CONSTANT .OO.    \ JNO to ENDIF,
 0A CONSTANT U<      \ JLO to ENDIF,
 0B CONSTANT U>=     \ JH  to ENDIF,
 0C CONSTANT .NP.    \ JOP to ENDIF,

CR .( branching and looping)
: IF     ( addr token -- 'jmp') IF, ;
: ENDIF  ( 'jmp addr --)  ENDIF, ;
: ELSE   ( -- addr ) ELSE, ;

: BEGIN  ( -- addr)  HERE ;
: WHILE  ( token -- *while *begin) WHILE, ;
: AGAIN  ( *begin --) AGAIN,  ;
: UNTIL  ( *begin token --) UNTIL, ;
: REPEAT ( *while *begin -- ) REPEAT, ;

CR .( memory fetch/store)
: @     ( TOSaddr -- n) *TOS TOS MOV, ;
: #@    ( addr -- n) TOS PUSH, ( addr) @@ TOS MOV, ; \ fetch from literal address

\ added byte operations: BFox
: #C@   ( addr -- c)  TOS PUSH, ( addr) TOS MOVB,  TOS 8 SRL, ;
: C@    ( addr -- c) *TOS TOS MOVB,    TOS 8 SRL, ;

: !      ( n addr --)  NOS+ *TOS MOV, DROP ;
: #!     ( n [variable] -- ) TOS SWAP @@ MOV, DROP ;

: TO    ( reg -> variable)  ' >BODY  ! ; \ register to variable
: LD#   ( n REG -- )  SWAP ?REGARG LI, ; \ n -> REG
: #     ( n -- )   TOS PUSH,  TOS SWAP LI, ; \ literal to TOS

HEX
: ->   ( var1 <var2> --) \ X -> Y   1 instruction 6 bytes
       ' >BODY   \ find CFA(var2), convert to data field
        SWAP  @@  ROT @@  MOV, ;  \ assign var1 to var2

\ Writes code to swaps byte in register automatically
: C!     ( c  addr -- )   NOS SWPB,   NOS+ *TOS    MOVB, DROP ;
: #C!    ( REG [addr] --) TOS SWPB,   TOS  SWAP @@ MOVB, DROP ;

\ ********* ANS/ISO Forth, Stack operators ****************
: OVER  ( n1 n2 -- n1 n2 n1)  DUP  3RD TOS MOV, ;
: NIP   ( n1 n2 -- n2)  SP INCT, ;
: SWAP  ( n1 n2 -- n2 n1)  TOS R0 MOV,  NOS TOS MOV,  R0 NOS MOV, ;

\ ////////////////////////////////////////////////////////
\ --------------  higher level constructs  --------------
\ \\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\
: BOUNDS ( adr len -- adr2 adr1) NOS R1 MOV, TOS NOS ADD, R1 TOS MOV, ;
: NOT       ( -- )  R1 STST,  R1 2000 ANDI, ;  \ invert EQ flag status
: ?TERMINAL ( -- ?) 0020 @@ BL,  NOT ;

\ CUT n characters from left side of STRING (addr,len)
: /STRING ( addr len n -- addr' len' ) TOS NOS SUB,  TOS 2 (SP) ADD,  DROP ;

\ ** WARNING ** puts the string address in register A
: $@   ( Caddr --  len) ( A: Caddr+1)
        A!     \ base address to register A
        A1+!   \ bump address past count byte
       *AC@    \ fetch byte count onto data stack
;

CR .( sub-routine creator)
\ subs call themselves when invoked by compiling a BL instruction
: SUB:
\ compile time action
   CREATE  !CSP
           R11 RPUSH,    \ compile "enter sub-routine"
                  \ <--- your program code compiles here
   DOES> ( sub-addr) @@ BL, ; \ Runtime: compile BL to this sub-routine

: ;SUB    ?CSP  R11 RPOP,  RT, ;  \ compile exit sub-routine code

: ;CODE    *R10 B,   ENDCODE ;

CR .( FOR/NEXT)
\ Simple FOR/NEXT loop written in ASM Forth.
\ Uses return stack for index because registers are in short supply.
\ Speed reduction is ~11% on 9900 VS index in a register.
\ Use  R@  as a loop index.  Use  nn R+!  to STEP down faster.
\ Use TOS or A register if you need an up-counting register
: FOR  ( n --)  >R  BEGIN ;
: NEXT ( -- )   R1-! .NC. UNTIL  RDROP ;

: COUNT  ( Caddr -- addr len )
        DUP
        NOS INC,
       *TOS TOS MOVB,
        TOS 8 SRL, ;

HERE SWAP - DECIMAL .  .( bytes)

 

 

Some simple test code

 

Spoiler

\ MFORTH Assembler tests

ONLY FORTH DEFINITIONS
ALSO ASSEMBLER \ Compiler understands ASM words

VARIABLE X
VARIABLE Y
VARIABLE Z

\ Code in Forth Assembler
HEX
CODE ASM1
       TOS PUSH,      \ make space in the TOS register (R4)
       TOS FFFF LI,   \ literal number to TOS
       BEGIN,
         TOS DEC,
       EQ UNTIL,       \ !!! does not consume the top of stack
       TOS POP,        \ restore old TOS from data stack
       NEXT,
ENDCODE

\ Same program in MForth Assembler.
ONLY FORTH ALSO MFORTH
MFORTH DEFINITIONS
HEX
CODE MFTEST1
       FFFF #        \ literal number to TOS (# makes space in TOS)
       BEGIN
          1-
       0= UNTIL      \ !!! does not consume the top of stack
       DROP          \ restore old TOS from data stack
;CODE

\ using variables/addresses
CODE MFTEST2
       FFFF #
       BEGIN
          1-
          DUP X !   \ Store uses ONLY symbolic addressing
          X -> Y    \ mem2mem  X->X assignment
          Y -> Z    \ Y -> X
       0= UNTIL
       DROP
;CODE
\ emitted code for Mforth2
\   CADA  0644  dect R4                     (14)
\   CADC  C584  mov  R4,*R6                 (30)
\   CADE  0204  li   R4,>ffff               (20)
\   CAE2  0604  dec  R4
\   CAE4  C804  mov  R4,@>ca86
\   CAE8  C820  mov  @>ca86,@>ca90
\   CAEE  C820  mov  @>ca90,@>ca9a
\   CAF4  16F6  jne  >cae2
\   CAF6  045A  b    *R10

CODE MFTEST3  \ counter using A register
      FFFF #
      BEGIN
         A2+!
         1-
      0= UNTIL
      DROP
;CODE

CODE MFTEST4
     FFFF # FOR  A1+!  NEXT  ;CODE

\ \\\\\\\\\\\\\  sub-routines /////////////
SUB: SUB1
    Y #@
    FOR
        R@ X !
    NEXT
;SUB

SUB: SUB2
    10 # Y !
    SUB1
    Z 1+!
;SUB

CODE MAIN
     1000 #
     FOR
       SUB2
       20 # Z +!
     NEXT
;CODE

 

 

  • Like 3
Link to comment
Share on other sites

Hello world in ASM Forth becomes pretty understandable

Spoiler

\ hello world in ASM Forth. Running inside Camel99 Forth

ONLY FORTH ALSO MFORTH
MFORTH DEFINITIONS

HEX
8C02 CONSTANT VDPWA   \ Write Address port (absolute address so use EQU)
8C00 CONSTANT VDPWD   \ Write Data port

CREATE TXT  S" Hello World!" S,

SUB: TYPE ( addr len) \ make a sub-routine because we can
    1- FOR   COUNT VDPWD #C!   NEXT DROP
;SUB

CODE HELLO
     0 # VDPWA #C!     \ character store VDP address LSB
    40 # VDPWA #C!     \ character store VDP address MSB + "write" bit
    TXT #  COUNT TYPE  \ address -> tos
;CODE

 

 

Classic99 QI399.046 2022-02-11 2_12_38 PM.png

  • Like 2
Link to comment
Share on other sites

1 minute ago, GDMike said:

Ok. I'm getting this..I'll review a bit more, looks like something I really need.

Well... I think TF can get you where you are going as the first pass.

 

Then if you needed something to go much faster you re-write the bottleneck word, in Assembler -or- you could use this kind of thing.

With Assembler and this compiler you don't want them in memory with your application cuz TI-99 so teeny.

So you develop the faster word, convert to machine code and put the machine code version in your program.

 

This compiler is my mental exercise for something I always thought was possible with Forth Assembler but didn't know how to do it exactly.

I am happy that it is readable to you.

It's just a bit different than normal Forth and you can put ASM code inline if your want to. :) 

 

I replaced the source code for the compiler above.  Take a look at it, since you know ALC and you might get some insights to how your TF code actually works at the primitive level.

 

  • Like 3
Link to comment
Share on other sites

MachForth Update

(MachForth is a Forth compiler that generates executable binary programs that run native code, not threaded code) 

 

Learning how to use a new kind of Forth has been challenging especially while writing it at the same time. :)

 

I have gone back to working on interfacing to the VDP chip. This has lead me to see how much overhead happens when you run a stack machine on top of a register machine especially when you want a fast loop.  It can be done of course in Assembler but my goal has been to try and find a way to make MachForth source code compile code that is as efficient as possible.

 

Chuck Moore added an extra register to his later Forth CPU designs that he called the 'A' register that is used to hold addresses that are used repeatedly. 

I took R9 on the 9900 for this purpose.

 

The VDP chip port addresses seem to be a perfect use case. With that in mind I have worked on the Forth word "TYPE".

If I did with only Forth constructs it was pretty fast but it had noise words to handle the data stack inside the inner loop. 

Using the A register idea gave me the tightest code.  (It makes me think I should find a way to use it in regular Forth)

\ print string 
: TYPE ( Caddr len -- )
    8C00 A!   \ load the address register with VDP port
    1- FOR
        *TOS->*AC!
    NEXT
    DROP
;

 

Of course I needed to make that magic instruction for the inner loop.  Since the TOS register is where the action is in Forth, it made sense to add an instruction that moves bytes from the address in TOS to the address in the A register with auto-incrementing on the TOS  

 

(The macro is created with the H:   host Forth's colon compiler not the TARGET compiler colon operator. )

H: *TOS->*AC!  ( addr -- addr') *TOS+ *AR MOVB,  ;H

 

The resulting code still has the overhead of a 9900 nested sub-routine call and FOR/NEXT loop setup, but the inner loop is pretty tight!

For reference: Special register allocations

 

R4  TOS  cache

R6  DATA stack pointer

R7  Return stack pointer

R8  I register for loop indices

R9  A register for addresses 

  2034  0647  dect R7            ( start FOR loop)
  2036  C5C8  mov  R8,*R7        ( save I register, the loop index)
  2038  C204  mov  R4,R8         ( load new loop index)
  203A  C136  mov  *R6+,R4       ( refill TOS from data stack with string address)

  203C  D674  movb *R4+,*R9      ( *TOS->*AC!  new instruction)
  203E  0608  dec  R8            ( NEXT loop )        
  2040  18FD  joc  >203c         

  2042  C237  mov  *R7+,R8       ( restore I register)       
  2044  C136  mov  *R6+,R4       ( DROP refills TOS from data stack         

  2046  C2F7  mov  *R7+,R11      ( restore R11 from return stack   
  2048  045B  b    *R11          ( return from sub-routine)         

 

 

 

 

 

  • Like 4
Link to comment
Share on other sites

Not sure if this is of any value to you, but in the UCSD p-system, when you write programs that declare constants, then the compiler creates a constant pool with these values. The pool is loaded into the heap when the program is to be executed. Then there are p-code instructions that fetch a constant from the constant pool to the stack. Of course you get the one-time overhead of creating the constant pool, but then you can push a word in the constant pool to the top of stack pretty easily:

DECT SP
MOV OFFSET(CONSTPOOL),*SP

SP is the stack pointer register, CONSTPOOL the constant pool pointer and OFFSET the offset into the constant pool where you have the constant.

If you want to move the constant pool in memory, you only need to update the pointer.

  • Like 2
Link to comment
Share on other sites

Yeah, that TYPE must be really fast! However, for a 'proper' implementation, you'll want to write TYPE in terms of EMIT, which may or may not invoke a screen scroll. EMIT is the bottleneck, as it has to maintain a notion of a current cursor position. And I was heartbroken at the impact of screen scrolling - it's as slow as hell. I don't think there's anything particularly wrong with TF screen scroll as invoked by EMIT, it reads/writes up to 80 bytes at a time. But boy is it slow! I have a little utility that allows one to read a DV80 text file and TF will compile it. Works a treat. Default action is to display the lines of code on the screen as it works through the text file. IIRC, the screen scrolling adds 300% overhead (in 80 column mode).

 

In TF, you can disable screen scrolling with the SSCROLL variable - then it flies (the screen wraps, bottom to top).

  • Like 3
Link to comment
Share on other sites

On 2/18/2022 at 7:59 AM, apersson850 said:

Not sure if this is of any value to you, but in the UCSD p-system, when you write programs that declare constants, then the compiler creates a constant pool with these values. The pool is loaded into the heap when the program is to be executed. Then there are p-code instructions that fetch a constant from the constant pool to the stack. Of course you get the one-time overhead of creating the constant pool, but then you can push a word in the constant pool to the top of stack pretty easily:


DECT SP
MOV OFFSET(CONSTPOOL),*SP

SP is the stack pointer register, CONSTPOOL the constant pool pointer and OFFSET the offset into the constant pool where you have the constant.

If you want to move the constant pool in memory, you only need to update the pointer.

 

Thank for taking an interest in this project.  Your background and experience far exceeds mine in this kind of thing. 

This is a very good idea if we want to hold the constants in memory. It could become part of the project if I fly into a wall. :) 

 

Since this little compiler is to generate a binary program image, I have, for better or worse, made constants generate no code unless invoked by name.

So my "constant pool" is maintained in the compiler Forth's dictionary of words.

This means constants must be declared after the "COMPILER" directive so they become part of the compiler's word set.

 

Later when the constant is used the following code is emitted into the program:

\ compiler code to put literal into top of stack register
                   SP DECT,
             TOS   *SP MOV,  ( this is effectively "DUP" 
             TOS <cons> LI, 
 

So the constant is loaded as an immediate value into the TOS register.

This is more verbose than normal because I have turned the 9900 into kind of Accumulator machine by dedicating R4 to hold the top of stack in a register.

So we have to "push" the TOS before we use it for a new purpose.

The two instructions that push the TOS register (ie: DUP)  have been changed into a PUSH/POP optimizer (called SMARTDUP) that removes those instructions if the TOS was previously "refilled" from memory and it also removes the refilling instruction ( *SP+ TOS MOV,) saving 6 bytes and lots of cycles.  

 

So it is not as bad as it appears most of the time if the optimizer is turned-on.

So far it works ... most of the time. :) 

 

 

 

 

 

Link to comment
Share on other sites

On 2/18/2022 at 8:48 AM, Willsy said:

Yeah, that TYPE must be really fast! However, for a 'proper' implementation, you'll want to write TYPE in terms of EMIT, which may or may not invoke a screen scroll. EMIT is the bottleneck, as it has to maintain a notion of a current cursor position. And I was heartbroken at the impact of screen scrolling - it's as slow as hell. I don't think there's anything particularly wrong with TF screen scroll as invoked by EMIT, it reads/writes up to 80 bytes at a time. But boy is it slow! I have a little utility that allows one to read a DV80 text file and TF will compile it. Works a treat. Default action is to display the lines of code on the screen as it works through the text file. IIRC, the screen scrolling adds 300% overhead (in 80 column mode).

 

In TF, you can disable screen scrolling with the SSCROLL variable - then it flies (the screen wraps, bottom to top).

Yes it is fast and of course is only useful if you keep it on the screen as you say. I am still at the stage of trying to make the compiler generate correct code that is reasonably optimal. :) 

 

I have to get all of my screen i/o lib working reliably to make a proper type as you describe but it is in progress. An yes SCROLLing sucks on the VDP chip.

In the SEVENS benchmark Camel99 Forth does it in about 1:04. but over RS232 the same code runs in 26 seconds because the terminal is doing the scrolling. :)

I like the top/bottom wrapping idea. I make use that for testing purposes. 

 

  • Like 1
Link to comment
Share on other sites

11 hours ago, TheBF said:

This is a very good idea if we want to hold the constants in memory. It could become part of the project if I fly into a wall. :) 

 

Since this little compiler is to generate a binary program image, I have, for better or worse, made constants generate no code unless invoked by name.

So my "constant pool" is maintained in the compiler Forth's dictionary of words.

This means constants must be declared after the "COMPILER" directive so they become part of the compiler's word set.

Pascal is a language which is strict with lexical levels. A global constant can be accessed by anyone, but a constant declared in a procedure can only be accessed by that procedure, and it's children. On a previous level, you can't see it.

Having constants in a pool also makes more sense for longer values, like real numbers (8 bytes) and strings (up to 256 bytes). Accessing a long string constant ten times via a pool, rather than repeating it ten times, makes a big difference in memory consumption.

 

The p-system even has provisions for accessing global constants and variables from a supporting assembly program. The process is more convoluted, as the p-system (as most traditional systems) require that you write and compile Pascal programs separatly from writing and assembling assembly programs. At the end, you need to run yet another program to link the two together. But the linker can resolve references to a constant in the constant pool, for example, and also store data in the host's global variable area.

 

As I wrote, this may be of limited use to you. The concepts used by the UCSD p-system were in a way ahead of its time. They are too complex to be handled by the limited capacity hardware on which they often ran, and still get good performance. But they support the program developer's task very well. That's why I keep on repeating that the p-system is the best development environment on the TI 99/4A. In spite of not resulting in the fastest programs, you may still end up with programs that are easiest to maintain.

If you instead look at Forth, it's all about performance, performance, perfomance. While you can start designing constructs that will approach the structure you have in Pascal, you normally don't. It's not the point of Forth. A typical example is that if you index an array in Forth outside its bounds, then you just get what you ask for. If you store something there, the program will most likely shoot itself in the foot. Try that in Pascal and you get a Value range error. No guesswork involved in what happened. But that range checking does of course consume resources at runtime.

 

My professional experience includes developing machine control programs. They frequently have a lifetime over at least 20 years. We try to make the same program support all machines in the same series, in spite of hardware changes due to components becoming obsolete and replaced by similar, but not identical, components. We try to make the same program support all configurations, in spite of the machines being modular, so they can be a combination of several different modules. If you multiply all possible hardware combinations with all possible machine module combinations, you get more than one million configurations, which all should be supported by the same program. Occasionally, when we have bought back some old, used machine as part of a deal for selling new ones, I try loading the newest version of a program into that old machine, just to verify that it still works. Usually it does, and if not, I figure out why and fix the issue.

 

Since the programs live that long, they are often developed and modified by several programmers, sometimes located in different countries. The size of these programs typically range from 5000 lines for something simple to over 100000 lines for the more complex things.

 

Such programming does of course impose some other demands on what you do than what hobby programs do. Although I've found that the same principles applied to programs for the 99/4A, written 35 years ago, makes it easier when I look at them again today. So something can still be learnt from what's a necessity in the professional field.

 

So, that was just a detour to explain why my views occasionally aren't traditional in the hobby field. Be inspired if you like it, or disregard it if you find it non-applicable.

  • Like 2
Link to comment
Share on other sites

 

3 hours ago, apersson850 said:

So, that was just a detour to explain why my views occasionally aren't traditional in the hobby field. Be inspired if you like it, or disregard it if you find it non-applicable.

Understood. 

It certainly piques my interest.  Are these "machine control" programs written in P-code Pascal?

I would think that an underlying interpreter like p-code would be ideal to abstract the endlessly changing hardware.

If you are allowed to share, I would love to learn more. 

 

Similar story from the Forth arena:

This approach was taken my MPE in the UK (a Forth shop) when they got a contract for a European card terminal architecture. They created a byte coded VM that was a Forth VM under the hood.

I think it had to be ported to existing hardware used all over Europe that ran on Z80, 68000 and I don't know what else.

It is now an ISO standard I see:  https://www.iso.org/standard/54776.html

They wrote a C compiler for it and you could also use their Forth toolchain. I suspect there would be other languages now if it still is in use.

Since it's byte code I should think almost any appropriate language could be ported to it.

 

So although Forth has had a tradition from the founder of endlessly looking for performance, when professionals use it is "sculpted" to be what makes sense for the application.

Funny coincidence in that I was just demonstrating on another topic how simple it can be to add array index protection to a Forth array. :)

Since you build your own data structures up from the ground you make them what you need. Failure to do so would be silly and/or outright dangerous depending on the application area.

 

 

Link to comment
Share on other sites

The language and system depends on who delivers it.

We have our own controllers, usually running under Linux and using some C-compiler for the software development.

Then we have systems purchased from the outside. Today, many use ISO 61131 programming, where we most of the time write programs using Structured text. That's a control system language developed with influence from Pascal. Some of these also support C programming. Some have limited communcation capabilities and thus require some form of low level programming in the motor drives themselves.

Some systems are outside of that "standard". We have some that are programmed in somethnig called Trio Motion BASIC. That's a parallel processing BASIC version, with deterministic timing in task execution and motion system commands. It's typically used for synchronizing several motors in a machine. There could be dozens of motors in the same machine, where some of them belong to groups that are linked together in more or less complex ways.

Safety related systems are running on special, redundant hardware, where they execute special programs, written by combininig a finite number of function blocks with each other.

  • Like 1
  • Thanks 1
Link to comment
Share on other sites

Join the conversation

You can post now and register later. If you have an account, sign in now to post with your account.
Note: Your post will require moderator approval before it will be visible.

Guest
Reply to this topic...

×   Pasted as rich text.   Paste as plain text instead

  Only 75 emoji are allowed.

×   Your link has been automatically embedded.   Display as a link instead

×   Your previous content has been restored.   Clear editor

×   You cannot paste images directly. Upload or insert images from URL.

Loading...
  • Recently Browsing   0 members

    • No registered users viewing this page.
×
×
  • Create New...