6502.org Forum  Projects  Code  Documents  Tools  Forum
It is currently Fri May 10, 2024 1:12 pm

All times are UTC




Post new topic Reply to topic  [ 17 posts ]  Go to page 1, 2  Next
Author Message
PostPosted: Sun Aug 05, 2018 10:08 pm 
Offline

Joined: Fri May 05, 2017 9:27 pm
Posts: 858
The Forth I wrote for the Commodore 64 has a word to go from high level code to assembly called >ASSEM and a word to go from assembly to high level called >FORTH. They do not need paired. A word can start out as a colon definition and go to assembly with >ASSEM and end with a jump to NEXT (or jump to code that jumps or falls through to NEXT) or it can go back to high level with >FORTH. Likewise, a code word can go high level with >FORTH and terminate with ; or go back to assembly with >ASSEM. Here is a short segment of code which uses the C64 REU (ram expansion unit).
Code:
   DF09 LDA,  01F # CMP,  0= IF,  ( test for presence of REU)
      DF0A LDA,  03F # CMP,
   0= NOT ELIF,
      >FORTH TRUE
      ABORT" REU NOT PRESENT"
      >ASSEM
   THEN,
   <rest of code>

It's an easy way to test for the presence of the REU and abort from the code level word. In another example, my version of (TYPE), the vector for TYPE is a code word but I want multitasking support.
Code:
: (TYPE)  ( ADR CNT -- )
   PAUSE   ( task switcher)
   >ASSEM
   2 # LDA,  SETUP JSR,
   <rest of code>

Type starts as a colon definition so PAUSE can be called and goes to assembly level where it stays and ends with a jump to NEXT.

cheers,
Jim


Top
 Profile  
Reply with quote  
PostPosted: Thu Aug 09, 2018 6:58 pm 
Offline

Joined: Sat Dec 13, 2003 3:37 pm
Posts: 1004
I take it "; " terminates the compiler whether under >ASSEM or >FORTH ?


Top
 Profile  
Reply with quote  
PostPosted: Sun Aug 12, 2018 6:22 pm 
Offline

Joined: Fri May 05, 2017 9:27 pm
Posts: 858
whartung wrote:
I take it "; " terminates the compiler whether under >ASSEM or >FORTH ?

No. My Forth is a Forth-83 standard ITC Forth for the Commodore 64. Semicolon ; terminates high level (colon) definitions. Code definitions are terminated by END-CODE. A code word must have a jump to NEXT or code that jumps to or falls through ( like PUSH and PUT) to NEXT.
>FORTH is an immediate word that can only be used while interpreting, as in compiling a code definition. If STATE is compiling, then >FORTH aborts with the message "EXECUTION ONLY". >FORTH compiles a JSR to the body of (>FORTH) then sets the context vocabulary to the current one and sets the compiling state.
(>FORTH) pulls the JSR's return address off the return stack, increments it and saves it in N, the scratch pad area in zero page, and the Y register. It then pushes IP to the return stack. It takes the address saved in N and the Y register and stores it in IP and jumps to NEXT. Since (>FORTH) performs the function of 'nest', the word transitions from a code word to a high level 'colon definition' without the need to return to the assembly code level. This high level code can now be written to do anything any other high level code can do. It can have multiple EXIT's (EXIT is the word compiled by semicolon ;) or branch into another high level word.
This is in the kernel source.
Code:
CODE (>FORTH)  ( -- )
   CLC,
   PLA,  1 # ADC,  N STA,
   PLA,  0 # ADC,  TAY,
   IP 1+ LDA,  PHA,
   IP    LDA,  PHA,
   N LDA,
   IP    STA,
   IP 1+ STY,
   NEXT JMP,  END-CODE

And this is in the system loader loaded by the kernel.
Code:
: >FORTH  ( -- )  ?EXEC
   [ ' (>FORTH) >BODY ] LITERAL
   [ ASSEMBLER ] JSR, [ FORTH ]
   CURRENT @ CONTEXT !
   ] ; IMMEDIATE

>ASSEM is an immediate word that can only be used while compiling. If STATE is interpreting, then >ASSEM aborts with the message "COMPILING ONLY". >ASSEM compiles (>ASSEM) into the high level code then sets CONTEXT to the assembler vocabulary and sets the interpreting state.
(>ASSEM) stores IP in N and N+1, then pulls the value off the return stack and stores it in IP, performing an unnest. It then performs an indirect jump through N. Since (>ASSEM) performs the function 'unnest' (what EXIT does), the word transitions from a high level 'colon definition' to a code word without the need to return to high level. This code level word can now be written to do anything any other code word can do.
This is in the kernel source.
Code:
CODE (>ASSEM)  ( -- )
   IP    LDA,  N    STA,
   IP 1+ LDA,  N 1+ STA,
   PLA,  IP STA,  PLA,  IP 1+ STA,
   N ) JMP,  END-CODE

And this is in the system loader loaded by the kernel.
Code:
: >ASSEM  ( -- )
   COMPILE (>ASSEM)
   [ ASSEMBLER ] MEM ASSEMBLER
   [ FORTH ]
   [COMPILE] [ ; IMMEDIATE

Here is my cold start routine for an example. Since this is on a Commodore 64, the system has one line of basic:
Code:
10 SYS 10952

The SYS causes a jump to the cold start routine at address 10952, hexadecimal 2AC8.
Code:
SCR# A1
// COLD
HEX // USER COLD START
: COLD  ( -- )
   SAVE-BUFFERS  EMPTY
   ACLOSE     // CLOSE ALL FILES
   >ASSEM
// POWERUP COLD START
// PATCH THE 'BASIC FUSE'
DECIMAL HERE 0 (UD.)
HEX 80B OVER - SWAP CMOVE>V
   SEI,
   0FF87 JSR, // RAMTAS
   0FF8A JSR, // RESTOR
   0FFE7 JSR, // CLALL
   0FF84 JSR, // IOINIT
   0FF81 JSR, // CINT

SCR# A2
// COLD
   ' WARM @  100 /MOD SWAP
      # LDA,  300 STA,
      # LDA,  301 STA,
   0D # LDY,  (WARM) JSR,
   >FORTH
   RP!
   EMPTY 0 DRIVE CONFIGURE
   0A SPACES
   ." C64      FORTH"
   CR CR
   ." COPYRIGHT (C) 1995-2018 BY JAMES BOYD"
   CR INITIAL ABORT ; -2 ALLOT

At start up, BASIC performs a SYS to the Set Interrupt Disable instruction (SEI,) in the cold start routine. Once the system is up and running, the cold start routine can also be called with the word COLD. COLD first saves the block buffers, empties the dictionary to the lesser of its initial and current sizes (saving this value as the new empty point), and closes all files before transitioning to the low level cold start routine.
The Commodore 64 lacks a backslash key so the double slash // is the word to treat the rest of the line as a comment. The funny names like RAMTAS and RESTOR are the names given to Commodore kernel routines in the Commodore 64 Programmer's Reference Guide.
I blanked out the name I'm using for my Forth for now. I'm having trouble thinking of a really good one.
Sorry about the commas at the end of the names of the op codes, I have them there to be compatible with other C64 Forths. Both 64Forth and Blazin' Forth have commas in the op code names. I'd personally like to remove them from my assembler but I hope to make this Forth publicly available one day and I don't know how much grief it would cause someone to rewrite assembly code, by removing all the commas in the opcode names of their source, to try on this Forth.
For another example, here is the full source for (RR/W), the code to access the REU, Commodore's Ram Expansion Unit, as Forth blocks.
Code:
SCR# 2A
// (RR/W)
HEX
CODE (RR/W)  ( ADR BLK# F CNT -- )
   DF09 LDA,  1F # CMP,  0= IF,
      DF0A LDA,  3F # CMP,
   0= NOT ELIF,
      >FORTH TRUE
      ABORT" REU NOT PRESENT"
      >ASSEM
   THEN,
   DF04 STY,  4 ,X LDA,
   .A ASL,  5 ,X ROL,
   .A ASL,  5 ,X ROL,
   DF05 STA,
   5 ,X LDA,  DF06 STA,

SCR# 2B
// (RR/W)
   0 ,X LDA,  DF07 STA,
   1 ,X LDA,  DF08 STA,
   6 ,X LDA,  DF02 STA,
   7 ,X LDA,  DF03 STA,
   2 ,X LDA,  10 # ORA,  DF01 STA,
   80 # ORA,  DF01 STA,
   BEGIN,
      DF00 LDA,  40 # AND,
   0= NOT UNTIL,
   INX,  INX,  INX,  INX,
   POPTWO JMP,  END-CODE
' (RR/W) IS RR/W

There is one caveat when using >FORTH and >ASSEM with control structures which should be obvious, but I'll mention it anyway. If a transition from low to high or high to low occurs in a control structure, the opposite transition must occur before a matching control structure word is used. I don't have actual examples other than the IF, ELIF, THEN, control block in the code above for the ram expander, so here is some pseudo-code:
Code:
: <A-HIGH-LEVEL-WORD>
   BEGIN
      SOME-HIGH-LEVEL-STUFF
      >ASSEM
      SOME-LOW-LEVEL-STUFF
      >FORTH
   WHILE
      MORE-STUFF
   REPEAT ;
   
CODE <A-CODE-LEVEL-WORD>
   BEGIN,
      SOME-LOW-LEVEL-STUFF
   WHILE,
      MORE-LOW-LEVEL-STUFF
      >FORTH
      SOME-HIGH-LEVEL-STUFF
      >ASSEM
      EVEN-MORE-LOW-LEVEL-STUFF
      >FORTH
      MORE-HIGH-LEVEL-STUFF
      >ASSEM
   REPEAT,
   NEXT JMP,  END-CODE



Cheers,
Jim


Top
 Profile  
Reply with quote  
PostPosted: Mon Sep 10, 2018 9:21 pm 
Offline
User avatar

Joined: Fri Aug 30, 2002 1:09 am
Posts: 8433
Location: Southern California
JimBoyd wrote:
The Forth I wrote for the Commodore 64 has a word to go from high level code to assembly called >ASSEM and a word to go from assembly to high level called >FORTH.

Although your names make a lot of sense (and I like them), I would encourage going with names that are already in use like Bruce brought up, above, INLINE and END-INLINE. Even if they haven't made it into ANS or Forth 2012 standards, common usage is, in a way, a standard in itself. I changed the names of a few of my "inventions" after I found out other better-known Forths used a different name for the same thing. You haven't distributed your Forth yet, and hopefully you don't have much code written to use it yet. The sooner you change it, the easier it will be to change it and promote acceptance.

Although there are things about ANS that I don't think are suitable for 65xx, I know that one thing impeding the acceptance of Forth has been that we independent-minded, free-thinking Forthers all tend to do things our own way. That's a strength of Forth, that it allows us to do that possibly more than any other HLL; but it makes it harder for someone who wants to get into it and is looking over the options and just finds more confusion because he can't find agreement between versions. I remember letters to the editor in Forth Dimensions magazine lamenting that a problem standing in the way of acceptance of Forth is that there was no effective standard. That was before ANS Forth. The X3J14 committee had a huge task on their hands which was not easy. They did the best they could, I believe, and still ruffled a lot of feathers because there was no way to make everyone happy in some areas. Jack Woehr of Vesta Technologies who was on the X3J14 committee says in his book "Forth: The New Model", "When Forth, which some hold to be inextricably wedded to hardware, takes responsibility for cross-platform portability, a certain light-footedness and grace will be surrendered." He admits that optimum portability and optimum efficiency don't come at the same point. Fortunately he also says it's not the committee's intention to force anyone to comply with the standard.

For the parts that don't cramp the 65xx's style though, I try to make my word names conform to what's in common usage.

_________________
http://WilsonMinesCo.com/ lots of 6502 resources
The "second front page" is http://wilsonminesco.com/links.html .
What's an additional VIA among friends, anyhow?


Top
 Profile  
Reply with quote  
PostPosted: Mon Sep 10, 2018 10:36 pm 
Offline

Joined: Fri May 05, 2017 9:27 pm
Posts: 858
GARTHWILSON wrote:
JimBoyd wrote:
The Forth I wrote for the Commodore 64 has a word to go from high level code to assembly called >ASSEM and a word to go from assembly to high level called >FORTH.

Although your names make a lot of sense (and I like them), I would encourage going with names that are already in use like Bruce brought up, above, INLINE and END-INLINE.

Thanks, but I can't really take credit for the names. I saw in online documentation for Mosaic Forth ( I was trying to find more information on Forth) it had the names >ASSM and >FORTH. While I agree about standard names in general, long ago I renamed UNDO to UNLOOP, I see a problem with renaming >ASSEM and >FORTH. If I rename >ASSEM to INLINE and >FORTH to END-INLINE it looks fine with words that start high level, transition to assembly, then back to high level.
Code:
HEX
: #  ( D1 -- D2 )
   BASE @ UD/MOD ROT
   INLINE
   0 ,X LDA,  0A # CMP,  CS IF,
      6 # ADC,
   THEN,
   30 # ADC,  0 ,X STA,
   END-INLINE
   HOLD ;

It looks a little strange with a word that starts high level then goes to assembly and stays there.
Code:
HEX
: (TYPE)  ( ADR CNT -- )
   PAUSE  INLINE
   2 # LDA,  SETUP JSR,
   BEGIN,
      BEGIN,
         N CPY,
         0= IF,  N 1+ LDA,
            0= IF,  NEXT JMP,  THEN,
            N 1+ DEC,
         THEN,
         N 2+ )Y LDA,
         ' (EMIT) @ 8 + JSR,
      INY,  0= UNTIL,
      N 3 + INC,
   AGAIN,  END-CODE
   // Where did END-ENLINE go? wasn't that assembly just supposed to be inline code?

And looks really strange with a word that starts as a code definition, then transitions to high level then back.
Code:
HEX
CODE (RR/W)  ( ADR BLK# R/WF CNT -- )
   DF09 LDA,  1F # CMP,  0= IF,
      DF0A LDA,  3F # CMP,
   0= NOT ELIF,
      END-INLINE                       // This looks backwards
      TRUE ABORT" REU NOT PRESENT"     //
      INLINE                           // but it's not.
   THEN,
   DF04 STY,  4 ,X LDA,
   .A ASL,  5 ,X ROL,
   .A ASL,  5 ,X ROL,
   DF05 STA,
   5 ,X LDA,  DF06 STA,
   0 ,X LDA,  DF07 STA,
   1 ,X LDA,  DF08 STA,
   6 ,X LDA,  DF02 STA,
   7 ,X LDA,  DF03 STA,
   2 ,X LDA,  10 # ORA,  DF01 STA,
   80 # ORA,  DF01 STA,
   BEGIN,
      DF00 LDA,  40 # AND,
   0= NOT UNTIL,
   INX,  INX,  INX,  INX,
   POPTWO JMP,  END-CODE
' (RR/W) IS RR/W

I'm not trying to be difficult but it seems that >ASSEM and >FORTH aren't really like INLINE and END-INLINE. It looks as though INLINE and END-INLINE are meant to be paired in that order. >ASSEM and >FORTH don't need to be paired. >ASSEM performs an unnest, like EXIT and >FORTH performs a nest, like do-colon. As my definition of (TYPE) shows, they both don't need to be present in a definition.
[Edit: fixed a typo]


Last edited by JimBoyd on Thu Nov 18, 2021 2:22 am, edited 1 time in total.

Top
 Profile  
Reply with quote  
PostPosted: Mon Sep 10, 2018 11:00 pm 
Offline

Joined: Fri May 05, 2017 9:27 pm
Posts: 858
Actually, at the time I wrote >ASSEM and >FORTH, I'd forgotten that the Mosaic Industries version, >ASSM, didn't have an 'E' in the name.


Top
 Profile  
Reply with quote  
PostPosted: Mon Sep 10, 2018 11:16 pm 
Offline
User avatar

Joined: Fri Aug 30, 2002 1:09 am
Posts: 8433
Location: Southern California
If the function is different, and a major, popular Forth was already using >ASSEM and >FORTH, then I'd say go ahead and keep those names. I just haven't heard of them before. The way I did INLINE and END_INLINE, they don't particularly need to be paired. I also don't use vocabularies though, which might make a difference. There's no conflict between assembly language and Forth words though, because for example AND in assembly language is never just AND; instead, the addressing mode goes with it, like AND#, AND_ZP, etc.. Similarly, there's no conflict with the # of "sharp" (in Forth) and the # of "immediate" in assembly. So I would write for example AND# FOOBAR , (the comma being part of it, for '816 with the accum in 16-bit mode) which I think is a lot more readable than FOOBAR # AND , and there's no parsing because all AND# does is lay down the op code. It's up to the programmer to comma-in the operand (if any). (I've said this in previous posts, but you're a welcome new member who probably hasn't read all the archives yet. :D )

And you posted this while I was writing:
JimBoyd wrote:
Actually, at the time I wrote >ASSEM and >FORTH, I'd forgotten that the Mosaic Industries version, >ASSM, didn't have an 'E' in the name.

If they were going to leave out more letters, too bad they didn't shorten it to >ASM which might be even more clear because of the common use of those three letters for "assembly." "ASSM" could look like "assimilate" or any of a lot of other things.

_________________
http://WilsonMinesCo.com/ lots of 6502 resources
The "second front page" is http://wilsonminesco.com/links.html .
What's an additional VIA among friends, anyhow?


Top
 Profile  
Reply with quote  
PostPosted: Mon Sep 10, 2018 11:35 pm 
Offline

Joined: Fri May 05, 2017 9:27 pm
Posts: 858
GARTHWILSON wrote:
(I've said this in previous posts, but you're a welcome new member who probably hasn't read all the archives yet. :D )

Although I haven't read all the archives, not even close, I do remember reading about your assembler. From my code you can probably tell that I actually prefer the FOOBAR # LDA, approach. Maybe I've been using it so long that It's what I'm comfortable with.


Top
 Profile  
Reply with quote  
PostPosted: Tue Sep 11, 2018 3:24 pm 
Offline

Joined: Sun May 13, 2018 5:49 pm
Posts: 247
I ended up sneaking assembly into an Forth word for special cycle-count testing of Tali Forth 2 (an STC Forth). It was done to reduce the overhead of "stopwatching" a word. The simulator this runs in has a (virtual) stopwatch that is started by accessing $F006, stopped by accessing $F007, and the result (as a double-word with the bytes in correct 6502 forth order) shows up at $F008-$F00B. I use self-modifying code that replaces the address of the JSR between starting and stopping the virtual stopwatch. Processing the results is done in Forth. I don't have a Forth assembler loaded, so I just poked the opcodes into the word.

Code:
hex

\ The location of the result
F008 constant cycles

\ direct byte compiled
\  lda $f006
\  lda $f007
: cycles_overhead [ AD c, 06 c, F0 c, AD c, 07 c, F0 c, ] cycles 2@ ;

\ direct byte compiled
\  lda $F006
\  jsr (xt on stack goes here)
\  lda $f007
\ then forth code to fetch and print results.
: cycle_test_runtime
    [ AD c, 06 c, F0 c,    \ lda $F006
      20 c,  0000 ,        \ jsr (address to be filled in)
      AD c, 07 c, F0 c, ]  \ lda $F007
    cycles 2@              \ fetch result
    cycles_overhead d-     \ subtract overhead
    ." CYCLES: " 6 ud.r    \ print results
;

\ cycle_test updates the address of the given xt in cycle_test_runtime
\ then it runs the test.

\ To test a word, put any arguments it needs on the stack, use tick
\ (') on the word to get it's execution token (xt) and then put
\ cycle_test, then any stack cleanup.
\ eg. 5 ' dup cycle_test 2drop
: cycle_test ( xt -- )
    [ ' cycle_test_runtime 4 + ] literal ! cycle_test_runtime ;

To test a word, I just put some test arguments for it on the stack (if it needs them), use ' to get the XT of the word I want to test, and then run my test. Then I clean up the stack. I don't check the results of the operation because the test suite does that elsewhere. This is just to get an idea of how many CPU cycles each word takes. A sample test for DUP might look like:
Code:
5            ' dup           cycle_test 2drop

When run, that looks like:
Code:
5            ' dup           cycle_test 2drop      CYCLES:     37 ok


Top
 Profile  
Reply with quote  
 Post subject: Re:
PostPosted: Tue Sep 25, 2018 11:22 pm 
Offline

Joined: Fri May 05, 2017 9:27 pm
Posts: 858
dclxvi wrote:
Inline assembly with ITC or DTC isn't common because, unlike STC, you don't gain much.

Well, that depends. What about the case with inline high level code in an assembly ( code ) definition? My Forth is an ITC Forth for the C64 and has blocks. As I've mentioned elsewhere:
JimBoyd wrote:
If you were wondering, my Forth's BLOCK starts out as a code definition. As long as the requested block is the most recently used block, BLOCK stays at code level to replace the block number with the address of the appropriate buffer, then jumps to NEXT. If the requested block is not the most recently used one, BLOCK transitions to high level to deal with it.

It's been my experience that when BLOCK is called, it's usually called quite a few times with the same block number before a different block is requested. I thought,"Wouldn't it be nice if BLOCK were a code definition for all the times where it only has to replace the block number with an address?" Using >FORTH makes it easy to write BLOCK as a code definition if the requested block is the most recently used ( accessed ), yet be able to go to high level code for everything else.
Being able to ABORT or ABORT" from a code definition without the need to pass an error flag to a high level "wrapper word" is handy. I realize that some code words return a flag so the high level routine calling it can decide what to do. FIND comes to mind. If the word is not found in the CONTEXT vocabulary, search the CURRENT one, but I'm refering to a case where if the word were written in high level Forth, it would abort on an error. It would be nice to rewrite that word as a code word for speed, but it needs to abort on an error. It can by including inline high level forth code. It's also an easy way to get the coldstart and warmstart routines running the quit loop, just write it as a transition to high level:
Code:
<cold start stuff>
>FORTH
<high level initialization code>
INITIAL  \\ defered word -- default value is NOOP, a no-op
         \\ used to run additional initialization code
ABORT ;

I've found >FORTH and >ASSEM so useful that I've included them in my assembler and the primitives, (>FORTH) and (>ASSEM) are part of my Forth kernel. Since I already have them, including inline assembly in high level code doesn't cost anything extra. I rewrote # so it has inline assembly. the resulting word was four bytes smaller ( on my ITC Forth ) and the pictured numeric output words were a bit faster. When I have more time, I'll run some timing tests to get an idea of how much faster.
Anyway, I hope this gives food for thought.

Cheers,
Jim


Top
 Profile  
Reply with quote  
PostPosted: Mon Aug 17, 2020 11:08 pm 
Offline

Joined: Fri May 05, 2017 9:27 pm
Posts: 858
I noticed a typo while following a link from another topic to this one.
JimBoyd wrote:
>ASSEM performs an unnest, like EXIT and >FORTH performs a next, like do-colon.

Although it does jump to next, >FORTH performs a nest.


Top
 Profile  
Reply with quote  
 Post subject: Re:
PostPosted: Thu Dec 31, 2020 3:25 am 
Offline

Joined: Fri May 05, 2017 9:27 pm
Posts: 858
dclxvi wrote:
Inline assembly with ITC or DTC isn't common because, unlike STC, you don't gain much. Using a headerless code definition followed by an ordinary colon definition is often more flexible anyway. Even with something like FIG-Forth, which wasn't designed to use headerless words, it's easy to write a defining word that defines a headerless primitive. Many would argue, however, that inline assembly is a sign that you need to factor your definition.


What about inline high level Forth? Here is an example from Fleet Forth, an ITC Forth. I made (ABORT") , the word compiled by ABORT" , a primitive that has inline high level Forth.
If there is an error, the speed penalty of the high level Forth in (ABORT") is not a problem since we're aborting anyway.
If the top of stack is zero, (ABORT") increments IP past the inline string and jumps to POP, getting it's job done fast.
Since (ABORT") starts as a CODE word and stays at low level if there is no error, it greatly reduces the speed penalty of error checking.


Top
 Profile  
Reply with quote  
PostPosted: Thu May 18, 2023 12:20 am 
Offline

Joined: Fri May 05, 2017 9:27 pm
Posts: 858

A minor update. The source for my Forth's # used to be this:
Code:
HEX
: #  ( D1 -- D2 )
   BASE @ UD/MOD ROT
   INLINE
   0 ,X LDA,  0A # CMP,  CS IF,
      6 # ADC,
   THEN,
   30 # ADC,  0 ,X STA,
   END-INLINE
   HOLD ;

It is now this:
Code:
: #  ( D1 -- D2 )
   BASE @ UD/MOD ROT
   >ASSEM
   0 ,X LDA  #10 # CMP
   CS IF  6 # ADC  THEN
   #48 # ADC  0 ,X STA
   LABEL HOLD.BODY
   SEC
   ' HLD >BODY C@ # LDY
   DEX  DEX
   UP )Y LDA  1 # SBC  UP )Y STA
   0 ,X STA  INY
   UP )Y LDA  0 # SBC  UP )Y STA
   1 ,X STA
   LABEL C!.BODY
   2 ,X LDA  0 X) STA
   POPTWO JMP  END-CODE

HOLD and C! have no bodies. Their code fields point into the low level portion of # and SIGN is now a primitive.
Code:
CODE HOLD  ( C -- )
   HOLD.BODY  LATEST NAME> !
   END-CODE
CODE C!  ( C ADR -- )
   C!.BODY  LATEST NAME> !
   END-CODE
CODE SIGN  ( N -- )
   1 ,X ASL  ASCII - # LDA
   0 ,X STA
   ' HOLD @ CS BRAN
   POP JMP  END-CODE

Although # is much larger, less memory is used for these words than if # , HOLD and SIGN were high level. A savings of a few bytes and a speed up from mixing low level code in a high level word.


Top
 Profile  
Reply with quote  
Display posts from previous:  Sort by  
Post new topic Reply to topic  [ 17 posts ]  Go to page 1, 2  Next

All times are UTC


Who is online

Users browsing this forum: No registered users and 1 guest


You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot post attachments in this forum

Search for:
Jump to: