6502.org Forum  Projects  Code  Documents  Tools  Forum
It is currently Fri Apr 26, 2024 12:19 am

All times are UTC




Post new topic Reply to topic  [ 25 posts ]  Go to page 1, 2  Next
Author Message
PostPosted: Thu Jan 15, 2015 7:54 pm 
Offline

Joined: Mon Jan 07, 2013 2:42 pm
Posts: 576
Location: Just outside Berlin, Germany
While coding DEFER and friends for Tali Forth, I realized that I had made a fundamental design error with DOES> so that it only worked with simple cases (as in, the ones I initially tested for). I ended up rewriting CREATE, DOVAR, and (DOES>) and DODOES. Since CREATE/DOES is one of the most complex, but also most powerful parts of Forth, here's the walkthrough I created for myself. The basis is Subroutine Threaded Code (STC) variant for the 65c02. You'll probably want to read Brad's backgrounder on CREATE/DOES at http://www.bradrodriguez.com/papers/moving3.htm for the general idea and terminology.

So we start with the following standard learning example:
Code:
       : CONSTANT CREATE , DOES> @ ;
We examine this in three phases or "sequences", based on Derick and Baker (see Brad for details):

SEQUENCE I: Compiling the word CONSTANT

CONSTANT is a "defining word", one that makes new words. In pseudocode, the above compiles to:
Code:
        [Header "CONSTANT"]
        jsr CREATE
        jsr COMMA
        jsr (DOES>)         ; from DOES>
   a:   jsr DODOES          ; from DOES>
   b:   jsr FETCH
        rts
To make things easier to explain later, we've added the labels "a" and "b" in the listing. Note that DOES> is an immediate word that adds two subroutine jumps, one to (DOES>) and one to DODOES, which is a pre-defined system routine like DOVAR. We'll see what it does later.

SEQUENCE II: Executing the word CONSTANT / creating LIFE

Now, when we execute
Code:
        42 CONSTANT LIFE
This pushes the RTS of the calling routine -- call it "main" -- to the 65c02's stack (the Return Stack, as Forth calls it). It now looks something like this:
Code:
        [1] RTS to main routine
Without going into detail, the first two subroutine jumps of CONSTANT give us this word:
Code:
        [Header "LIFE"]
        jsr DOVAR               ; in CFA, from LIFE's CREATE
        4200                     ; in PFA (little-endian)
Next, we JSR to (DOES>). This jump places the RTS address to CONSTANT on the 65c02's stack, the address we had labeled "a".
Code:
        [2] RTS to CONSTANT ("a")
        [1] RTS to main routine
Now the tricks start. (DOES>) takes this address off the stack and uses it to replace the DOVAR JSR target in the CFA of our freshly created LIFE word. We now have this:
Code:
        [Header "LIFE"]         
        jsr a                     ; in CFA, modified by (DOES>)
   c:   4200                     ; in PFA (little-endian)
Note we added a label "c". Now when (DOES>) reaches its own RTS, it finds the RTS to the main routine on its stack. This is Good Thing (TM), because it aborts the execution of the rest of CONSTANT, and we don't want to do DODOES or FETCH now. We're back at the main routine.

SEQUENCE III: Executing LIFE

So now we have whatever main program we're running, and execute LIFE.
Code:
        jsr LIFE
The first thing this call does is push the RTS to the main routine on the 65c02's stack:
Code:
        [1] RTS to main
The CFA of LIFE executes a JSR to label "a" in CONSTANT. This pushes the RTS of LIFE on the 65c02' stack:
Code:
        [2] RTS to LIFE ("c")
        [1] RTS to main
This JSR to a lands us at the JSR to DODOES, so the return address to CONSTANT gets pushed on the stack as well. We had given this the label "b". After this, we have three addresses on the 65c02's stack:
Code:
        [3] RTS to CONSTANT ("b")
        [2] RTS to LIFE ("c")
        [1] RTS to main
DODOES pops address b off the 65c02's stack and puts it in a nice safe place in Zero Page, which we'll call "z". More on that in a moment. First, DODOES pops the RTS to LIFE. This in fact is "c", the address of the PFA or LIFE, where we stored the payload of this constant. Basically, DODOES performs a DOVAR here, and pushes "c" on the Data Stack. Now all we have left on the 65c02's stack is the RTS to the main routine.
Code:
        [1] RTS to main
This is where "z" comes in, the location in Zero Page where we stored address "b" of CONSTANT. Remember, this is where CONSTANT's own PFA begins, the FETCH command we had originally codes after DOES> in the very first definition. The really clever part: We perform an indirect JMP -- not a JSR! -- to this address.
Code:
        jmp (z)
Now CONSTANT's little program is executed, the subroutine jump to FETCH. Since we just put the PFA ("c") on the Data Stack, FETCH replaces this by 42, which is what we were aiming for all along. And since CONSTANT ends with a RTS, we pull the last remaining address off the 65c02's stack, which is the return address to the main routine where we started.

And that is sort of it. Put together, this is what we have to code:

DOES>: Compiles a subroutine jump to (DOES>), compiles a subroutine jump to DODOES.

(DOES>): Pops the stack (address of subroutine jump to DODOES in CONSTANT), increase this by one, replace the original DOVAR jump target in LIFE.

DODOES: Pop stack (CONSTANT's PFA), increase address by one, store on Zero Page; pop stack (LIFE's PFA), increase by one, store on Data Stack; JMP to address we stored in Zero Page.

Remember we have to increase the addresses by one because of the way JSR stores the return address for RTS on the stack on the 65c02: It points to the third byte of the JSR instruction itself, not the actual return address.

Of course, DEFER still doesn't work, but I think that's a completely different problem :D .


Last edited by scotws on Fri Jan 16, 2015 4:09 pm, edited 1 time in total.

Top
 Profile  
Reply with quote  
PostPosted: Fri Jan 16, 2015 3:16 am 
Offline
User avatar

Joined: Sun Jun 30, 2013 10:26 pm
Posts: 1926
Location: Sacramento, CA, USA
I'm not yet qualified to comment on the correctness of your implementation, but I will definitely re-read it (and Dr. Brad's page) several more times, since I'm going through a similar learning process for my attempt at a 65m32 Forth, just trailing behind you by several lengths. Perhaps someone here with more experience could provide some counter-examples, using DTC and ITC, to help us compare and contrast?

I have become disenchanted with all the jumping around that my incomplete ITC version is doing, and would like to convert to a more efficient DTC or STC design, but I am not yet aware of all the pitfalls that may loom ahead.

For example, ITC makes a habit of updating W in NEXT, but I'm wondering if it's possible to avoid this, and have the more-advanced words that use it try to work around its absence. I know that it's possible in STC, since NEXT is non-existent (due to the fact that PC and IP are one and the same), but I would also like to know if it's possible to avoid setting W in DTC's NEXT, because that would enable me to code it as a single machine instruction (rather than the two instructions I'm using for ITC).

I was excited to find the attached copy of forth9.asm for the 6809 on the 'net somewhere, because translating 6809 assembly to 65m32 assembly is a cake-walk for me. However, I was disappointed by what appears to me to be the misleading comment "This FORTH is direct threaded for speed, ..." because all of the "FDB *+2" lines at the CFA locations of the primitives tell me that it is ITC, not DTC, and I really want a complete DTC version for reference.

Attachment:
forth9.asm [78.72 KiB]
Downloaded 188 times


Dr. Brad's Z80 version of CamelForth is DTC, but translating Z80 assembly to 65m32 assembly is not nearly as much fun for me. I'll do it if I have to, and probably learn something in return, but there will be curse words involved in the process, because the Z80 (although obviously a capable little machine) rubs me the wrong way, and always has.

Does anyone have a 6xxx DTC Forth written in standard assembly format to which I could link?

Thanks,

Mike B.


Top
 Profile  
Reply with quote  
PostPosted: Fri Jan 16, 2015 1:39 pm 
Offline

Joined: Mon Jan 07, 2013 2:42 pm
Posts: 576
Location: Just outside Berlin, Germany
barrym95838 wrote:
Dr. Brad's Z80 version of CamelForth is DTC, but translating Z80 assembly to 65m32 assembly is not nearly as much fun for me.
I remember there was a 6809 version of CamelForth, but that was the metacompiled version?

The problem with STC Forth is that the clock cycles of the JSR/RTS quickly start to add up -- 12 ticks of overhead every single time. If you can stay below that, you're faster. Also, since the address pushed by RTS is the actual return address minus one, you spend a lot of time adding that one back, which is a hassle with 8 bit (after I finish Tali, I swear I'm switching to the 65816).

Do you have some mechanism to native-compile short words (so DROP is INX INX and not a jump or call)? At the moment, deciding which words to native compile in Tali is rather ad hoc ("looks short"). Once stuff is stable, I'll have to figure out something a bit more scientific based on a "acceptable percentage of overhead".


Top
 Profile  
Reply with quote  
PostPosted: Fri Jan 16, 2015 1:43 pm 
Offline

Joined: Mon Jan 07, 2013 2:42 pm
Posts: 576
Location: Just outside Berlin, Germany
One more thing I forgot to mention, which took me a few hours to figure out by myself: Normal CREATE includes a subroutine jump to DOVAR. But when CREATE is called by ":" (COLON), that jump is overwritten by whatever comes after it. Practically speaking, you back up three bytes after COMPILE is executed.

I need to clean up the code a bit, but hopefully should have the working new code on GitHub this weekend.


Top
 Profile  
Reply with quote  
PostPosted: Fri Jan 16, 2015 8:15 pm 
Offline
User avatar

Joined: Fri Aug 30, 2002 1:09 am
Posts: 8427
Location: Southern California
scotws wrote:
The problem with STC Forth is that the clock cycles of the JSR/RTS quickly start to add up -- 12 ticks of overhead every single time. If you can stay below that, you're faster. Also, since the address pushed by RTS is the actual return address minus one, you spend a lot of time adding that one back, which is a hassle with 8 bit (after I finish Tali, I swear I'm switching to the 65816).

Do you have some mechanism to native-compile short words (so DROP is INX INX and not a jump or call)? At the moment, deciding which words to native compile in Tali is rather ad hoc ("looks short"). Once stuff is stable, I'll have to figure out something a bit more scientific based on a "acceptable percentage of overhead".

We discussed this a little at viewtopic.php?f=9&t=533&p=3339#p3339 . (Actually this link starts you at the third post of the topic.)

_________________
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: Sat Jan 17, 2015 12:58 am 
Offline

Joined: Tue Jan 07, 2014 8:40 am
Posts: 91
scotws wrote:
I remember there was a 6809 version of CamelForth, but that was the metacompiled version?

Yes, that was the metacompiled version, using a postfix Forth assembler.

Sorry, I haven't had time to read your code walkthrough yet.

_________________
Because there are never enough Forth implementations: http://www.camelforth.com


Top
 Profile  
Reply with quote  
PostPosted: Sat Jan 17, 2015 2:59 pm 
Offline

Joined: Mon Jan 07, 2013 2:42 pm
Posts: 576
Location: Just outside Berlin, Germany
Actual code is now available at https://github.com/scotws/TaliForth . Oh, and I got DEFER to work :-) .


Top
 Profile  
Reply with quote  
PostPosted: Mon Jan 26, 2015 5:40 pm 
Offline

Joined: Mon Jan 26, 2015 6:19 am
Posts: 85
scotws wrote:
While coding DEFER and friends for Tali Forth, I realized that I had made a fundamental design error with DOES> so that it only worked with simple cases (as in, the ones I initially tested for). I ended up rewriting CREATE, DOVAR, and (DOES>) and DODOES. Since CREATE/DOES is one of the most complex, but also most powerful parts of Forth, here's the walkthrough I created for myself. The basis is Subroutine Threaded Code (STC) variant for the 65c02. You'll probably want to read Brad's backgrounder on CREATE/DOES at http://www.bradrodriguez.com/papers/moving3.htm for the general idea and terminology.

I didn't have reference to any other programmer's code when I was writing my STC forth so I had to come up with my own algorithm for implementing CREATE/DOES (and ;CODE). It is rather unique so I am including it below for comparison.

You will have to forgive the apparent messiness of the code but C64ASM codes zero-page instructions as absolute (3 byre) instructions so I had to create a lot of psuedo instructions to get the correct zero page instructions assembled.

Some notes of explanation (since they don't appear in this snippet of code):
All words are created in exactly the same manner, the name pointer is decremented and the name, a pointer to the current value of the code pointer (CP) and a pointer to the current value of the data pointer (DP) stored. This makes it easy to forget the word afterwards. Since this is all that is required to create a CODE word, the routine is called CODE rather than WORD.
LITERAL compiles the number on the data stack into the word being defined as a series of assembly language instructions.
SEMIS compiles the RTS instruction, sets the STATE to INTERPRETING and clears the CODEFLG.
ACOMMA stores the A register at the memory pointed to by CP and increments the CP.
Code:
;
; CREATE -      CREATES A WORD THAT PUSHES AN ADDRESS ON THE STACK
;               THE ADDRESS IS THE CURRENT VALUE OF THE DP
;
CREATE  JSR     CODE
.BYTE   LDAZ,   DP+1
        STA     STACK,X
        DEX
.BYTE   LDAZ,   DP
        STA     STACK,X
        DEX
        JSR     LITERAL
        JMP     SEMIS           ; RTS ISTRUCTION GETS OVERWRITTEN
                                ; IN CASE OF DOES> EXTENSION

;
; DOES> -       COMPILES ADDRESS OF DOES> INTO WORD BEING DEFINED
;
DOES    LDY     #_EDOES-1
_LOOP   LDA     _DOES,Y         ; COPY _DOES CODE TO DEFINED WORD
        STA     (CP),Y
        DEY
        BPL     _LOOP
        CLC                     ; CALCULATE ADDRESS FOLLOWING DOES>
.BYTE   LDAZ,   CP
        ADC     #_EDOES
.BYTE   STAZ,   TEMP            ; STORE THAT ADDRESS AT TEMP
.BYTE   LDAZ,   CP+1
        ADC     #0
.BYTE   STAZ,   TEMP+1
        LDY     #_LWER-1
.BYTE   LDAZ,   TEMP            ; COMPILE TEMP INTO _DOES
        STA     (CP),Y
        LDY     #_UPER-1
.BYTE   LDAZ,   TEMP+1
        STA     (CP),Y
.BYTE   LDAZ,   TEMP            ; UPDATE CP
.BYTE   STAZ,   CP
.BYTE   LDAZ,   TEMP+1
.BYTE   STAZ,   CP+1
        RTS
;
_DOES .BYTE LDAZ, CP
        BNE     _DOES1
.BYTE   DECZ,   CP+1            ; BACKUP CP AND
_DOES1 .BYTE DECZ, CP           ; REPLACE RTS INSTRUCTION WITH
        LDA     #$4C            ; JMP INSTRUCTION
        JSR     ACOMMA
        LDA     #0              ; JUMP TO WORD FOLLOWING _DOES
_LWER = * - _DOES
        JSR     ACOMMA
        LDA     #0
_UPER = * - _DOES
        JSR     ACOMMA
        RTS
_EDOES = * - _DOES

;
; DOESCD -   ( ;CODE ) AS FOR DOES> AND THEN
;                         SET STATE TO INTERPRET
;
DOESCD   JSR     DOES
        LDA   #0
   STA   STATE      ; SET STATE TO 0 (INTERPRET)
   STA   STATE+1
        RTS


Top
 Profile  
Reply with quote  
PostPosted: Mon Jan 26, 2015 6:43 pm 
Offline

Joined: Mon Jan 07, 2013 2:42 pm
Posts: 576
Location: Just outside Berlin, Germany
Wow, impressive, coming up with that yourself. One major difference seems to be that you're using the labels and a loop to compile the _DOES (which seems to be my (DOES>) ) and I'm getting the address from JSR and a generalized subroutine. Yours is faster -- do you use the same principle in other places?


Top
 Profile  
Reply with quote  
PostPosted: Tue Jan 27, 2015 3:21 am 
Offline

Joined: Mon Jan 26, 2015 6:19 am
Posts: 85
Yes, all the compiler words lay down assembly language instructions in situ. My aim was to get the fastest working forth possible. The above principle applies to words like CONSTANT, IF, ELSE, THEN, WHILE, REPEAT and FOR/NEXT (I took a leaf out of Frank Sergeant's pygmy forth (http://pygmy.utoh.org/pygmyforth.html) and didn't bother with the DO/LOOP constructs). String literals also use the same principle though you need to JMP over the string once its address has been pushed on the stack.

However, DOES and ;CODE seem to be the only words that don't involve a space penalty as compared to the indirect methods you use.


Top
 Profile  
Reply with quote  
PostPosted: Wed Feb 18, 2015 3:20 am 
Offline
User avatar

Joined: Sun Jun 30, 2013 10:26 pm
Posts: 1926
Location: Sacramento, CA, USA
scotws wrote:
... Do you have some mechanism to native-compile short words (so DROP is INX INX and not a jump or call)? At the moment, deciding which words to native compile in Tali is rather ad hoc ("looks short"). Once stuff is stable, I'll have to figure out something a bit more scientific based on a "acceptable percentage of overhead".


Sorry that I forgot to answer you sooner, Scot. I am writing a Forth for my 65m32 not for speed or utility, but for learning and shaking out my machine instruction set before putting a final seal on it. I know that I'm on to something good, because I always find myself fighting the urge to code high-level words as primitives, due to the almost inevitable conclusion that so many of them wind up being not just faster, but shorter as well.

In my unfinished [sigh] DTC Forth based on Dr. Brad's Camel Forth, NEXT is one machine instruction, and the following primitives are all one (or zero!) machine instructions (plus NEXT):
Code:
+ - 1+ 1- 2* >BODY @ ALIGN ALIGNED AND branch C@ CELL+ CELLS CHAR+ CHARS DROP DUP enter EXECUTE EXIT INVERT NEGATE NIP OR SWAP UNLOOP XOR [ ]

Dozens of my other primitives are only two or three machine instructions (plus NEXT), and I can imagine that I would be doing tons of in-lining in an STC system. In fact, (and this may bring some criticism down on me), I'm having trouble justifying spending any more of my limited spare time learning how to program in Forth, because programming in assembler is so much fun, even though I'm still hand-assembling everything :shock: . I am porting a version of Forth because the act of porting interests me, but I get this nagging feeling that actually programming something non-trivial in Forth will never feel "natural" to me, like programming in BASIC or C or assembler does. I wind up with something awkward like this, because "stackrobatics" don't come naturally to me (this doesn't quite work correctly, and I haven't figured it out yet):
Code:
: line                  \ plot solid line       ( 'x 'y --  )
                        \ Draw a solid line from x,y to 'x,'y
                        \ x and y are global variables, and update to 'x,'y
                        \   . means "delta "
                        \   ' means "updated value of "
                        \   ~ means "sign of delta " ... -1 if <0, +1 if >=0
                        \   | means "absolute value of delta "
  y @ -                 \ calculate .y          ( 'x .y )
  dup 0< 1 or swap      \          ~.y          ( 'x ~y .y )
  abs dup >r            \          |.y          ( 'x ~y |y )            ( R: |y )
  rot x @ -             \ calculate .x          ( ~y |y .x )
  dup 0< 1 or swap      \          ~.x          ( ~y |y ~x .x )
  abs                   \          |.x          ( ~y |y ~x |x )
  dup                   \ c is slope accum.     ( ~y |y ~x |x c )
  dup r> +              \ k is loop counter     ( ~y |y ~x |x c k )     ( R: )
  negate 1 swap do      \ main loop (           ( ~y |y ~x |x c )       ( R: 1 -k )
    plot                \   plot (x,y)
    i 0< if             \   is line finished? ( ( ~y |y ~x |x c )
      dup 0< if         \     n:  c < 0? (
        over + >r       \       y: ( c += |x    ( ~y |y ~x |x )         ( R: 1 'k 'c )
        3 pick y        \            y += ~y    ( ~y |y ~x |x ~y y )
      else              \          )
        3 pick - >r     \       n: ( c -= |y    ( ~y |y ~x |x )         ( R: 1 'k 'c )
        over x          \            x += ~x    ( ~y |y ~x |x ~x x )
      then              \          )
      +! r>             \       update x or y   ( ~y |y ~x |x 'c )      ( R: 1 'k )
    then                \   )
  loop                  \ )                     ( ~y |y ~x |x 'c )      ( R: )
  drop 2drop 2drop      \ delete temps          (  )
;                       \                       (  )


Mike B.

[Edit: Ah, I think I found something ... I should be initializing my slope accumulator to |dx|-|dy| ... not sure if that's all, but I will have to test it later.]


Last edited by barrym95838 on Thu Feb 19, 2015 4:19 pm, edited 1 time in total.

Top
 Profile  
Reply with quote  
PostPosted: Wed Feb 18, 2015 10:11 am 
Offline

Joined: Mon Jan 07, 2013 2:42 pm
Posts: 576
Location: Just outside Berlin, Germany
If it makes you feel better, I spent most of the last months with Forth with a feeling of low-level frustration, usually along the lines of "but why can't I just do X like in Python? What is wrong with these people?!" I've come to assume this is the normal way to learn Forth, which possibly requires a streak of masochism. But hey, I program assembler for fun :D .

No offence, but I had to laugh that you've picked "plot a solid line" for your Forth code, because this is the text-book example of something that Forth is horrible at. See Thinking Forth page 201, where four lines are drawn for a box:
Quote:
Although we’re using the stack to get the four arguments, the algorithm for drawing a box doesn’t lend itself to the nature of the stack.
This is used to introduce local variables, which seem to be something of a hack in Forth born out of necessity. Maybe a miniature text adventure or something else instead?

However, if I may, it also looks like you are programming "C in Forth": One big routine instead lots of little words that are one or two lines long at most. So for example, you could isolate the first parts of the code something like this:
Code:
: delta-point ( 'p p -- ~p |p) - dup 0< 1 or swap abs ;
\ ... more stuff ...
: line ( 'x 'y  -- )
    y @  delta-point
    \ ... stack glue ...
    x @  delta-point
I admit I don't understand the basic algorithm here ("0< 1 OR" looks strange because of the 1 OR), so maybe I haven't understood something quite right.

The idea as explained to me is that Forth has lots of words that do the actual work and the DUP and SWAP stuff between them is "stack glue code" that holds them together but is not really important. The words ideally go from low-level stuff to increasingly abstract concepts that use earlier words as building blocks. So the, uh, "gross visual layout" of a Forth program would be something like this
Quote:
: lowlevel-word1 ( --- ) blablabla ;
: lowlevel-word2 ( --- ) blablabla ;
: lowlevel-word3 ( --- ) blablabla ;
: higherlevel-word1 ( --- ) lowlevel-word1 lowlevel-word2 ;
: higherlevel-word2 ( --- ) lowlevel-word2 lowlevel-word3 ;
: higherlevel-word3 ( --- ) lowlevel-word3 lowlevel-word1 ;
: big-word1 ( --- ) higherlevel-word2 higherlevel-word3 ;
: big-word2 ( --- ) higherlevel-word1 higherlevel-word3 ;
: theword ( --- ) big-word1 big-word2 ;
This, of course, looks nothing like C or Python, and gives Forth a very distinct layout (and an almost perfect top-to-bottom flow of logic, I might add).

An example of what this looks like coded by somebody who actually knows what he is doing would be ther Eulex editor by David Vázquez Púa: https://github.com/davazp/eulex/blob/master/editor.fs I learned a lot from reading Púa's code there, though it's interesting he doesn't seem to have used CREATE/DOES> even once.


Top
 Profile  
Reply with quote  
PostPosted: Thu Feb 19, 2015 4:35 am 
Offline
User avatar

Joined: Sun Jun 30, 2013 10:26 pm
Posts: 1926
Location: Sacramento, CA, USA
Yeah, I'm sure that you're correct ... ~60-word definitions are not in the true spirit of Forth. I am going to try to debug and factor my line definition, and eventually start a fresh thread detailing my progress (to prevent further pollution of this thread).

Thanks for your insights, :)

Mike B.


Top
 Profile  
Reply with quote  
PostPosted: Thu Feb 19, 2015 9:20 am 
Offline

Joined: Mon Jan 26, 2015 6:19 am
Posts: 85
scotws wrote:
... Do you have some mechanism to native-compile short words (so DROP is INX INX and not a jump or call)?

My solution to that problem is to have a word called DROP, which in-lines INX INX as distinct from DROP which is a subroutine that does the same thing. The latter can be run when you are in interpret mode.

barrym95838 wrote:
I can imagine that I would be doing tons of in-lining in an STC system.

Just a word of caution here. Words that in-line are compiler words and won't work for you when you are in interpret mode.

You could always make such words "state smart" meaning that they will in-line code when you are in compiler mode or perform the action when you are in interpreter mode. The problem is that the final run time behaviour of such words is unpredictable when you POSTPONE (or [COMPILE]) such words.

I have no choice but to make the string literal ( " ) state smart since I need it to open files when in interpreter mode but I must be careful about POSTPONEing this word.


barrym95838 wrote:
I am porting a version of Forth because the act of porting interests me, but I get this nagging feeling that actually programming something non-trivial in Forth will never feel "natural" to me, like programming in BASIC or C or assembler does. I wind up with something awkward like this, because "stackrobatics" don't come naturally to me.

i have successfully ported a number of C functions to Forth (eg MALLOC as defined in Kernighan and Richie's ANSI C) without problems. With plenty of factoring, stackrobatics is not too difficult.

My only problem is that even though I include plenty of stack diagrams in the comments, I invariably find that when I look at the code a few months later, I find myself asking, "what is this ****?" :wink:


Top
 Profile  
Reply with quote  
PostPosted: Thu Feb 19, 2015 1:21 pm 
Offline

Joined: Wed Jan 08, 2014 3:31 pm
Posts: 563
Because the arguments are already on the stack, a function call in Forth is really cheap compared to a language like C which builds a call frame on the stack. That encourages the factoring of code into small testable units.

C compilers do put locals on the stack or in registers, so they can optimize the call linkage, but only for functions that don't call other functions. Once you call another function those registers have to be saved which incurs the call frame penalty. Of course Forth is low level compared to more modern languages, and stack manipulation isn't as natural as local variables, but its design has appeal.

theGSman wrote:
i have successfully ported a number of C functions to Forth (eg MALLOC as defined in Kernighan and Richie's ANSI C) without problems. With plenty of factoring, stackrobatics is not too difficult.

My only problem is that even though I include plenty of stack diagrams in the comments, I invariably find that when I look at the code a few months later, I find myself asking, "what is this ****?" :wink:


I'd love to see your malloc implementation. I usually learn a thing or two when I read someone else's code. I often have that "who wrote this" when I look at any code I've written more than a few months back.


Top
 Profile  
Reply with quote  
Display posts from previous:  Sort by  
Post new topic Reply to topic  [ 25 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: