Jump to content
IGNORED

Camel99 Forth Information goes here


TheBF

Recommended Posts

Looking at my Github site I find a few half-baked files. Oops.

So I fixed up this one that might be useful.

 

\ *
\ * Boot tracking
\ *
\ * Code copied more or less verbatim from:
\ * 1.7. The Art Of Assembly Part 7. Why A Duck?
\ * By Bruce Harrison 1991
\ *
\ BOOTTR MOV  @>83D0,R12          * GET THE CRU BASE IN R12
\        MOV  @>83D2,R9           * GET THE ROM ADDRESS FOR \DEVICE
\        SBO  0                   * ENABLE THE ROM
\        AI   R9,4                * ADDING FOUR PUTS US AT THE LENGTH BYTE
\        MOVB *R9+,R4             * PLACE THAT IN R4 AND INCREMENT R9
\        SRL  R4,8                * RIGHT JUSTIFY LENGTH IN R4
\        LI   R10,FILEDV          * POINT TO TEXT BUFFER
\ MOVIT  MOVB *R9+,*R10+          * MOV ONE BYTE FROM ROM TO TEXT BUFFER
\        DEC  R4                  * FINISHED?
\        JNE  MOVIT               * NO, DO ANOTHER BYTE
\        SBZ 0                    * DISABLE THE ROM (R4 IS ZERO AT THIS POINT)
\        B   *R11                 * BRANCH TO NEXT SECTION OF CODE
\ FILEDV TEXT "DSK1."             * File device

\ NEEDS MARKER     FROM DSK1.MARKER
\ NEEDS .S         FROM DSK1.TOOLS
\ MARKER REMOVE

DECIMAL
24 USER 'R12  \ address of R12 in any CAmel99 workspace
              \ >8324 in other TI-99 Forths

HEX
CODE 0SBO  ( -- ) 1D00 ,  NEXT, ENDCODE
CODE 0SBZ  ( -- ) 1E00 ,  NEXT, ENDCODE

83D0 CONSTANT DISKCARD
83D2 CONSTANT ROMADDR

HEX
: BOOTDISK ( -- addr len)
          DISKCARD @ 'R12 !
          0SBO
          ROMADDR @ 4 + COUNT PAD PLACE
          0SBZ
          PAD COUNT ;

 

 

 

 

 

BOOTDISK.png

  • Like 2
Link to comment
Share on other sites

Just now, Lee Stewart said:

 

This will only be valid in a, likely unpredictable, narrow window of time, n’est-ce pas?

 

...lee

I think so. I don't even remember where I found the ALC reference. :)

Perhaps the intent is that you run it early and retain the string in your program for future file reads to use. ?

 

Come to think of it I could use it in my Shell program to set the load disk as a default and display it in a prompt like DOS/CPM maybe.

 

I will try a couple of other file reads from other disks and see what happens.

 

 

  • Like 1
Link to comment
Share on other sites

4 minutes ago, TheBF said:

I will try a couple of other file reads from other disks and see what happens.

Yes indeed I loaded a text file of source code from DSK3.  and BOOTDISK TYPE   showed DSK3.

So I think I will rename it to LASTDISK.

What to you think of that name?

  • Like 1
Link to comment
Share on other sites

The cleanup never ends :) 

 

I was never happy with the TRANSIENT, PERMANENT, ERADICATE  system I created, mostly because I didn't finish it. 

I like it now. This is clean and easy.  ERADICATE  removes the TRANSIENT dictionary.

 

Spoiler

CR .( Transient.fth    Jan 17 2022 B Fox)

\ Compile code into another RAM location and remove it later)
\ SEE: DSK1.LOWTOOLS DSK1.SUPERTOOLS for demo code
HEX
VARIABLE SAVEDP
VARIABLE OLDNFA  \ NFA of last word in the old dictionary 

: TRANSIENT ( NEWDP -- ) \ Usage   HEX 2000 TRANSIENT
           LATEST @ OLDNFA !
           HERE SAVEDP !     \ save the dictionary pointer.
           DP ! ;            \ Point DP to transient memory

: PERMANENT ( -- ) ( Restores high ram compiling )
           HERE H !          \ give back what we didn't use to the HEAP
           SAVEDP @ DP !     \ restore DP back to original address

         \ built a dummy word as the link to the permanent dictionary
          S" $$$$" HEADER, COMPILE DOCON  HERE ,  COMPILE EXIT
;

: ERADICATE ( -- ) ( removes TRANSIENT dictionary code)
          OLDNFA @  LATEST !  \ relink the dictionary
          2000 H ! ;          \ init-the heap.

 

 

DSK1.SUPERTOOLS 

CR .( Compile Tools in SuperCart RAM)

NEEDS TRANSIENT FROM DSK1.TRANSIENT
HEX 6000 TRANSIENT   \ transient dictionary in supercart
CR .( Compiling to address:) HERE U.

  INCLUDE DSK1.ELAPSE
  INCLUDE DSK1.TOOLS
  INCLUDE DSK1.ASM9900

PERMANENT
CR .( Now compiling to: ) HERE HEX U.

.FREE
DECIMAL

 

 

 

 

  • Like 2
Link to comment
Share on other sites

BTW, do you have a simple Forth assembly code I can look at to figure out how things are done without labels, branches like what I use in a loop whenever you find a moment.. just something I'd like to review. 

I did put together marks TF assembler manual that he provides, but again, I forgot to bring it to work with me for the second day.

Link to comment
Share on other sites

20 minutes ago, GDMike said:

BTW, do you have a simple Forth assembly code I can look at to figure out how things are done without labels, branches like what I use in a loop whenever you find a moment.. just something I'd like to review. 

I did put together marks TF assembler manual that he provides, but again, I forgot to bring it to work with me for the second day.

Well... I have overhauled the old TI-Forth assembler for these things using some new-fangled thinkin' that came from a crazy Forth guy in Australia.

It's much simpler code and takes less space in our little 99s.

To be clear, the parts that are "really" changed are IF, ELSE, THEN,  UNTIL, WHILE, etc.

They have no error checking they just work.  You may have a question or two. It took me a while to grok these things. :) 

 

Here is a link:

https://github.com/bfox9900/CAMEL99-V2/blob/master/LIB.ITC/ASM9900.FTH

Edited by TheBF
typo
  • Like 1
Link to comment
Share on other sites

52 minutes ago, GDMike said:

BTW, do you have a simple Forth assembly code I can look at to figure out how things are done without labels, branches like what I use in a loop whenever you find a moment.. just something I'd like to review. 

I did put together marks TF assembler manual that he provides, but again, I forgot to bring it to work with me for the second day.

Oops.

You may have questions about Forth loops not Assembler loops. The good news is they are similar.

Forth has two "jump"  instructions.

 

?BRANCH  ( sometimes called 0BRANCH)   jumps if  top of stack=0.

The cell right after ?branch contains a negative or a positive number.  TurboForth uses a 16bit address to jump to.   FbForth and Camel Forth use +/- value to add to the instruction pointer to know where to jump to.

 

BRANCH  Jump unconditionally to the address (or the offset) that follows branch.

 

So the trick is how you do all those fancy IF THEN  BEGIN UNTIL  when you only have 2 jump instructions?

 

Here is the magic code from Australia. :) 

They are dead simple without error checking so it's simpler to understand. 


: AHEAD    ( -- addr) HERE   0 , ;
: <BACK ( addr --) HERE -  , ;

: THEN   ( addr -- ) HERE OVER - SWAP ! ;     IMMEDIATE
: BEGIN   HERE ;                              IMMEDIATE
: IF      POSTPONE ?BRANCH AHEAD ;            IMMEDIATE
: ELSE    POSTPONE BRANCH  AHEAD SWAP POSTPONE THEN ; IMMEDIATE
: UNTIL   POSTPONE ?BRANCH <BACK ;  IMMEDIATE
: AGAIN   POSTPONE BRANCH  <BACK ;  IMMEDIATE
: WHILE   POSTPONE IF SWAP ;        IMMEDIATE
: REPEAT  POSTPONE AGAIN POSTPONE THEN ; IMMEDIATE

Think of POSTPONE as a word that "compiles" something into a Forth definition.  

 

 Simplest loop structure to understand:   BEGIN  AGAIN 

: TEST    

     BEGIN        ( puts HERE on the data stack because it's an immediate word) 

        2 2 +    (  we put some code in the definition which moves the dictionary pointer forward. (Remember that HERE just does fetch on the dictionary pointer variable)

        DUP DROP 

     AGAIN     ( compile the Forth BRANCH word into the definition,

                   ( <BACK  computes the difference between the HERE at BEGIN and HERE right now and compiles that number with comma)

                   ( TF compiles the actual HERE from BEGIN)

;  

Give it a stare and ask more questions.

 

 

Edited by TheBF
  • Like 2
Link to comment
Share on other sites

Now I gotta try this out. Actually, I am asking about both, this is a nice start.

Meaning forth assembler. But I have that manual, I'll look at that. But this is very good to start with. I Know simple loops using DO .. LOOP and using that, but this is a nice example I never seen. Thank you.

I'll jump out now...

 

Edited by GDMike
Link to comment
Share on other sites

Immediate words are the key to doing powerful things in the Forth language. As you can see, CAMEL99 uses POSTPONE to compile a word (immediate or not) into a definition. TF (and possibly fbForth?) uses COMPILE and [COMPILE] (though POSTPONE is defined on the TurboForth TOOLS disk if you want to use POSTPONE in TF).

 

For an introduction to immediate words, have a read of this (this took a bit of tracking down!):

 

The information presented above applies to all Forth systems, not just TF or CAMEL or fbForth. Immediate words are a pretty much universal Forth concept.

 

I'm having a blast reading these old articles - it's like someone else wrote them! I'm impressed at how much stuff I knew, and depressed at how much stuff I've forgotten! :roll:

Edited by Willsy
  • Like 3
Link to comment
Share on other sites

Funny thing, as I was typing letter by letter in a screen,  because of other reasons, into my TF  as I needed the SAMs functionality and only had a screenshot of the definitions, and I saw this, [COMPILE] and I noticed a word prior to the word [COMPILE] and i assumed it was creating a word on the fly so to speak, and I haven't had time to try this on my own yet, and I haven't quite understood the difference between [COMPILE] and COMPILE... but anyway..let me get back into the book first before tying up the Post.

A lot can be had by reading... thx all

Edited by GDMike
Link to comment
Share on other sites

On 1/18/2022 at 3:27 PM, GDMike said:

Funny thing, as I was typing letter by letter in a screen,  because of other reasons, into my TF  as I needed the SAMs functionality and only had a screenshot of the definitions, and I saw this, [COMPILE] and I noticed a word prior to the word [COMPILE] and i assumed it was creating a word on the fly so to speak, and I haven't had time to try this on my own yet, and I haven't quite understood the difference between [COMPILE] and COMPILE... but anyway..let me get back into the book first before tying up the Post.

A lot can be had by reading... thx all

This can get into the weeds pretty fast in Forth and truth be told I most of the time have to try things a few times before they work as I want them to.

 

So COMPILE and [COMPILE] are used to make a special kind of words that let you extend or change how the compiler works.

It's important to understand this point because when programming in most languages you don't change the compiler. :) 

So this is a pretty special case. I would say black-belt level Forth.

 

So lets look at the examples for IF up above. 

In Forth83 or Fig Forth this would be like below (their are other error protection words used in a lot of systems but this is the payload section)

: IF         COMPILE ?BRANCH   AHEAD ;  IMMEDIATE 

The system has a word called ?BRANCH that compares the TOS to zero and jumps ahead if it is true.

 

When we make this code in our program it will type "TRUE!" if the TOS of stack is anything other than zero.

Here is how that happens.

: TEST       IF  ." TRUE!"  THEN ;  

Internally it looks like this which is really weird when you don't understand it. 

( Details will vary a bit on various Forth systems but here is what Camel Forth compiles)

: TEST     ?BRANCH 12  S" TRUE!" TYPE  ;                   
                                

Notice that when we typed IF the compiler put in ?BRANCH .  That is what COMPILE did.  It "compiled" the token for ?BRANCH into the word we created.  

 

Why go to that trouble?  Because ?BRANCH needs to know how far to jump "ahead". 

We don't actually know that when are programming so if figures that out for us.

Guess which word figures out how far to jump AHEAD? :) 

 

IF is an immediate word so even though we were in compile mode by the ':'     AHEAD ran when IF was invoked.

 

This what AHEAD did:

  • put the HERE address on the data stack to remember where it is
  • it compiled  0 into the HERE  address (using comma)
    **The zero is a place holder for how far "ahead" we have to jump. We won't know that until we hit "THEN". 
     

-----------------

Next we compiled a string "TRUE!" and TYPE to print the string.

 

When the compiler hits THEN  some magic happens.

: THEN   ( addr -- ) HERE OVER - SWAP ! ;     IMMEDIATE

There is already HERE on the data stack that is right after ?BRANCH.  

THEN  puts HERE on the data stack so we know where it is in memory.

If only we could somehow subtract those two addresses we would know how far ?BRANCH has to jump AHEAD! :)

Thank G_d we have a computer handy.

 

The calculation is HERE1 HERE2 OVER -  ( -- HERE1 offset)

Remember that zero we stuck in memory, it is at address HERE1.

So    SWAP !  puts the offset in memory that ?BRANCH needed all along.

 

You can use [COMPILE]  for the same thing as COMPILE but for "compiling" IMMEDIATE words.

 

"Thus endeth the lesson"

 

Edited by TheBF
removed whitespace
  • Like 1
  • Thanks 1
Link to comment
Share on other sites

Right on. Sorry to tie you up..it's fun though, but I don't see your arms wailing around...so much is missing by typing it out. 

I gotcha exactly, but I'm comparing it a bit to the assembler doing math for me at assembly Time when I don't know a particular value would be until run time for a situation, like a clock time or screen timer value..I suppose, maybe a poor comparison, but it's all I got..

I'm really jumping the gun and I should be in the book a bit more..I think, maybe, that some of this isn't really found that easy...it might be in the book but have no example...etc .

It'll be awhile before I use those words.. but I'll promise to get what I can get in my TF manual.

 

 

  • Like 1
Link to comment
Share on other sites

The explanations of COMPILE and [COMPILE] by @Willsy and @TheBF are spot on, but, to me, the very use of “compile” in the names of both of these two words has been the reason I took so long to grok what they actually did and how to use them. I agree with both fellas that POSTPONE is much to be preferred because the programmer does not lose any sleep over which of the other two words to use, but I think it is more consistent to think that what is always postponed is execution rather than compilation. The reason I say this is that, while the interpreter is compiling a new word started with : , [COMPILE] is the only way to compile an immediate word (execution only), whereas COMPILE does, in fact, defer or postpone compilation one level (but only for normal words).  [Note: You can use [COMPILE] to compile a normal word, but the interpreter would compile it anyway, so it is only reasonable to use it for immediate words. On the other hand, COMPILE will not work on immediate words at all. It must be used on normal words or bad things will happen.]

 

So, in line with “deferring execution”, [COMPILE] defers execution of an immediate word, COMPILE defers execution of a normal word, and POSTPONE defers execution of either. Here is how to use [COMPILE] and COMPILE :

 

Spoiler

: IMMEDIATE_WORD_1  ( do stuff, even while compiling )  ;
IMMEDIATE    \ make IMMEDIATE_WORD_1 immediate

: IMMEDIATE_WORD_2  ( do stuff, even while compiling )  ;
IMMEDIATE    \ make IMMEDIATE_WORD_2 immediate

: NORMAL_WORD  ( do stuff normally )  ;
: OTHER_STUFF  ( do stuff normally )  ;

: WORD1
   IMMEDIATE_WORD_1              \ IMMEDIATE_WORD_1 executes now
   [COMPILE] IMMEDIATE_WORD_2    \ IMMEDIATE_WORD_2 compiles now
   COMPILE NORMAL_WORD           \ COMPILE & NORMAL_WORD both compile now
   OTHER_STUFF                   \ OTHER_STUFF compiles now
   ;
IMMEDIATE   \ make WORD1 immediate

:WORD2
   WORD1    \ executes now and does the following:
      \ IMMEDIATE_WORD_2 executes now
      \ COMPILE executes and compiles NORMAL_WORD
      \ OTHER_STUFF executes now
   \ remainder of definition...
   ;

WORD2    \ WORD2 executes now and does the following:
         \ NORMAL_WORD executes now
         \ remainder of definition executes now

 

 

...lee

  • Like 2
Link to comment
Share on other sites

That's a good example, Lee. Here's another (re-hashed from the article I quoted above) with observable results:

 

In TF or fbForth, type this (it will work in CAMEL99, too - just use POSTPONE instead of [COMPILE]:

: BOB ( -- ) CR ." BOO! BOB WAS HERE!" CR ; IMMEDIATE

Okay, you typed it in. Nothing much happened. Now execute it: type BOB and press enter. Again, no big surprises.

 

Now, try this:

: TOM ( -- ) BOB CR ." HELLO! I AM TOM!" CR ;

Did you see what happened? While *TOM* was being compiled, BOB got in on the act and ran, rather rudely announcing his presence. Why? Because he is an immediate word, and so, when encountered by the compiler, it is executed IMMEDIATEly.

 

So what happens if we run TOM (type TOM and press enter)?

 

HELLO! I AM TOM!

 

Where's BOB? Should BOB not also say BOO!? No. Because BOB was executed at compile-time (during the compilation of TOM).

 

Sometimes, we might to override this behaviour. Sometimes we want an immediate word to be actually compiled by the compiler rather than executed. We can do this with [COMPILE]. So, we could re-write TOM like this:

: TOM ( -- ) [COMPILE] BOB CR ." HELLO! I AM TOM!" CR ;

Now, when TOM is compiled, nothing really happens. It just compiles it. And when TOM is executed, BOB announces his presence along with TOM, exactly the same as if we'd said:

: TOM ( -- ) BOB CR ." HELLO! I AM TOM!" CR ;

 

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

4 hours ago, Willsy said:

(with apologies to Brian for hijacking the CAMEL99 thread with a discussion in IMMEDIATE words!) ;-)

No apology needed. It's all important for GDMike to help him code his project so thanks for contributing Mark.

  • Like 1
Link to comment
Share on other sites

Don't like RPN you say...

 

I found this code on a site by Marcel Hendrix, author of iForth, a very fast native code compiler for intel boxes.

ec 212a KISS (iae.nl)

 

The code by Albert Nijhof is devilishly clever. The way you can just declare operators is brilliant.

I think I could improve it by making another vocabulary so there are no name conflicts with Forth operators. 

 

I changed a couple of names because these suited my mentality but I did get the original version to compile with only a three-line harness.

I also added (( and ))  to make things look nicer when they are needed.

I think I tried a few years back but did not have a compliant wordlist library.  Three cheers for ANS Forth.

 

It hurts my head to type infix math into a Forth command line. :) 

Spoiler

\ KISS COMMANDS (Albert Nijhof) -- 1 april 2003
\ Mods for Camel Forth and some name changes   Brian Fox Jan 20 2022

\ Camel99 harness
INCLUDE DSK1.TOOLS
INCLUDE DSK1.WORDLISTS
' 2- ALIAS CELL-

ONLY FORTH DEFINITIONS
DECIMAL
VOCABULARY INFIX
ALSO INFIX DEFINITIONS

\ P-stack with relative stackpointer in cell # 0
12 CELLS CONSTANT PQ
CREATE P   0 ,   PQ ALLOT
: FRESH    0 P ! ;                 \ Reset p-stack

: ?P ( p# -- )   \ Check overflow and underflow
  PQ 0 WITHIN
  IF   FRESH TRUE ABORT" Syntax Error "
  THEN ;
: P> ( -- x ) P @ DUP CELL- DUP ?P P ! P + @ ;

: >P ( x -- ) P @ DUP ?P CELL+ DUP P ! P + ! ;

ALSO FORTH DEFINITIONS
: ) ( -- )
  P> 2@                   ( xt imm? )
  0< STATE @ AND
  IF   COMPILE, EXIT
  THEN EXECUTE ; IMMEDIATE

: INFIX: ( ccc -- )
  >IN @ >R
  ' DROP       \ Does this word exist?
  R@ >IN !
  BL WORD FIND  ( -- xt imm?)
  R> >IN !
  CREATE
      HERE 2 CELLS ALLOT 2! IMMEDIATE
  DOES>
      >P
      BL WORD COUNT EVALUATE
      POSTPONE ) ;

: DUMMY ; IMMEDIATE

INFIX: DUMMY

\ we now loose or ( -- ) comments but oh well
: (   \ --
  ['] DUMMY >BODY >P ; IMMEDIATE

: ((    POSTPONE (  POSTPONE ( ;  IMMEDIATE
: ))    POSTPONE )  POSTPONE ) ;  IMMEDIATE

PREVIOUS FORTH
\ ----- End of code -----

\ ----- Examples -----
\ define infix operators
INFIX: +      INFIX: -       INFIX: *       INFIX: /
INFIX: .      INFIX: EMIT
INFIX: >      INFIX: <       INFIX: =       INFIX: <>
INFIX: IF     INFIX: THEN
INFIX: AND

: TEST \  ( x -- )
    CR . DUP ." is "
    IF ( DUP = 0 )  THEN ( ." zero " )
    IF ( DUP < 0 )  THEN ( ." negative " )
    IF ( 0 < OVER ) THEN ( ." positive " )
    ." and "
    IF   ( = ( 1 AND TUCK ) )
    THEN ( ." odd." ELSE ." even." ) ;

\ make a infix version of TEST
INFIX: TEST

INFIX: OR      INFIX: XOR    INFIX: WITHIN

: >UP  \ ( ch1 -- ch2 )
    XOR ( DUP
          WITHIN ( [CHAR] a [CHAR] z + 1 )
          AND BL
        ) ;
INFIX: >UP

 

 

infix-screen.png

  • Like 2
Link to comment
Share on other sites

Nice job! Do you remember, decades ago (mid 80s?) Charles Moore himself wrote a version of BASIC in Forth. It was published in Forth Dimensions IIRC. It was relatively simple, as the idea was to prove a concept, but IIRC there was some clever stuff going on in there! Must see if I can find out - still need to dig my old laptop out of the garage!

  • Like 3
Link to comment
Share on other sites

2 hours ago, Willsy said:

Nice job! Do you remember, decades ago (mid 80s?) Charles Moore himself wrote a version of BASIC in Forth. It was published in Forth Dimensions IIRC. It was relatively simple, as the idea was to prove a concept, but IIRC there was some clever stuff going on in there! Must see if I can find out - still need to dig my old laptop out of the garage!

LOL.  I didn't have to do much. Mr. Nijhof is a pretty hot Forth programmers.

 

Yes I do remember that one.  I tried porting it once but failed.

It does beg the question. What would a BASIC in Forth be like?  

I often wonder would it run faster than on written in GPL ?

The BASIC compiler that the community uses is actually compiling to direct threaded code so that's a pretty good indicator of what could be done.

 

 

 

  • Like 4
Link to comment
Share on other sites

Now that I seem to have a stable build

 

I have read that an ITC Forth system spends about 50% of its time running the inner interpreter called NEXT.

 

I often wondered how much difference this would make:

 

NEXT as it exists in the existing TI-99 Forth systems...

l: _next     *IP+ W  MOV,    
             *W+  R5 MOV,    
                 *R5 B,         

Versus this:

l: _next     *IP+ W  MOV,    
             *W   R5 MOV,    
                 *R5 B,      

The difference is only one auto-increment, 4 clocks, but it is a reduction from 56 total to 52 total or a speedup of 3.7%

 

Now that I have a nice build file it was easier to find out.

I made a new version of my primitives file with this new NEXT code and I had to add one line to four routines:

W INCT, 

to  DOVAR  DOCON DOUSER and DOCOL.

 

And the results are...  its a bit faster. :) 

On code like OPTEST below where each word is short and NEXT makes up a big piece of the running time I measured

12.6 sec.  vs  12.2 sec   or  3.3% speedup.

 

On a big test like the SEVENS benchmark it was 64.7 secs vs 64.1 secs so very little, but still faster. 

HEX
: OPTEST      ( mixed )
          3000 0
          DO
               AAAA   ( lit)
               DUP
               SWAP
               OVER
               ROT
               DROP
               DUP AND
               DUP OR
               DUP XOR
               1+
               1-
               2+
               2-
               2*
               2/
               NEGATE
               ABS
               +
               2 *
               DROP
          LOOP  ;

 

  • Like 4
Link to comment
Share on other sites

5 hours ago, TheBF said:

Now that I seem to have a stable build     I have read that an ITC Forth system spends about 50% of its time running the inner interpreter called NEXT. I often wondered how much difference this would make:       NEXT as it exists in the existing TI-99 Forth systems...


l: _next     *IP+ W  MOV,    
             *W+  R5 MOV,    
                 *R5 B,         

Versus this:


l: _next     *IP+ W  MOV,    
             *W   R5 MOV,    
                 *R5 B,      

The difference is only one auto-increment, 4 clocks, but it is a reduction from 56 total to 52 total or a speedup of 3.7%. Now that I have a nice build file it was easier to find out. I made a new version of my primitives file with this new NEXT code and I had to add one line to four routines:


W INCT, 

to  DOVAR  DOCON DOUSER and DOCOL. And the results are...  its a bit faster. :)  On code like OPTEST below where each word is short and NEXT makes up a big piece of the running time I measured 12.6 sec.  vs  12.2 sec   or  3.3% speedup.

 

Not sure how this would play in TI Forth and fbForth. The payloads for DOVAR DOCON DOUSER all call DODOES , which falls through to DOCOL and $NEXT . All colon definitions end in ; , which executes $SEMIS , which executes a copy of $NEXT , which actually might make it possible to separate direct calls to $NEXT with your improvement (would also affect DOEXEC ). All of this code is in scratchpad RAM on the 16-bit bus for speed:

DODOES DECT SP
       MOV  W,*SP
       MOV  LINK,W
DOCOL  DECT R
       MOV  IP,*R
       MOV  W,IP
$NEXT  MOV  *IP+,W
DOEXEC MOV  *W+,R1
       B    *R1
$SEMIS MOV  *R+,IP
       MOV  *IP+,W   <<<----copy of $NEXT
       MOV  *W+,R1   <<<----copy of DOEXEC
       B    *R1      <<<---+

...lee

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...