• Re: Parsing timestamps?

    From B. Pym@Nobody447095@here-nor-there.org to comp.lang.forth on Mon Jun 9 12:34:18 2025
    From Newsgroup: comp.lang.forth

    B. Pym wrote:

    mhx wrote:

    On Sun, 6 Oct 2024 7:51:31 +0000, dxf wrote:

    Is there an easier way of doing this? End goal is a double number representing centi-secs.


    empty decimal

    : SPLIT ( a u c -- a2 u2 a3 u3 ) >r 2dup r> scan 2swap 2 pick - ;
    : >INT ( adr len -- u ) 0 0 2swap >number 2drop drop ;

    : /T ( a u -- $hour $min $sec )
    2 0 do [char] : split 2swap dup if 1 /string then loop
    2 0 do dup 0= if 2rot 2rot then loop ;

    : .T 2swap 2rot cr >int . ." hr " >int . ." min " >int . ." sec " ;

    s" 1:2:3" /t .t
    s" 02:03" /t .t
    s" 03" /t .t
    s" 23:59:59" /t .t
    s" 0:00:03" /t .t

    Why don't you use the fact that >NUMBER returns the given
    string starting with the first unconverted character?
    SPLIT should be redundant.

    -marcel

    : CHAR-NUMERIC? 48 58 WITHIN ;
    : SKIP-NON-NUMERIC ( adr u -- adr2 u2)
    BEGIN
    DUP IF OVER C@ CHAR-NUMERIC? NOT ELSE 0 THEN
    WHILE
    1 /STRING
    REPEAT ;

    : SCAN-NEXT-NUMBER ( n adr len -- n2 adr2 len2)
    2>R 60 * 0. 2R> >NUMBER
    2>R D>S + 2R> ;

    : PARSE-TIME ( adr len -- seconds)
    0 -ROT
    BEGIN
    SKIP-NON-NUMERIC
    DUP
    WHILE
    SCAN-NEXT-NUMBER
    REPEAT
    2DROP ;

    S" hello 1::36 world" PARSE-TIME CR .
    96 ok


    Using regular expressions in SP-Forth.

    ( pcre.dll must be in your path.)
    REQUIRE PcreMatch ~ac/lib/string/regexp.f \ PCRE wrapper
    REQUIRE S>NUM ~nn\lib\s2num.f \ String to number


    VARIABLE HOW-MANY-SECONDS
    : INCREMENT-SECONDS ( n adr --)
    SWAP OVER @ 60 * + SWAP ! ;

    : PARSE-TIME ( adr len -- seconds)
    0 HOW-MANY-SECONDS !
    BEGIN
    S" \d+(.*)" PcreGetMatch
    WHILE
    S>NUM HOW-MANY-SECONDS INCREMENT-SECONDS
    REPEAT
    HOW-MANY-SECONDS @ ;

    S" hello 20::_:55 world" PARSE-TIME CR .

    1255


    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Mon Jun 9 15:21:52 2025
    From Newsgroup: comp.lang.forth

    On 08-06-2025 04:38, dxf wrote:
    On 8/06/2025 3:07 am, LIT wrote:
    My solution is rather straightforward:

    1 VARIABLE C6
    1 VARIABLE C1

    : TIMESTRSCAN ( addr count -- d )
    t;R >R 0 0 R> R>
     OVER + 1-
     DO
       I C@ DUP 58 =
       IF
         DROP
         C6 @ 60 * C6 !
         1 C1 !
       ELSE
         48 - C1 @ * C6 @ M* D+
         10 C1 !
       THEN
     -1 +LOOP
     1 C6 !  1 C1 !
    ;

    First of all: are you an 8-bit hobbyist? I mean, you can convert 32-bit
    values close to 600,000 hours - that's a whopping 68 years - before you overflow this thing. Signed, that is.

    Second, stamp out the variables! You use two globals for this trivial
    routine. This does the same thing:

    : timescan
    over swap chars + >r 0 tuck begin
    over r@ <
    while
    over c@ [char] : =
    if rot + 60 * swap 0 else 10 * over c@ [char] 0 - + then
    swap char+ swap
    repeat r> drop nip +
    ;

    And the beauty of CHAR is - less magic numbers in your code. But even if
    you are dedicated to using a double word accumulator, you won't need
    those variables:

    : dtimescan
    over swap chars + >r >r 0. r> 0 begin
    over r@ <
    while
    over c@ [char] : =
    if
    swap >r s>d d+ 60 1 m*/ r> 0
    else
    10 * over c@ [char] 0 - +
    then
    swap char+ swap
    repeat r> drop nip s>d d+
    ;


    Now - did I win anything? Maybe a T-shirt "May the Forth be with you"?

    Virtue is its own reward.

    Hans Bezemer

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Mon Jun 9 13:34:51 2025
    From Newsgroup: comp.lang.forth

    This does the same thing:

    Indeed - "this does the same thing"
    introducing plenty of stack noise.
    That's why I preferred to use two
    variables.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Mon Jun 9 21:31:00 2025
    From Newsgroup: comp.lang.forth

    On 09-06-2025 15:34, LIT wrote:
    This does the same thing:

    Indeed - "this does the same thing"
    introducing plenty of stack noise.
    That's why I preferred to use two
    variables.

    --

    If you introduce variables for every triviality, the noise becomes
    deafening very quickly. Especially if you combine it with a lacking
    algorithm.

    All you need to know about mine:

    <general accu><addr><local accu>

    The rest fills itself in. But sure - if you can't write Forth, using
    massive amounts of variables is the way to go. Cheers!

    Hans Bezemer
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Mon Jun 9 20:00:09 2025
    From Newsgroup: comp.lang.forth

    Mr. Fifo - self-proclaimed "Mark Twain of Forth"
    - has no idea, that writing Forth code doesn't
    mean to move bytes around "Back and Forth"
    (where did I see that? Let's see... :D ).

    Stack jugglery means wasting CPU cycles for
    moving the bytes around - it's contrproductive.
    Variables have been invented to be used. They're
    useful, if you didn't notice, or if they didn't
    tell you that in your college, or wherever.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Mon Jun 9 23:40:28 2025
    From Newsgroup: comp.lang.forth

    On 09-06-2025 22:00, LIT wrote:
    Mr. Fifo - self-proclaimed "Mark Twain of Forth"
    - has no idea, that writing Forth code doesn't
    mean to move bytes around "Back and Forth"
    (where did I see that? Let's see... :D ).

    Stack jugglery means wasting CPU cycles for
    moving the bytes around - it's contrproductive.
    Variables have been invented to be used. They're
    useful, if you didn't notice, or if they didn't
    tell you that in your college, or wherever.

    First, a stack has been invented to be used as well. And a canonical
    Forth program uses the stack. Tut mir Leid. If you want to use local variables, there are plenty of languages that use that stuff. Like
    Python, the language of champions.

    Second, there are CPUs that are stack oriented - and using variables
    should be wasteful in that case. There are also plenty of CPUs that have
    a stack, like Z80, 8080 and friends. Sorry to say, but using ANY
    instruction burns CPU cycles. There is no way around that.

    Third, any statement must come with proof. And in this case that means extended benchmarking. I can tell you beforehand that I've never seen significant differences between locals and stack. I'm sorry to say that
    - but it's true.

    Finally, you have to know that good software comes with MANY qualities,
    speed being only one of them. If I have to choose between correct and
    fast, there has to be a very convincing argument for the speed
    requirement. They didn't tell you that in your college? Oh dear. I'm so
    sorry for you! You must have had a miserable life.

    Hans Bezemer

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Tue Jun 10 12:31:51 2025
    From Newsgroup: comp.lang.forth

    On 10/06/2025 6:00 am, LIT wrote:
    ...
    Stack jugglery means wasting CPU cycles for
    moving the bytes around - it's contrproductive.
    Variables have been invented to be used. They're
    useful, if you didn't notice, or if they didn't
    tell you that in your college, or wherever.

    Forth uses variables in the global sense and this works well.
    Variables at the word level is often an indication something is
    wrong. Locals users rarely justify on grounds of performance as
    experience over the years has shown time and again well-written
    stack code is both shorter and faster. The temptation is to
    write one routine that does it all and this is where variables
    and 'stack juggling' can sneak in. OTOH some implementations
    are just neater and its a matter of finding them!

    : HMS>SEC ( s m h -- ud ) 3600 um* 2swap 60 * + 0 d+ ;

    \ Parse HH:MM:SS or free-form ref: sjack
    : >HMS ( a u -- sec min hr )
    2>r 0 0 0 2r> begin
    /int 5 -roll rot drop dup while [char] : ?skip
    repeat 2drop ;

    \ Parse HMS string returning #csecs
    : /HMS ( a u -- ud ) >hms hms>sec 100 mu* ;


    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From mhx@mhx@iae.nl (mhx) to comp.lang.forth on Tue Jun 10 07:32:51 2025
    From Newsgroup: comp.lang.forth

    On Tue, 10 Jun 2025 2:31:51 +0000, dxf wrote:
    [..]
    OTOH some implementations
    are just neater and its a matter of finding them!

    [..]
    2>r 0 0 0 2r> begin
    /int 5 -roll rot drop dup while [char] : ?skip
    repeat 2drop ;
    [..]

    I don't get if you are joking or not.

    -marcel
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Tue Jun 10 18:30:17 2025
    From Newsgroup: comp.lang.forth

    On 10/06/2025 5:32 pm, mhx wrote:
    On Tue, 10 Jun 2025 2:31:51 +0000, dxf wrote:
    [..]
    OTOH some implementations
    are just neater and its a matter of finding them!

    [..]
      2>r  0 0 0  2r>  begin
        /int  5 -roll  rot drop  dup while  [char] : ?skip
      repeat 2drop ;
    [..]

    I don't get if you are joking or not.

    Dead serious. What's the joke?


    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From B. Pym@Nobody447095@here-nor-there.org to comp.lang.forth on Tue Jun 10 09:18:33 2025
    From Newsgroup: comp.lang.forth

    B. Pym wrote:

    mhx wrote:

    On Sun, 6 Oct 2024 7:51:31 +0000, dxf wrote:

    Is there an easier way of doing this? End goal is a double number representing centi-secs.


    empty decimal

    : SPLIT ( a u c -- a2 u2 a3 u3 ) >r 2dup r> scan 2swap 2 pick - ;
    : >INT ( adr len -- u ) 0 0 2swap >number 2drop drop ;

    : /T ( a u -- $hour $min $sec )
    2 0 do [char] : split 2swap dup if 1 /string then loop
    2 0 do dup 0= if 2rot 2rot then loop ;

    : .T 2swap 2rot cr >int . ." hr " >int . ." min " >int . ." sec " ;

    s" 1:2:3" /t .t
    s" 02:03" /t .t
    s" 03" /t .t
    s" 23:59:59" /t .t
    s" 0:00:03" /t .t

    Why don't you use the fact that >NUMBER returns the given
    string starting with the first unconverted character?
    SPLIT should be redundant.

    -marcel

    : CHAR-NUMERIC? 48 58 WITHIN ;
    : SKIP-NON-NUMERIC ( adr u -- adr2 u2)
    BEGIN
    DUP IF OVER C@ CHAR-NUMERIC? NOT ELSE 0 THEN
    WHILE
    1 /STRING
    REPEAT ;

    : SCAN-NEXT-NUMBER ( n adr len -- n2 adr2 len2)
    2>R 60 * 0. 2R> >NUMBER
    2>R D>S + 2R> ;

    : PARSE-TIME ( adr len -- seconds)
    0 -ROT
    BEGIN
    SKIP-NON-NUMERIC
    DUP
    WHILE
    SCAN-NEXT-NUMBER
    REPEAT
    2DROP ;

    S" hello 1::36 world" PARSE-TIME CR .
    96 ok


    : SCAN-NUMBER-OR-SKIP ( n adr len -- n' adr' len')
    DUP >R
    0 0 2SWAP >NUMBER
    DUP R> =
    IF 2SWAP 2DROP 1 /STRING
    ELSE
    2>R D>S SWAP 60 * + 2R>
    THEN ;

    : PARSE-TIME ( adr len -- seconds)
    0 -ROT
    BEGIN
    DUP
    WHILE
    SCAN-NUMBER-OR-SKIP
    REPEAT
    2DROP ;

    S" hi 5 or 1 is 44 ho " PARSE-TIME CR .
    18104


    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Tue Jun 10 09:52:32 2025
    From Newsgroup: comp.lang.forth

    Mr. Fifo - self-proclaimed "Mark Twain of Forth"
    - has no idea, that writing Forth code doesn't
    mean to move bytes around "Back and Forth"
    (where did I see that? Let's see... :D ).

    Stack jugglery means wasting CPU cycles for
    moving the bytes around - it's contrproductive.
    Variables have been invented to be used. They're
    useful, if you didn't notice, or if they didn't
    tell you that in your college, or wherever.

    First, a stack has been invented to be used as well.

    ..which doesn't deny use of variables where it's useful.

    And a canonical
    Forth program uses the stack. Tut mir Leid.

    You're sorry that you 'have' (IYO) to use the stack
    not quite senseful way? They force you to do so?
    Poor you.

    If you want to use local variables, there are plenty
    of languages that use that stuff. Like Python, the
    language of champions.

    Contact me with your "recommendation" again when you
    become appointed of some kind of 'authority' who'll
    decide, who should use what. Until then - I'll use
    whatever language I'll decide to use at the moment.

    Second, there are CPUs that are stack oriented - and using variables
    should be wasteful in that case. There are also plenty of CPUs that have
    a stack, like Z80, 8080 and friends. Sorry to say, but using ANY
    instruction burns CPU cycles. There is no way around that.

    Yes, indeed - these CPUs have a stack, and what you've
    presented is pointless stack jugglery. We may 'burn CPU
    cycles' to do something useful - or, following you (if
    anyone would be keen, which I doubt) we could use that
    stack for pointless moving the bytes "Back and Forth".

    Third, any statement must come with proof. And in this case that means extended benchmarking. I can tell you beforehand that I've never seen significant differences between locals and stack. I'm sorry to say that
    - but it's true.

    Oh, really? That speaks in favor of the most clean solution.

    Finally, you have to know that good software comes with MANY qualities,
    speed being only one of them. If I have to choose between correct and
    fast, there has to be a very convincing argument for the speed
    requirement. They didn't tell you that in your college? Oh dear. I'm so
    sorry for you! You must have had a miserable life.

    Yes, software comes with many qualities - and one of them,
    which you didn't mention (maybe you have no clue), is
    clarity of the code. The code filled with strings of that
    DUPs, SWAPs and ROTs not only works inefficiently, but also
    rather quickly becomes unreadable. And then serves as
    another example of 'typical write-only Forth code'.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Tue Jun 10 10:10:33 2025
    From Newsgroup: comp.lang.forth

    Stack jugglery means wasting CPU cycles for
    moving the bytes around - it's contrproductive.
    Variables have been invented to be used. They're
    useful, if you didn't notice, or if they didn't
    tell you that in your college, or wherever.

    Forth uses variables in the global sense and this works well.
    Variables at the word level is often an indication something is
    wrong. Locals users rarely justify on grounds of performance as
    experience over the years has shown time and again well-written
    stack code is both shorter and faster.

    Maybe, but:

    - it had to be well-written

    - at some point (I mean after 'critical' amount of ROTs, DUPs
    and SWAPs has been reached) it becomes unreadable - and after
    longer time unmanageable, if you'd like to modify it later.
    Or at least difficult to manage

    What I learned is to use these stack-related words to
    set the bytes in proper order - but to avoid the constant
    threshing bytes at the stack, as counterproductive. What is
    the result of ROTs, DUPs and SWAPs? The bytes in different
    order (and probably their count may vary). Nothing more.
    The CPU time taken for all that is wasted time. Your program
    did nothing really useful.
    So although I'm of course not opposed to use these words
    when needed, the key is to recognize 'do I really need to
    do it this way?'. And when cleaner solution can be applied
    - like using a variable or two instead - then the kind
    of 'ideological stance' (like "the canonical Forth programs
    require...") doesn't make much sense.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Tue Jun 10 20:32:58 2025
    From Newsgroup: comp.lang.forth

    On 10/06/2025 7:18 pm, B. Pym wrote:
    ...
    : SCAN-NUMBER-OR-SKIP ( n adr len -- n' adr' len')
    DUP >R
    0 0 2SWAP >NUMBER
    DUP R> =
    IF 2SWAP 2DROP 1 /STRING
    ELSE
    2>R D>S SWAP 60 * + 2R>
    THEN ;

    0 0 2SWAP >NUMBER invariably crops up so I have it in the kernel as
    (NUMBER). 2SWAP 2DROP is another and becomes 2NIP. Forth would
    have one define the same thing over and over. Do it once and be done
    with it IMO.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Tue Jun 10 10:43:32 2025
    From Newsgroup: comp.lang.forth

    : SCAN-NUMBER-OR-SKIP ( n adr len -- n' adr' len')
    DUP >R
    0 0 2SWAP >NUMBER
    DUP R> =
    IF 2SWAP 2DROP 1 /STRING
    ELSE
    2>R D>S SWAP 60 * + 2R>
    THEN ;

    0 0 2SWAP >NUMBER invariably crops up so I have it in the kernel as (NUMBER). 2SWAP 2DROP is another and becomes 2NIP. Forth would
    have one define the same thing over and over. Do it once and be done
    with it IMO.

    So now you see: one can either use variable to
    make the solution cleaner - or one can create new word(s).
    Either way - some new names are added to the vocabulary.
    Why the use of variable, instead of new words,
    should be perceived of 'inferior'? Variable is a word too.

    This reminds me somewhat that talk about 'using Lynx
    browser in every condition no-matter-what'. Even, if
    it makes me 'fighting the WWW' instead of just getting
    required job done and switching to more pleasant things.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From albert@albert@spenarnc.xs4all.nl to comp.lang.forth on Tue Jun 10 12:48:32 2025
    From Newsgroup: comp.lang.forth

    In article <6ea4ccd1cb6ae8c828144444fe51fea9@www.novabbs.com>,
    LIT <zbigniew2011@gmail.com> wrote:
    Mr. Fifo - self-proclaimed "Mark Twain of Forth"
    - has no idea, that writing Forth code doesn't
    mean to move bytes around "Back and Forth"
    (where did I see that? Let's see... :D ).

    Stack jugglery means wasting CPU cycles for
    moving the bytes around - it's contrproductive.
    Variables have been invented to be used. They're
    useful, if you didn't notice, or if they didn't
    tell you that in your college, or wherever.

    Have you looked at my Roman digits?
    There are two stack words DUP used in whole, meaning that you
    use a stack item twice.
    That is in a word `_row that isn't even essential to the whole
    exercise.
    The stack shuffling is probably a sign of bad code.

    Groetjes Albert


    --
    --
    Temu exploits Christians: (Disclaimer, only 10 apostles)
    Last Supper Acrylic Suncatcher - 15Cm Round Stained Glass- Style Wall
    Art For Home, Office And Garden Decor - Perfect For Windows, Bars,
    And Gifts For Friends Family And Colleagues.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Tue Jun 10 11:08:12 2025
    From Newsgroup: comp.lang.forth

    Stack jugglery means wasting CPU cycles for
    moving the bytes around - it's contrproductive.
    Variables have been invented to be used. They're
    useful, if you didn't notice, or if they didn't
    tell you that in your college, or wherever.

    Have you looked at my Roman digits?
    There are two stack words DUP used in whole, meaning that you
    use a stack item twice.
    That is in a word `_row that isn't even essential to the whole
    exercise.

    Not bad indeed.

    The stack shuffling is probably a sign of bad code.

    Yes, I agree - so although I don't 'detest'
    these words (nor moving bytes around when needed),
    when I see too many of them accumulating, I simply
    look for a cleaner, more comprehensible and manageable
    solution.
    '+' does something useful. It produces a sum.
    'SWAP' merely changes the order of two subsequent
    bytes.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Stephen Pelc@stephen@vfxforth.com to comp.lang.forth on Tue Jun 10 12:07:39 2025
    From Newsgroup: comp.lang.forth

    On 9 Jun 2025 at 23:40:28 CEST, "Hans Bezemer" <the.beez.speaks@gmail.com> wrote:

    Third, any statement must come with proof. And in this case that means extended benchmarking. I can tell you beforehand that I've never seen significant differences between locals and stack. I'm sorry to say that
    - but it's true.

    I suspect tthat the lack difference comes from the underlying Forth system.
    For threaded code systems, the threading costs a lot of performance. In
    our tests, subroutine threaded code on 32 bit systems averages 2.2
    times the performance of direct threaded code for 68k class CPUs.

    Once full native code compilation and optimisation is turned on, you
    can get surprising results. At one stage we (MPE) de-localled a
    substantial portion of the PowerNet TCP/IP stack - all in high-level
    Forth. For the modified code, size decreased by 25% and performance
    increased by 50%.

    Stephen
    --
    Stephen Pelc, stephen@vfxforth.com
    Wodni & Pelc GmbH
    Vienna, Austria
    Tel: +44 (0)7803 903612, +34 649 662 974 http://www.vfxforth.com/downloads/VfxCommunity/
    free VFX Forth downloads
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Tue Jun 10 14:29:01 2025
    From Newsgroup: comp.lang.forth

    On 10-06-2025 12:48, albert@spenarnc.xs4all.nl wrote:
    In article <6ea4ccd1cb6ae8c828144444fe51fea9@www.novabbs.com>,
    LIT <zbigniew2011@gmail.com> wrote:
    Mr. Fifo - self-proclaimed "Mark Twain of Forth"
    - has no idea, that writing Forth code doesn't
    mean to move bytes around "Back and Forth"
    (where did I see that? Let's see... :D ).

    Stack jugglery means wasting CPU cycles for
    moving the bytes around - it's contrproductive.
    Variables have been invented to be used. They're
    useful, if you didn't notice, or if they didn't
    tell you that in your college, or wherever.

    Have you looked at my Roman digits?
    There are two stack words DUP used in whole, meaning that you
    use a stack item twice.
    That is in a word `_row that isn't even essential to the whole
    exercise.
    The stack shuffling is probably a sign of bad code.

    Well, that's exactly the point. If you can't write Forth, you'll end up juggling stuff around - and yes, that results in unmaintainable Forth.

    But IMHO it says more about the programmer that experiences this
    phenomenon rather than the practice of using a stack.

    The largest programs I have - and have been maintaining for decades by
    the way - are perfectly readable (at least I can). They've extended in
    both features as well as corrective maintenance.

    I agree that excessive stack juggling is a sign of bad code - and I've
    thrown out the odd library member if I'm unable to make head or tails
    from it. Because trying to maintain such code, let's say it only gets worse.

    How to combat excessive stack juggling - I guess every programmer has
    his tricks. I use one-liners and program analysis, but I'm open to hear
    about other strategies. I'd say it's an interesting item.

    Hans Bezemer



    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Tue Jun 10 14:44:53 2025
    From Newsgroup: comp.lang.forth

    On 10-06-2025 13:08, LIT wrote:
    Stack jugglery means wasting CPU cycles for
    moving the bytes around - it's contrproductive.
    Variables have been invented to be used. They're
    useful, if you didn't notice, or if they didn't
    tell you that in your college, or wherever.

    '+' does something useful. It produces a sum.
    'SWAP' merely changes the order of two subsequent
    bytes.

    Interesting. So you claim that instructions like:

    LD HL, (23672)
    PUSH HL
    POP HL

    Have no use, since they are just "moving bytes around"? Which means that
    every single assignment (without additional calculation) is "useless".
    Let's apply that rule to your own program:

    : TIMESTRSCAN ( addr count -- d )
    0 0
    + 1-
    DO
    I 58 =
    IF
    *
    ELSE
    48 - * M* D+
    10
    THEN
    -1 +LOOP
    1 1
    ;

    Roughly 25 from the 55 odd words concerned. Less than half. That's all
    that's left from your own program. And I'm still quite nice, because technically, throwing magic numbers on the stack can be considered
    "moving bytes around".

    Now - how am I doing? Using the very same rules, about 25 of the 40 odd
    words remain.. So..

    : timescan
    chars + 0 begin
    <
    while
    c@ [char] : =
    if + 60 * 0 else 10 * c@ [char] 0 - + then
    repeat +
    ;

    Hans Bezemer
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Tue Jun 10 12:48:09 2025
    From Newsgroup: comp.lang.forth

    Mr. Fifo - self-proclaimed "Mark Twain of Forth"
    - has no idea, that writing Forth code doesn't
    mean to move bytes around "Back and Forth"
    (where did I see that? Let's see... :D ).

    Stack jugglery means wasting CPU cycles for
    moving the bytes around - it's contrproductive.
    Variables have been invented to be used. They're
    useful, if you didn't notice, or if they didn't
    tell you that in your college, or wherever.

    Have you looked at my Roman digits?
    There are two stack words DUP used in whole, meaning that you
    use a stack item twice.
    That is in a word `_row that isn't even essential to the whole
    exercise.
    The stack shuffling is probably a sign of bad code.

    Well, that's exactly the point. If you can't write Forth, you'll end up juggling stuff around - and yes, that results in unmaintainable Forth.

    Like this example:

    : timescan
    over swap chars + >r 0 tuck begin
    over r@ <
    while
    over c@ [char] : =
    if rot + 60 * swap 0 else 10 * over c@ [char] 0 - + then
    swap char+ swap
    repeat r> drop nip +
    ;

    15 "byte shufflers" within single word,
    and even 8 of them within a loop(!). So
    byte threshing over and over again.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Tue Jun 10 12:56:27 2025
    From Newsgroup: comp.lang.forth

    Stack jugglery means wasting CPU cycles for
    moving the bytes around - it's contrproductive.
    Variables have been invented to be used. They're
    useful, if you didn't notice, or if they didn't
    tell you that in your college, or wherever.

    '+' does something useful. It produces a sum.
    'SWAP' merely changes the order of two subsequent
    bytes.

    Interesting. So you claim that instructions like:

    LD HL, (23672)
    PUSH HL
    POP HL

    Have no use, since they are just "moving bytes around"? Which means [..]

    Which DOESN'T 'mean', because I DIDN'T write anywhere
    that the instructions used for moving bytes are useless;
    what I wrote was that YOUR way of 'overloading' Forth
    words with byte moving stuff (in the strange belief that
    it is 'canonical way') doesn't make much sense.

    Since you aren't able to read WITH UNDERSTANDING - or
    maybe you're twisting my words on purpose, which means
    you're trolling - we better end such 'discussion', because
    it's as pointless as creating the words that half of their
    execution time just move the bytes "Back and Forth".

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Tue Jun 10 15:12:52 2025
    From Newsgroup: comp.lang.forth

    On 10-06-2025 11:52, LIT wrote:
    First, a stack has been invented to be used as well.

    ..which doesn't deny use of variables where it's useful.

    ..which doesn't deny use of a stack where it's useful.

    You're sorry that you 'have' (IYO) to use the stack
    not quite senseful way? They force you to do so?
    Poor you.

    You don't fart (loudly) in the middle of a wedding.

    Contact me with your "recommendation" again when you
    become appointed of some kind of 'authority' who'll
    decide, who should use what. Until then - I'll use
    whatever language I'll decide to use at the moment.

    That in itself would be a logical fallacy ("call to authority"). That
    you're serious considering this is committing this very logical fallacy.
    Given that you seem to be collecting logical fallacies, that's not much
    of a surprise.

    You have to start learning that someone not agreeing with you leaves you
    two options: 1. Simply ignoring it, or: 2. Debating the issue in a
    civilized manner.

    I'm not saying you can't hammer a screw into the wall, I'm just saying
    it's not the best way to do it. The language was not designed for that.
    There are plenty of sources concerning the design objectives and
    suggested usage of the language. I'm particularly fond of "Thinking
    Forth". You want some quotes from that volume?

    Yes, indeed - these CPUs have a stack, and what you've
    presented is pointless stack jugglery. We may 'burn CPU
    cycles' to do something useful - or, following you (if
    anyone would be keen, which I doubt) we could use that
    stack for pointless moving the bytes "Back and Forth".

    Of course there are ways to XOR your way around the stack without ever
    using a SWAP, e.g. "OVER XOR DUP >R XOR DUP R> XOR". I don't think it
    will enhance your Forth experience, though. Although it may make you
    feel a little better.

    Oh, really? That speaks in favor of the most clean solution.

    According to Locke, "clean" is a secondary quality - AKA, in the eye of
    the beholder. "Canonical", since it refers to a standard, is not.

    Yes, software comes with many qualities - and one of them,
    which you didn't mention (maybe you have no clue), is
    clarity of the code. The code filled with strings of that
    DUPs, SWAPs and ROTs not only works inefficiently, but also
    rather quickly becomes unreadable. And then serves as
    another example of 'typical write-only Forth code'.

    "Clarity" must be codified, otherwise it is (like "clean") a secondary
    quality - and hence open to endless debate. Are strawberry milkshakes
    *really* tastier than chocolate ones?

    It must be clear by now that stack instructions are *not* the cause of
    bad performance (next time, do your homework before posting stupid
    things). So, this straw does not provide any hold.

    As I stated, I have no trouble to maintain multi-KLOC codebases in Forth
    for decades on end. That you obviously cannot, may illustrate your capabilities as a Forth programmer, though. There is no shame in that.
    We all had to start there. The best antidote though, is to learn. Even
    winning a debate doesn't improve your programming skills a shred.

    Hans Bezemer


    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Tue Jun 10 14:06:37 2025
    From Newsgroup: comp.lang.forth

    Stephen Pelc <stephen@vfxforth.com> writes:
    Once full native code compilation and optimisation is turned on, you
    can get surprising results. At one stage we (MPE) de-localled a
    substantial portion of the PowerNet TCP/IP stack - all in high-level
    Forth. For the modified code, size decreased by 25% and performance
    increased by 50%.

    This demonstrates that you implemented locals less efficiently than
    stack manipulation, not that locals are inevitably slow. For more
    information, see

    @InProceedings{ertl22-locals,
    author = {M. Anton Ertl},
    title = {Are Locals Inevitably Slow?},
    crossref = {euroforth22},
    pages = {48--49},
    url = {http://www.euroforth.org/ef22/papers/ertl-locals.pdf},
    url-slides = {http://www.euroforth.org/ef22/papers/ertl-locals-slides.pdf},
    video = {https://www.youtube.com/watch?v=tPjSKetEJn0},
    OPTnote = {presentation slides},
    abstract = {Code quality of locals on two code examples on
    various systems}
    }

    @Proceedings{euroforth22,
    title = {38th EuroForth Conference},
    booktitle = {38th EuroForth Conference},
    year = {2022},
    key = {EuroForth'22},
    url = {http://www.euroforth.org/ef22/papers/proceedings.pdf}
    }

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2023 proceedings: http://www.euroforth.org/ef23/papers/
    EuroForth 2024 proceedings: http://www.euroforth.org/ef24/papers/
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Tue Jun 10 16:28:12 2025
    From Newsgroup: comp.lang.forth

    On 10-06-2025 14:56, LIT wrote:
    Which DOESN'T 'mean', because I DIDN'T write anywhere
    that the instructions used for moving bytes are useless;

    1. "[He] - has no idea, that writing Forth code doesn't mean to move
    bytes around."

    2. "Stack jugglery means wasting CPU cycles for moving the bytes around
    - it's contrproductive."

    3. "Yes, indeed - these CPUs have a stack, and what you've presented is pointless stack jugglery. We may 'burn CPU cycles' to do something
    useful - or, following you (if anyone would be keen, which I doubt) we
    could use that stack for pointless moving the bytes back and forth."

    4. "What I learned is to use these stack-related words to set the bytes
    in proper order - but to avoid the constant threshing bytes at the
    stack, as counterproductive."

    That's a lot of literal quotes for "NOWHERE".

    Since you aren't able to read WITH UNDERSTANDING - or
    maybe you're twisting my words on purpose, which means
    you're trolling - we better end such 'discussion',

    As I say my wife often enough: "Honey, I'm not a mind reader. Say what
    you mean and mean what you say."

    because it's as pointless as creating the words that half of their
    execution time just move the bytes back and forth.

    This is quote number 5. You never learn, do you? You rather be the mean
    girl on the schoolyard, who thinks her opinion of me bears any
    significance. There are 8 billion people on the world, honey. I've got
    neither the time nor the energy to bother with every ones opinion on me.

    Hans Bezemer


    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Tue Jun 10 16:48:16 2025
    From Newsgroup: comp.lang.forth

    On 10-06-2025 14:48, LIT wrote:
    Like this example:

    : timescan
      over swap chars + >r 0 tuck begin
        over r@ <
      while
        over c@ [char] : =
        if rot + 60 * swap 0 else 10 * over c@ [char] 0 - + then
        swap char+ swap
      repeat r> drop nip +
    ;

    15 "byte shufflers" within single word,
    and even 8 of them within a loop(!). So
    byte threshing over and over again.

    1. I consider this a minor word - but worth to be adopted as a library
    member. That's why I dropped the possibility to factor out inner words.
    I might do so when that code is shared with another word;

    2. Note I ripped 30 "byte shufflers" from your code. So 15 is not that bad.

    3. As Mr. Pelc remarked, stack operators are faster. So far, my own BMs haven't shown a significant difference - but I consider "variableless"
    code to be cleaner - and it is (without contest) canonical.

    4. Note that the order of the data elements doesn't change, unless
    they're updated. Setting up that stack diagram takes two to four stack operations. Cleaning up roughly the same. So half is executed only once.

    Of the remaining seven (not eight), one is used to test the terminating condition. One is used to get and test for a colon. Two for updating a pointer. That leaves three, divided between two branches of an "IF"
    statement.

    You, on the other hand, have six (!) variable accesses and two
    additional stack operators (which BTW, could have been avoided if you
    knew how to write Forth).

    Hans Bezemer

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Tue Jun 10 16:56:55 2025
    From Newsgroup: comp.lang.forth

    On 09-06-2025 22:00, LIT wrote:
    Mr. Fifo - self-proclaimed "Mark Twain of Forth"
    - has no idea, that writing Forth code doesn't
    mean to move bytes around "Back and Forth"
    (where did I see that? Let's see... :D ).

    I wondered where this came from - but obviously merely mentioning a
    quote attributed to Mark Twain equates to "proclaiming to be Mark
    Twain". I'm sorry if the meaning of the quote itself eludes your limited capacity - but I'm afraid, it is what it is.

    As one great philosopher once exclaimed: "Since you aren't able to read
    WITH UNDERSTANDING - or maybe you're twisting my words on purpose, which
    means you're trolling - we better end this 'discussion'".

    Hans Bezemer

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Wed Jun 11 00:58:22 2025
    From Newsgroup: comp.lang.forth

    On 10/06/2025 8:43 pm, LIT wrote:
    : SCAN-NUMBER-OR-SKIP ( n adr len -- n' adr' len')
      DUP >R
      0 0 2SWAP >NUMBER
      DUP R> =
      IF  2SWAP 2DROP  1 /STRING
      ELSE
        2>R D>S SWAP 60 * + 2R>
      THEN ;

    0 0 2SWAP >NUMBER  invariably crops up so I have it in the kernel as
    (NUMBER).  2SWAP 2DROP  is another and becomes  2NIP.  Forth would
    have one define the same thing over and over.  Do it once and be done
    with it IMO.

    So now you see: one can either use variable to
    make the solution cleaner - or one can create new word(s).
    Either way - some new names are added to the vocabulary.
    Why the use of variable, instead of new words,
    should be perceived of 'inferior'? Variable is a word too.

    Unlike variables, factors (subroutines) don't contradict effective
    stack-based programming.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Tue Jun 10 15:39:34 2025
    From Newsgroup: comp.lang.forth

    Unlike variables, factors (subroutines) don't contradict effective stack-based programming.

    Variables "per se" don't contradict that neither.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Tue Jun 10 18:02:54 2025
    From Newsgroup: comp.lang.forth

    On 10-06-2025 17:39, LIT wrote:
    Unlike variables, factors (subroutines) don't contradict effective
    stack-based programming.

    Variables "per se" don't contradict that neither.

    Yes, they do. Best example is recursive code. Recursive won't work with
    global variables. Since code with global variables isn't re-entrant.

    Hans Bezemer

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Tue Jun 10 17:34:42 2025
    From Newsgroup: comp.lang.forth

    So now you see: one can either use variable to
    make the solution cleaner - or one can create new word(s).
    Either way - some new names are added to the vocabulary.
    Why the use of variable, instead of new words,
    should be perceived of 'inferior'? Variable is a word too.

    Unlike variables, factors (subroutines) don't contradict effective stack-based programming.

    From "Thinking Forth":

    "TIP: Simplify code by using the stack. But don’t stack too
    deeply within any single definition. Redesign, or, as a last resort,
    use a named variable.

    Some newcomers to Forth view the stack the way a gymnast views
    a trampoline: as a fun place to bounce around on. But the stack
    is meant for data-passing, not acrobatics.

    [..]

    (not going to paste (almost) whole chapter, but you may want
    to read the section "Redesign" that follows the above)

    I’ve been guilty many times of playing hotshot, trying to do
    as much as possible on the stack rather than define a local
    variable. There are three reasons to avoid this cockiness.

    First, it’s a pain to code that way. Second, the result
    is unreadable. Third, all your work becomes useless when
    a design change becomes necessary, and the order of two
    arguments changes on the stack. The DUPs, OVERs and ROTs
    weren’t really solving the problem, just jockeying things
    into position. With this third reason in mind, I recommend
    the following:

    TIP: Especially in the design phase, keep on the stack only
    the arguments you’re using immediately. Create local
    variables for any others. (If necessary, eliminate the variables
    during the optimization phase.)

    Fourth, if the definition is extremely time-critical, those
    tricky stack manipulators, (e.g., ROT ROT) can really eat up
    clock cycles. Direct access to variables is faster."


    Yes, Brodie warns us next "but careful with variables' use
    too" - and I still think my use of variables in two examples
    I recently pasted wasn't "legit" in any way. It was just
    applying the tips you see above.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Tue Jun 10 17:39:19 2025
    From Newsgroup: comp.lang.forth

    ..I still DON'T think, that... (was supposed to be).

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Tue Jun 10 20:56:28 2025
    From Newsgroup: comp.lang.forth

    3. As Mr. Pelc remarked, stack operators are faster.

    This is what Mr. Pelc remarked, regarding such style
    of programming - yes, many years ago I was guilty of
    that too - already 15 years ago:

    https://groups.google.com/g/comp.lang.forth/c/m9xy5k5BfkY/m/FFmH9GE5UJAJ

    "Although the code is compilable and can be made efficient,
    the source code is a maintenance nightmare!"

    Maybe he changed his mind since that time - well, since
    he's here, you may want to ask him a question.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Wed Jun 11 11:49:17 2025
    From Newsgroup: comp.lang.forth

    On 11/06/2025 3:34 am, LIT wrote:
    ...
    Fourth, if the definition is extremely time-critical, those
    tricky stack manipulators, (e.g., ROT ROT) can really eat up
    clock cycles. Direct access to variables is faster."

    Pushing variables on the stack, executing them, along with their
    associated @ and ! eats clock cycles. This is certainly the case
    in the systems you use.

    Yes, Brodie warns us next "but careful with variables' use
    too" - and I still think my use of variables in two examples
    I recently pasted wasn't "legit" in any way. It was just
    applying the tips you see above.

    When is it "legit" to give up? I've written routines I believed
    needed VARIABLEs. But after a 'cooling off' period, I can look
    at the problem again afresh and find I can do better. Folks will
    say in the real world one couldn't afford this. That's true and
    likely why I'm a hobbyist and not a professional programmer.
    OTOH it's pretty rare that I write routines with variables in them
    to begin with.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Wed Jun 11 09:04:50 2025
    From Newsgroup: comp.lang.forth

    When is it "legit" to give up? I've written routines I believed
    needed VARIABLEs. But after a 'cooling off' period, I can look
    at the problem again afresh and find I can do better. Folks will
    say in the real world one couldn't afford this. That's true and
    likely why I'm a hobbyist and not a professional programmer.
    OTOH it's pretty rare that I write routines with variables in them
    to begin with.

    TO ME it doesn't make a problem how YOU create
    your code, if it suits you better in any way.
    I just explained why MY code looks differently:
    because I reckon the merits listed by Brodie,
    and longer time ago 'switched' from long strings
    of that DUPs, ROTs and SWAPs to something
    I perceive as a cleaner and more comprehensible
    solution - also not being "maintenance nightmare"
    if I later decide to change anything.

    It's the others - or maybe single "other" - who
    decided: "I'll show you how to write 'canonical
    Forth', look how the masters do this and learn".
    Obviously Brodie's "tips", applied in "real life",
    must be irritating for some "real programmers", or
    something.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Wed Jun 11 11:18:18 2025
    From Newsgroup: comp.lang.forth

    On 10-06-2025 22:56, LIT wrote:
    3. As Mr. Pelc remarked, stack operators are faster.

    This is what Mr. Pelc remarked, regarding such style
    of programming - yes, many years ago I was guilty of
    that too - already 15 years ago:

    https://groups.google.com/g/comp.lang.forth/c/m9xy5k5BfkY/m/FFmH9GE5UJAJ

    "Although the code is compilable and can be made efficient,
    the source code is a maintenance nightmare!"

    Maybe he changed his mind since that time - well, since
    he's here, you may want to ask him a question.

    Again, a perfect proof of people having *NO* idea of what they're doing.
    I tackled that *EXACT* problem in
    https://www.youtube.com/watch?v=gfE8arB3uWk

    3 constant vec

    vec array a
    vec array b
    vec array c

    : v! vec 0 do tuck i th ! loop drop ;
    : .v vec 0 do dup i th ? loop drop ;
    : v+ vec 0 do over i th @ over i th @ + -rot loop drop drop spin ;
    : vadd >r v+ r> v! ;

    3 2 1 a v!
    6 5 4 b v!

    a b c vadd c .v

    I don't see how that is problematic maintenance wise. It's not the
    language, it's not the method. It's the programmer overestimating
    himself "YEAH, I CAN TOTALLY DO THAT!!", humbling himself - and then
    blaming the language.

    Hans Bezemer




    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From B. Pym@Nobody447095@here-nor-there.org to comp.lang.forth on Wed Jun 11 09:25:50 2025
    From Newsgroup: comp.lang.forth

    B. Pym wrote:

    B. Pym wrote:

    mhx wrote:

    On Sun, 6 Oct 2024 7:51:31 +0000, dxf wrote:

    Is there an easier way of doing this? End goal is a double number representing centi-secs.


    empty decimal

    : SPLIT ( a u c -- a2 u2 a3 u3 ) >r 2dup r> scan 2swap 2 pick - ;
    : >INT ( adr len -- u ) 0 0 2swap >number 2drop drop ;

    : /T ( a u -- $hour $min $sec )
    2 0 do [char] : split 2swap dup if 1 /string then loop
    2 0 do dup 0= if 2rot 2rot then loop ;

    : .T 2swap 2rot cr >int . ." hr " >int . ." min " >int . ." sec " ;

    s" 1:2:3" /t .t
    s" 02:03" /t .t
    s" 03" /t .t
    s" 23:59:59" /t .t
    s" 0:00:03" /t .t

    Why don't you use the fact that >NUMBER returns the given
    string starting with the first unconverted character?
    SPLIT should be redundant.

    -marcel

    : CHAR-NUMERIC? 48 58 WITHIN ;
    : SKIP-NON-NUMERIC ( adr u -- adr2 u2)
    BEGIN
    DUP IF OVER C@ CHAR-NUMERIC? NOT ELSE 0 THEN
    WHILE
    1 /STRING
    REPEAT ;

    : SCAN-NEXT-NUMBER ( n adr len -- n2 adr2 len2)
    2>R 60 * 0. 2R> >NUMBER
    2>R D>S + 2R> ;

    : PARSE-TIME ( adr len -- seconds)
    0 -ROT
    BEGIN
    SKIP-NON-NUMERIC
    DUP
    WHILE
    SCAN-NEXT-NUMBER
    REPEAT
    2DROP ;

    S" hello 1::36 world" PARSE-TIME CR .
    96 ok


    : SCAN-NUMBER-OR-SKIP ( n adr len -- n' adr' len')
    DUP >R
    0 0 2SWAP >NUMBER
    DUP R> =
    IF 2SWAP 2DROP 1 /STRING
    ELSE
    2>R D>S SWAP 60 * + 2R>
    THEN ;

    : PARSE-TIME ( adr len -- seconds)
    0 -ROT
    BEGIN
    DUP
    WHILE
    SCAN-NUMBER-OR-SKIP
    REPEAT
    2DROP ;

    S" hi 5 or 1 is 44 ho " PARSE-TIME CR .
    18104


    Using local variables.

    : SCAN-NUMBER-OR-SKIP { n adr len -- n' adr' len' }
    0. adr len >NUMBER { adr' len' } D>S { m }
    len' len =
    IF n adr len 1 /STRING
    ELSE
    n 60 * m + adr' len'
    THEN ;

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Wed Jun 11 11:41:07 2025
    From Newsgroup: comp.lang.forth

    On 10-06-2025 19:34, LIT wrote:
    So now you see: one can either use variable to
    make the solution cleaner - or one can create new word(s).
    Either way - some new names are added to the vocabulary.
    Why the use of variable, instead of new words,
    should be perceived of 'inferior'? Variable is a word too.

    Unlike variables, factors (subroutines) don't contradict effective
    stack-based programming.

    From "Thinking Forth":

    "TIP: Simplify code by using the stack. But don’t stack too
    deeply within any single definition. Redesign, or, as a last resort,
    use a named variable.

    Some newcomers to Forth view the stack the way a gymnast views
    a trampoline: as a fun place to bounce around on. But the stack
    is meant for data-passing, not acrobatics.

    [..]

    (not going to paste (almost) whole chapter, but you may want
    to read the section "Redesign" that follows the above)

    I’ve been guilty many times of playing hotshot, trying to do
    as much as possible on the stack rather than define a local
    variable. There are three reasons to avoid this cockiness.

    First, it’s a pain to code that way. Second, the result
    is unreadable. Third, all your work becomes useless when
    a design change becomes necessary, and the order of two
    arguments changes on the stack. The DUPs, OVERs and ROTs
    weren’t really solving the problem, just jockeying things
    into position. With this third reason in mind, I recommend
    the following:

    TIP: Especially in the design phase, keep on the stack only
    the arguments you’re using immediately. Create local
    variables for any others. (If necessary, eliminate the variables
    during the optimization phase.)

    Fourth, if the definition is extremely time-critical, those
    tricky stack manipulators, (e.g., ROT ROT) can really eat up
    clock cycles. Direct access to variables is faster."

    You're mixing quotes with your own statements - and frankly, I'm not
    gonna clean that mess up.

    First of all, Brodie tries to cover as wide a field as possible - and as usual, there is an exception to every (heuristic) rule. So - yeah, I
    used the occasional variable as well. Like when keeping track of the
    position on a screen. I'm not going to drag that s*cker all over the
    data flow, just because Brodie said so.

    It also doesn't work very well for arrays in general. You may pass an
    address to an array to a word, but you're not setting those up in the beginning to surf on the data flow throughout the program.

    But you know very well that's not what I'm addressing..

    You know you're fighting a losing battle when you go into a chapter
    called "The stylish stack" and seek for cherries to pick. That's not
    gonna work.

    And although there is a very funny cartoon in that chapter, all you need
    to know is: "I have a friend who has the sign “Help stamp out variables” above his desk."

    So if you want to find some straw to hold on to, you're not gonna find
    it here:

    "TIP: Unless it involves cluttering up the stack to the point of unreadability, try to pass arguments via the stack rather than pulling
    them out of variables."

    There is much for you to learn here. If your stack clutters up, it
    doesn't automatically mean it can't be done. It just means *you* can't
    do it. I've been humbled by these grumpy old men here numerous times -
    and I thank them for that, because it made me a better programmer.

    Yes, Brodie warns us next "but careful with variables' use
    too" - and I still think my use of variables in two examples
    I recently pasted wasn't "legit" in any way. It was just
    applying the tips you see above.

    It wasn't legit, because I proved it could be done *without global
    variables.* And note every variable access takes two or three words.
    It's *not* automatically faster. If you think a programming language
    always behaves the same - in all situations, on all platforms, in every iteration - it's time for you to read "Advanced C" by the Andersons.
    Gee, you got a long way ahead of you!

    Hans Bezemer


    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Wed Jun 11 11:50:25 2025
    From Newsgroup: comp.lang.forth

    On 11-06-2025 03:49, dxf wrote:
    On 11/06/2025 3:34 am, LIT wrote:
    ...
    Fourth, if the definition is extremely time-critical, those
    tricky stack manipulators, (e.g., ROT ROT) can really eat up
    clock cycles. Direct access to variables is faster."

    Pushing variables on the stack, executing them, along with their
    associated @ and ! eats clock cycles. This is certainly the case
    in the systems you use.

    Agreed.

    Yes, Brodie warns us next "but careful with variables' use
    too" - and I still think my use of variables in two examples
    I recently pasted wasn't "legit" in any way. It was just
    applying the tips you see above.

    When is it "legit" to give up? I've written routines I believed
    needed VARIABLEs. But after a 'cooling off' period, I can look
    at the problem again afresh and find I can do better. Folks will
    say in the real world one couldn't afford this. That's true and
    likely why I'm a hobbyist and not a professional programmer.
    OTOH it's pretty rare that I write routines with variables in them
    to begin with.

    As a guy who used Forth programming in a professional environment, I can
    at least tell you how I did it..

    When you're on the spot, you're on the spot - and you got to provide in
    the allotted time, even if it means making sub-optimal code. That's just
    the way it is, that's corporate life.

    If you tell your boss "Brodie told you to", he's gonna shake his head,
    ask who Brodie is and then ship you to the corporate shrink for an
    emergency session.

    But what I did was to either collect stuff in advance ("Hey, that's a
    nice comma'd printout word by Ed. Better make it work in 4tH!") - or
    make certain libraries beforehand. In that case, all you have to do is
    to shove all those elements together and you're done. The tricky stuff
    is already in your tool chest..

    Take a look at the 4tH library and notice how much of this stuff is of
    no interest at all to the occasional user. Well, that was because it
    wasn't written for you. It was written to be applied at work, so I can
    do miracles and save my reputation. If you wanna win, you gotta cheat ;-)

    Hans Bezemer

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Wed Jun 11 09:58:10 2025
    From Newsgroup: comp.lang.forth

    If you wanna win, you gotta cheat

    Indeed it's what you're doing all the time:
    insisting on "winning" and cheating.
    But it's not that helpful for your so-called
    reputation.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From albert@albert@spenarnc.xs4all.nl to comp.lang.forth on Wed Jun 11 12:18:19 2025
    From Newsgroup: comp.lang.forth

    In article <nnd$215a8dbf$3352f729@c328f69c56780220>,
    Hans Bezemer <the.beez.speaks@gmail.com> wrote:
    On 11-06-2025 03:49, dxf wrote:
    On 11/06/2025 3:34 am, LIT wrote:
    ...
    Fourth, if the definition is extremely time-critical, those
    tricky stack manipulators, (e.g., ROT ROT) can really eat up
    clock cycles. Direct access to variables is faster."

    Pushing variables on the stack, executing them, along with their
    associated @ and ! eats clock cycles. This is certainly the case
    in the systems you use.

    Agreed.

    Yes, Brodie warns us next "but careful with variables' use
    too" - and I still think my use of variables in two examples
    I recently pasted wasn't "legit" in any way. It was just
    applying the tips you see above.

    When is it "legit" to give up? I've written routines I believed
    needed VARIABLEs. But after a 'cooling off' period, I can look
    at the problem again afresh and find I can do better. Folks will
    say in the real world one couldn't afford this. That's true and
    likely why I'm a hobbyist and not a professional programmer.
    OTOH it's pretty rare that I write routines with variables in them
    to begin with.

    As a guy who used Forth programming in a professional environment, I can
    at least tell you how I did it..

    When you're on the spot, you're on the spot - and you got to provide in
    the allotted time, even if it means making sub-optimal code. That's just
    the way it is, that's corporate life.

    Seriously? They ask me beforehand. Philips matlab got upset
    because they were not used to people finishing in the time they
    estimate.
    In another project I was 10% accurate on a total of 30 bugs, and
    within 30% of each bug individually.

    Then I was dropped as project leader into a project that had to finish
    in three months, and I succeeded. If I failed, nobody would complain.

    Fokker Space had a architectural design disapproved by ESO. It was due
    at a certain date. Big kudos if you succeed, and I did.


    If you tell your boss "Brodie told you to", he's gonna shake his head,
    ask who Brodie is and then ship you to the corporate shrink for an
    emergency session.

    There are stupid bosses, that insist on a one line change over
    as 10 line change, as if this made the change more "reliable".
    At the same time they disapprove of test automation.


    But what I did was to either collect stuff in advance ("Hey, that's a
    nice comma'd printout word by Ed. Better make it work in 4tH!") - or
    make certain libraries beforehand. In that case, all you have to do is
    to shove all those elements together and you're done. The tricky stuff
    is already in your tool chest..

    Take a look at the 4tH library and notice how much of this stuff is of
    no interest at all to the occasional user. Well, that was because it
    wasn't written for you. It was written to be applied at work, so I can
    do miracles and save my reputation. If you wanna win, you gotta cheat ;-)

    I don't agree that tool chests built on practice are personal.


    Hans Bezemer


    Groetjes Albert
    --
    Temu exploits Christians: (Disclaimer, only 10 apostles)
    Last Supper Acrylic Suncatcher - 15Cm Round Stained Glass- Style Wall
    Art For Home, Office And Garden Decor - Perfect For Windows, Bars,
    And Gifts For Friends Family And Colleagues.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Wed Jun 11 20:49:09 2025
    From Newsgroup: comp.lang.forth

    On 11/06/2025 7:04 pm, LIT wrote:
    When is it "legit" to give up?  I've written routines I believed
    needed VARIABLEs.  But after a 'cooling off' period, I can look
    at the problem again afresh and find I can do better.  Folks will
    say in the real world one couldn't afford this.  That's true and
    likely why I'm a hobbyist and not a professional programmer.
    OTOH it's pretty rare that I write routines with variables in them
    to begin with.

    TO ME it doesn't make a problem how YOU create
    your code, if it suits you better in any way.
    I just explained why MY code looks differently:
    because I reckon the merits listed by Brodie,
    and longer time ago 'switched' from long strings
    of that DUPs, ROTs and SWAPs to something
    I perceive as a cleaner and more comprehensible
    solution - also not being "maintenance nightmare"
    if I later decide to change anything.

    It's the others - or maybe single "other" - who
    decided: "I'll show you how to write 'canonical
    Forth', look how the masters do this and learn".
    Obviously Brodie's "tips", applied in "real life",
    must be irritating for some "real programmers", or
    something.

    I don't accept good coding has 'long strings of DUPs, ROTs and SWAPs'.
    If it did Moore would likely suggest one hasn't optimized one's stack
    - which is accusation he levels at locals users. Brodie also appears
    to rank locals last:

    Tip

    Simplify code by using the stack. But don’t stack too deeply within
    any single definition. Redesign, or, as a last resort, use a named
    variable.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Wed Jun 11 13:23:46 2025
    From Newsgroup: comp.lang.forth

    On 11-06-2025 12:18, albert@spenarnc.xs4all.nl wrote:
    Seriously? They ask me beforehand. Philips matlab got upset
    because they were not used to people finishing in the time they
    estimate.
    In another project I was 10% accurate on a total of 30 bugs, and
    within 30% of each bug individually.

    Then I was dropped as project leader into a project that had to finish
    in three months, and I succeeded. If I failed, nobody would complain.

    Fokker Space had a architectural design disapproved by ESO. It was due
    at a certain date. Big kudos if you succeed, and I did.

    Gee, if we got to pull out the rulers, I got a few myself. But I'm a
    humble man. :)

    If you tell your boss "Brodie told you to", he's gonna shake his head,
    ask who Brodie is and then ship you to the corporate shrink for an
    emergency session.

    There are stupid bosses, that insist on a one line change over
    as 10 line change, as if this made the change more "reliable".
    At the same time they disapprove of test automation.

    I worked a good 17 years for the Dutch government. Go figure.

    But what I did was to either collect stuff in advance ("Hey, that's a
    nice comma'd printout word by Ed. Better make it work in 4tH!") - or
    make certain libraries beforehand. In that case, all you have to do is
    to shove all those elements together and you're done. The tricky stuff
    is already in your tool chest..

    Take a look at the 4tH library and notice how much of this stuff is of
    no interest at all to the occasional user. Well, that was because it
    wasn't written for you. It was written to be applied at work, so I can
    do miracles and save my reputation. If you wanna win, you gotta cheat ;-)

    I don't agree that tool chests built on practice are personal.

    My wife doesn't agree she should do the dished. Everybody is entitled to
    an opinion - but without argumentation it doesn't mean very much.

    Hans Bezemer

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Wed Jun 11 13:25:48 2025
    From Newsgroup: comp.lang.forth

    On 11-06-2025 11:58, LIT wrote:
    If you wanna win, you gotta cheat

    Indeed it's what you're doing all the time:
    insisting on "winning" and cheating.
    But it's not that helpful for your so-called
    reputation.

    --

    LIT has managed to add another logical fallacy out of the top hat:
    quoting out of context.

    I'm preparing myself for our next discussion where you undoubtedly will
    claim I tend to fart loudly at weddings.

    Hans Bezemer
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Stephen Pelc@stephen@vfxforth.com to comp.lang.forth on Wed Jun 11 11:39:48 2025
    From Newsgroup: comp.lang.forth

    On 10 Jun 2025 at 22:56:28 CEST, "LIT" <LIT> wrote:

    3. As Mr. Pelc remarked, stack operators are faster.

    This is what Mr. Pelc remarked, regarding such style
    of programming - yes, many years ago I was guilty of
    that too - already 15 years ago:

    https://groups.google.com/g/comp.lang.forth/c/m9xy5k5BfkY/m/FFmH9GE5UJAJ

    "Although the code is compilable and can be made efficient,
    the source code is a maintenance nightmare!"

    Maybe he changed his mind since that time - well, since
    he's here, you may want to ask him a question.

    I take the last paragraph as a sort of passive-aggressive asking
    of some indirectly
    asked question. Hence I don't really know what your/the question
    is. Never mind,
    you opened the box.

    Of course I change my mind in 15 years. I'm a human being and so
    am entitled to
    do so and will do so.

    Working code beats all. Clear maintainable code that is easy to
    understand is
    best. I am stil maintaining 40 year old code and my brain is not
    as fast as it used
    to be. Keep it simple. Poking around in a Forth source tree of 1.4
    million lines
    of source code is not what I want to do.

    Once twp implementation techniques provide performance within
    (say) a factor of
    1.5 or 2 of each other, I stop worrying. Short words are better
    than long ones.

    The locals or Forth stack discussions between Anton and myself
    show up a design
    flaw I made 30 years or more ago when the VFX native code
    generator was new.
    The use of ADDR <local> to return the address of the local is a
    mistake that can
    be replaced by a LOCAL[ size ] buffer. When this is done, code
    generation of
    locals can become significantly better. However, I'm not going to
    wreck client
    code for it. My successors can argue about it.

    On Usenet, I take people who use their real names more seriously
    than those who
    do not. Just get a better flame-proof suit and stop being so
    precious.

    Stephen
    --
    Stephen Pelc, stephen@vfxforth.com
    Wodni & Pelc GmbH
    Vienna, Austria
    Tel: +44 (0)7803 903612, +34 649 662 974 http://www.vfxforth.com/downloads/VfxCommunity/
    free VFX Forth downloads
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Wed Jun 11 21:51:33 2025
    From Newsgroup: comp.lang.forth

    On 11/06/2025 7:25 pm, B. Pym wrote:
    B. Pym wrote:

    B. Pym wrote:

    mhx wrote:

    On Sun, 6 Oct 2024 7:51:31 +0000, dxf wrote:

    Is there an easier way of doing this? End goal is a double number
    representing centi-secs.


    empty decimal

    : SPLIT ( a u c -- a2 u2 a3 u3 ) >r 2dup r> scan 2swap 2 pick - ;
    : >INT ( adr len -- u ) 0 0 2swap >number 2drop drop ;

    : /T ( a u -- $hour $min $sec )
    2 0 do [char] : split 2swap dup if 1 /string then loop
    2 0 do dup 0= if 2rot 2rot then loop ;

    : .T 2swap 2rot cr >int . ." hr " >int . ." min " >int . ." sec " ; >>>>>
    s" 1:2:3" /t .t
    s" 02:03" /t .t
    s" 03" /t .t
    s" 23:59:59" /t .t
    s" 0:00:03" /t .t

    Why don't you use the fact that >NUMBER returns the given
    string starting with the first unconverted character?
    SPLIT should be redundant.

    -marcel

    : CHAR-NUMERIC? 48 58 WITHIN ;
    : SKIP-NON-NUMERIC ( adr u -- adr2 u2)
    BEGIN
    DUP IF OVER C@ CHAR-NUMERIC? NOT ELSE 0 THEN
    WHILE
    1 /STRING
    REPEAT ;

    : SCAN-NEXT-NUMBER ( n adr len -- n2 adr2 len2)
    2>R 60 * 0. 2R> >NUMBER
    2>R D>S + 2R> ;

    : PARSE-TIME ( adr len -- seconds)
    0 -ROT
    BEGIN
    SKIP-NON-NUMERIC
    DUP
    WHILE
    SCAN-NEXT-NUMBER
    REPEAT
    2DROP ;

    S" hello 1::36 world" PARSE-TIME CR .
    96 ok


    : SCAN-NUMBER-OR-SKIP ( n adr len -- n' adr' len')
    DUP >R
    0 0 2SWAP >NUMBER
    DUP R> =
    IF 2SWAP 2DROP 1 /STRING
    ELSE
    2>R D>S SWAP 60 * + 2R>
    THEN ;

    : PARSE-TIME ( adr len -- seconds)
    0 -ROT
    BEGIN
    DUP
    WHILE
    SCAN-NUMBER-OR-SKIP
    REPEAT
    2DROP ;

    S" hi 5 or 1 is 44 ho " PARSE-TIME CR .
    18104


    Using local variables.

    : SCAN-NUMBER-OR-SKIP { n adr len -- n' adr' len' }
    0. adr len >NUMBER { adr' len' } D>S { m }
    len' len =
    IF n adr len 1 /STRING
    ELSE
    n 60 * m + adr' len'
    THEN ;

    VFX64
    ( 101 bytes, 27 instructions ) stack
    ( 200 bytes, 50 instructions ) locals

    NTF32
    ( 124 bytes, 34 instructions ) stack
    ( 189 bytes, 48 instructions ) locals




    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Thu Jun 19 08:14:53 2025
    From Newsgroup: comp.lang.forth

    Stack jugglery means wasting CPU cycles for
    moving the bytes around - it's contrproductive.
    Variables have been invented to be used. They're
    useful, if you didn't notice, or if they didn't
    tell you that in your college, or wherever.

    Forth uses variables in the global sense and this works well.
    Variables at the word level is often an indication something is
    wrong.

    "As as result of Forth's heavy use of the stack
    for parameter passing and the efficiency with which
    the stack operators execute, it is easy for the beginner
    to run away with the idea that the stack operators should
    be employed at every opportunity. This is not the case,
    the key to good Forth programming being structure and
    simplicity of coding achieved through correct analysis
    of the problem. Part of the beauty of Forth program is
    the ease with which they can be maintained and adapted
    to cope with new circumstances, due to their extreme
    modularity. A major factor in program maintenance is
    the readability of the code and this is certainly not
    helped by massive clusters of stack operators. The use
    of named variables, whilst consuming more dictionary
    space and executing more slowly, leads to far more
    readable source code and often to a better factored
    and ultimately more efficient application. This becomes
    ever more significant the larger the application."

    (R. Olney, M. Benson - "Forth Fundamentals" - chapter
    7.4. "Stack versus variables")

    Your talk with Marcel reminded me the above.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Fri Jun 20 12:34:52 2025
    From Newsgroup: comp.lang.forth

    On 19/06/2025 6:14 pm, LIT wrote:
    Stack jugglery means wasting CPU cycles for
    moving the bytes around - it's contrproductive.
    Variables have been invented to be used. They're
    useful, if you didn't notice, or if they didn't
    tell you that in your college, or wherever.

    Forth uses variables in the global sense and this works well.
    Variables at the word level is often an indication something is
    wrong.

    "As as result of Forth's heavy use of the stack
    for parameter passing and the efficiency with which
    the stack operators execute, it is easy for the beginner
    to run away with the idea that the stack operators should
    be employed at every opportunity. This is not the case,
    the key to good Forth programming being structure and
    simplicity of coding achieved through correct analysis
    of the problem. Part of the beauty of Forth program is
    the ease with which they can be maintained and adapted
    to cope with new circumstances, due to their extreme
    modularity. A major factor in program maintenance is
    the readability of the code and this is certainly not
    helped by massive clusters of stack operators. The use
    of named variables, whilst consuming more dictionary
    space and executing more slowly, leads to far more
    readable source code and often to a better factored
    and ultimately more efficient application. This becomes
    ever more significant the larger the application."

    (R. Olney, M. Benson - "Forth Fundamentals" - chapter
    7.4. "Stack versus variables")

    Your talk with Marcel reminded me the above.

    The claim made 40 years ago was: "Forth's heavy use of the stack for
    parameter passing [...] it is easy for the beginner to run away with
    the idea that the stack operators should be employed at every
    opportunity." The suggestion being there's so much traffic one must
    use stack juggling to solve it.

    That's the fear and bogeyman that's regularly trotted out about Forth.
    But is it true? None of the colon definitions the authors provide in
    their book would indicate it. Each used 0, 1, 2 and occasionally 3
    parameters. Any variables they employed were sparse and global in
    nature.

    How about more comprehensive applications? One of mine has 154 colon definitions. The number of parameters vs. definitions breaks down as
    follows:

    0 100
    1 27
    2 17
    3 9
    4 1

    10 Values, most of which are set once
    3 Variables

    How much 'stack juggling' did I employ? If by that one means two or
    more stack ops in sequence, it was very rare - two or three instances.
    I don't recall struggling to achieve these results. If anything I was
    on 'auto-pilot' - much the same as when one drives a car.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net (minforth) to comp.lang.forth on Fri Jun 20 05:36:05 2025
    From Newsgroup: comp.lang.forth

    Counter-example: a good number of my apps involve structs, arrays
    and signal vectors in heap memory. Stack juggling? Absolutely not.
    The code would be unreadable and a nightmare to debug.

    Factoring in smaller code portions is often impossible because
    you can't always distribute data, that inherently belongs together,
    over separate words.

    Then why factor, when with using named parameters = locals, the
    code is already short, readable, maintainable, and bug-free.

    Ask yourself why the Forth Scientific Library makes heavy use of
    locals.

    Of course things look different with simpler applications.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From mhx@mhx@iae.nl (mhx) to comp.lang.forth on Fri Jun 20 06:21:40 2025
    From Newsgroup: comp.lang.forth

    On Fri, 20 Jun 2025 5:36:05 +0000, minforth wrote:

    Counter-example: a good number of my apps involve structs, arrays
    and signal vectors in heap memory. Stack juggling? Absolutely not.
    The code would be unreadable and a nightmare to debug.

    Factoring in smaller code portions is often impossible because
    you can't always distribute data, that inherently belongs together,
    over separate words.

    Then why factor, when with using named parameters = locals, the
    code is already short, readable, maintainable, and bug-free.

    Interesting questions. My experience says that arrays and vectors are
    ok, but structs are dangerous, (especially?) when nested. In a 'C'
    project that I contribute to, structs arbitrarily glue data together,
    and then forwardly defined macros hide the details.
    It is impossible to debug this code without tools to decompile/inspect
    the source. It is very difficult to change/rearrange/delete struct
    fields, because they may be used in other places of the code for a
    completely different purpose. The result is that structs only grow
    and nobody dares to prune them. The only remedy is to completely
    start over.

    Ask yourself why the Forth Scientific Library makes heavy use of
    locals.

    Because the original algorithms do.

    Of course things look different with simpler applications.

    And then Einstein's famous quote spoils the fun.

    -marcel
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Fri Jun 20 16:29:35 2025
    From Newsgroup: comp.lang.forth

    On 20/06/2025 3:36 pm, minforth wrote:
    Counter-example: a good number of my apps involve structs, arrays
    and signal vectors in heap memory. Stack juggling? Absolutely not.
    The code would be unreadable and a nightmare to debug.

    Factoring in smaller code portions is often impossible because
    you can't always distribute data, that inherently belongs together,
    over separate words.

    Then why factor, when with using named parameters = locals, the
    code is already short, readable, maintainable, and bug-free.

    Ask yourself why the Forth Scientific Library makes heavy use of
    locals.

    Of course things look different with simpler applications.

    What you're saying is at the level you program, it hardly matters whether
    it's Forth or something else. It's true I have little to no reason to
    use floating-point. I did wonder why Julian Noble persisted with Forth.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From mhx@mhx@iae.nl (mhx) to comp.lang.forth on Fri Jun 20 07:07:43 2025
    From Newsgroup: comp.lang.forth

    On Fri, 20 Jun 2025 6:29:35 +0000, dxf wrote:

    On 20/06/2025 3:36 pm, minforth wrote:
    Counter-example: a good number of my apps involve structs, arrays
    and signal vectors in heap memory. Stack juggling? Absolutely not.
    The code would be unreadable and a nightmare to debug.

    Factoring in smaller code portions is often impossible because
    you can't always distribute data, that inherently belongs together,
    over separate words.

    Then why factor, when with using named parameters = locals, the
    code is already short, readable, maintainable, and bug-free.

    Ask yourself why the Forth Scientific Library makes heavy use of
    locals.

    Of course things look different with simpler applications.

    What you're saying is at the level you program, it hardly matters
    whether it's Forth or something else. It's true I have little to
    no reason to use floating-point. I did wonder why Julian Noble
    persisted with Forth.

    No, I did not say that. What I've found is that when a subject is
    really interesting to you (in my case SPICE), it pays off to restart
    from scratch in Forth (and with a Forth mind-set).

    It is not feasible (and useful) to do that with everything, but it
    does give the type of very hard-to-believe results that are reported
    for Charles Moore. Using floating-point has nothing to do with it.

    -marcel
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net (minforth) to comp.lang.forth on Fri Jun 20 08:45:38 2025
    From Newsgroup: comp.lang.forth

    On Fri, 20 Jun 2025 6:29:35 +0000, dxf wrote:

    On 20/06/2025 3:36 pm, minforth wrote:
    Counter-example: a good number of my apps involve structs, arrays
    and signal vectors in heap memory. Stack juggling? Absolutely not.
    The code would be unreadable and a nightmare to debug.

    Factoring in smaller code portions is often impossible because
    you can't always distribute data, that inherently belongs together,
    over separate words.

    Then why factor, when with using named parameters = locals, the
    code is already short, readable, maintainable, and bug-free.

    Ask yourself why the Forth Scientific Library makes heavy use of
    locals.

    Of course things look different with simpler applications.

    What you're saying is at the level you program, it hardly matters
    whether
    it's Forth or something else.

    But yes, it does matter! Because Forth is compact and can can run
    on devices with limited resources. With Forth I can do realtime math
    on the device without huge libraries, such as LAPACK.

    BTW from a different direction, Krishna Myneni is pursuing a similar
    path:
    http://www.euroforth.org/ef22/papers/myneni-slides.pdf

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Fri Jun 20 08:46:54 2025
    From Newsgroup: comp.lang.forth

    The claim made 40 years ago was: "Forth's heavy use of the stack for parameter passing [...] it is easy for the beginner to run away with
    the idea that the stack operators should be employed at every
    opportunity." The suggestion being there's so much traffic one must
    use stack juggling to solve it.

    How many years ago it was made — it doesn't that matter.
    Pythagorean theorem was made over 2500 years ago, and
    AFAIK it's still actual.

    That's the fear and bogeyman that's regularly trotted out about Forth.
    But is it true? None of the colon definitions the authors provide in
    their book would indicate it. Each used 0, 1, 2 and occasionally 3 parameters. Any variables they employed were sparse and global in
    nature.

    How about more comprehensive applications?

    Then just compare the two examples from "my"
    thread "May the numbers speak". Is really the
    solution that uses strings of "r> drop nip s>d"
    etc. more clear and comprehensible? Oh, really?

    It's what we were talking about - not about
    "one of yours that had 154 colon definitions".

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From albert@albert@spenarnc.xs4all.nl to comp.lang.forth on Fri Jun 20 11:25:15 2025
    From Newsgroup: comp.lang.forth

    In article <f4aaff9dbf58ca3c0e5da7fe278b5a87@www.novabbs.com>,
    mhx <mhx@iae.nl> wrote:
    On Fri, 20 Jun 2025 5:36:05 +0000, minforth wrote:

    Counter-example: a good number of my apps involve structs, arrays
    and signal vectors in heap memory. Stack juggling? Absolutely not.
    The code would be unreadable and a nightmare to debug.

    Factoring in smaller code portions is often impossible because
    you can't always distribute data, that inherently belongs together,
    over separate words.

    Then why factor, when with using named parameters = locals, the
    code is already short, readable, maintainable, and bug-free.

    Interesting questions. My experience says that arrays and vectors are
    ok, but structs are dangerous, (especially?) when nested. In a 'C'
    project that I contribute to, structs arbitrarily glue data together,
    and then forwardly defined macros hide the details.
    It is impossible to debug this code without tools to decompile/inspect
    the source. It is very difficult to change/rearrange/delete struct
    fields, because they may be used in other places of the code for a
    completely different purpose. The result is that structs only grow
    and nobody dares to prune them. The only remedy is to completely
    start over.

    I took over the maintenance of manx (that Marcel wrote) and
    I gave up on maintenance because of the structs.
    The following example uses mini objects.
    A part is a subdivision of a musical score that is played on the
    same instrument. A timeline is used to keep track of the focus
    when the playing of the piece progresses.

    Now look at Forth objects that generalizes CREATE/DOES>
    Here the actions (methods) are directly linked to the
    offset in the object ("struct"):
    Note that mbeat !mbeat (mbeat) work on the same offset (0)
    where an arbitrary value (_) is initialised (using comma `,).
    These three words can be reordered with impunity.
    The same applies to the TIED-group.
    You could interchange the TIED-group with the mbeat-group
    without affecting other parts of the program.
    Methods of the real time "field" uses !mbeat, so this group
    then must move after the beat-group.
    m/note m/beat etc. are approcimately "fields", and can be
    reordered among themselves.
    \ -----------------------------------------------
    \ The class of a time line of a part.
    \ Each part has a time line, and then there is the real time.
    class TIMELINE
    M: mbeat @ M; \ Return current play TIME.
    M: !mbeat 0 SWAP ! M; \ Initialise timeline.
    M: (mbeat) M; _ , \ The timeline of this part.

    \ The real time in TICKS is associated with the current midi time
    \ and made the reference time.
    M: reference-ticks @ M;
    M: SET-TIME ! !mbeat M;
    0 , \ Real time corresponding to mbeat = 0 .

    \ \ The moment of the latest bar, in midibeats since the start.
    \ M: latestbar M; _ ,

    M: m/note M; _ , \ The current note duration in midibeats.
    M: m/beat M; _ , \ The current beat duration in midibeats.
    M: m/measure M; 0 , \ The current measure duration in midibeats.

    \ The amount of semitones the playing is higher than the score.
    \ Negative means lower.
    M: TRANSPOSE M; 0 ,
    \ Ratio between actual and formal note duration.
    M: (ARTICULATION) M; 1 , 1 , \ Default : legato.

    M: TIED-NOTES M; HERE 20 CELLS ALLOT !BAG \ A BAG with tied ``NOTE''s.
    M: TIED! TRUE SWAP ! M; \ Next note must be tied.
    M: UNTIED! FALSE SWAP ! M; \ .. must not ..
    M: TIED? @ M; 0 , \ "This note MUST be tied."
    endclass


    Ask yourself why the Forth Scientific Library makes heavy use of
    locals.

    Because the original algorithms do.

    Case in point the original manx from Marcel did not use too
    many locals, in the new manx they are not used at all.


    Of course things look different with simpler applications.

    And then Einstein's famous quote spoils the fun.

    The new manx is eminently servicable. There are version of
    different (ARM) hardware where the lowlevel control is
    completely different (Originally meant for the parallel port
    in MSDOS). The instrument drivers are of course hardware
    dependant, they are just plugged in.
    The original instruments were percussion, where the note-off
    from midi was ignored.
    Later the organ came along, that uses the note-off midi messages,
    without any repercussions on the architecture of the program.

    Please note that I introduced many names, but not named
    "local values".


    -marcel
    --
    Temu exploits Christians: (Disclaimer, only 10 apostles)
    Last Supper Acrylic Suncatcher - 15Cm Round Stained Glass- Style Wall
    Art For Home, Office And Garden Decor - Perfect For Windows, Bars,
    And Gifts For Friends Family And Colleagues.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Sat Jun 21 17:54:26 2025
    From Newsgroup: comp.lang.forth

    On 20/06/2025 6:45 pm, minforth wrote:
    On Fri, 20 Jun 2025 6:29:35 +0000, dxf wrote:

    On 20/06/2025 3:36 pm, minforth wrote:
    Counter-example: a good number of my apps involve structs, arrays
    and signal vectors in heap memory. Stack juggling? Absolutely not.
    The code would be unreadable and a nightmare to debug.

    Factoring in smaller code portions is often impossible because
    you can't always distribute data, that inherently belongs together,
    over separate words.

    Then why factor, when with using named parameters = locals, the
    code is already short, readable, maintainable, and bug-free.

    Ask yourself why the Forth Scientific Library makes heavy use of
    locals.

    Of course things look different with simpler applications.

    What you're saying is at the level you program, it hardly matters
    whether
    it's Forth or something else.

    But yes, it does matter! Because Forth is compact and can can run
    on devices with limited resources. With Forth I can do realtime math
    on the device without huge libraries, such as LAPACK.

    If that were true and no viable alternatives existed, Forth would have
    an entire market to itself recognized by industry. I'm not sure any
    language could lay claim to have an exclusive market. Presumably to
    do the things you say, you wrote your own libraries? There must exist
    equally competent programmers in C - also deemed a low level language.
    Forth has had its share of failures. Which makes me believe it's more
    about the team one can put together and choices made.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Sun Jun 22 02:02:10 2025
    From Newsgroup: comp.lang.forth

    On 20/06/2025 6:46 pm, LIT wrote:
    The claim made 40 years ago was: "Forth's heavy use of the stack for
    parameter passing [...] it is easy for the beginner to run away with
    the idea that the stack operators should be employed at every
    opportunity."  The suggestion being there's so much traffic one must
    use stack juggling to solve it.

    How many years ago it was made — it doesn't that matter.
    Pythagorean theorem was made over 2500 years ago, and
    AFAIK it's still actual.

    I expect 40 years to show the worthiness of a claim.

    That's the fear and bogeyman that's regularly trotted out about Forth.
    But is it true?  None of the colon definitions the authors provide in
    their book would indicate it.  Each used 0, 1, 2 and occasionally 3
    parameters.  Any variables they employed were sparse and global in
    nature.

    How about more comprehensive applications?

    Then just compare the two examples from "my"
    thread "May the numbers speak". Is really the
    solution that uses strings of "r> drop nip s>d"
    etc. more clear and comprehensible? Oh, really?

    I previously compared yours, with and without variables. I found a few comments added as much readability as variables, but cheaper and faster.

    It's what we were talking about - not about
    "one of yours that had 154 colon definitions".

    You brought to my and c.l.f's attention an assertion made in a book about Forth. It's not everyday one sees a book promoting a language and at the
    same time question its capability.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Sun Jun 22 16:35:40 2025
    From Newsgroup: comp.lang.forth

    On 20-06-2025 10:46, LIT wrote:
    The claim made 40 years ago was: "Forth's heavy use of the stack for
    parameter passing [...] it is easy for the beginner to run away with
    the idea that the stack operators should be employed at every
    opportunity." The suggestion being there's so much traffic one must
    use stack juggling to solve it.

    How many years ago it was made — it doesn't that matter.
    Pythagorean theorem was made over 2500 years ago, and
    AFAIK it's still actual.

    That's the fear and bogeyman that's regularly trotted out about Forth.
    But is it true? None of the colon definitions the authors provide in
    their book would indicate it. Each used 0, 1, 2 and occasionally 3
    parameters. Any variables they employed were sparse and global in
    nature.

    How about more comprehensive applications?

    Then just compare the two examples from "my"
    thread "May the numbers speak". Is really the
    solution that uses strings of "r> drop nip s>d"
    etc. more clear and comprehensible? Oh, really?

    It's what we were talking about - not about
    "one of yours that had 154 colon definitions".

    --
    You can repair such things by using new stack paradigms. I've added
    several ones, most of 'em inspired by others. E.g

    "swap 3OS with TOS" (SPIN, a b c -- c b a)
    "DUP 2OS" (STOW, a b -- a a b)

    -- and several Return Stack operators like R'@, R"@ and RDROP. They're
    not just shorthand, but also a template for stack manipulations.

    The R-stack operators are excellently suited to store (almost)
    constants. The D-stack operators document the intentions of the programmer.

    I'm sure your example comes from a "clean up" operation. It cleans up
    the stacks. Most probably TOS is a return value, that has to be extended
    to a double word (most likely because it is interfaced with a double
    word word).

    One of the techniques I developed is to figure out which stack diagram
    is most suited for the next set of operations. You do your stuff to get
    there, document the resulting scheme - and the rest of your stack manipulations are simple and shallow.

    But of course, you have to do the work. If you're incapable or too lazy
    to do the work, yeah, then you will find Forth bites you. Note that C is
    a very nice language as well. Beats Forth performance wise - so, what's
    there not to like :)

    Hans Bezemer
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net (minforth) to comp.lang.forth on Sun Jun 22 21:27:40 2025
    From Newsgroup: comp.lang.forth

    On Sun, 22 Jun 2025 14:35:40 +0000, Hans Bezemer wrote:
    You can repair such things by using new stack paradigms. I've added
    several ones, most of 'em inspired by others. E.g

    "swap 3OS with TOS" (SPIN, a b c -- c b a)
    "DUP 2OS" (STOW, a b -- a a b)
    <snip>
    But of course, you have to do the work. If you're incapable or too lazy
    to do the work, yeah, then you will find Forth bites you. Note that C is
    a very nice language as well. Beats Forth performance wise - so, what's
    there not to like :)

    I mostly belong to the lazy kind. Therefore, I prefer to let the
    computer
    do the tedious work before spending time on premature optimizations,
    such as stack ordering.

    So, I made me a small extension to the locals word set. Using your
    example SPIN (abc — cba), I can define it as follows:
    : SPIN { a b c == c b a } ; \ no need for additional code before ;
    or likewise for floats, doubles, strings, matrices
    : FSPIN { f: a b c == c b a } ;
    : DSPIN { d: a b c == c b a } ;
    : "SPIN { s: a b c == c b a } ;
    : MSPIN { m: a b c == c b a } ;
    Code generation and register optimization is the computer's job.

    SPIN/STOW or similar microexamples can, of course, be defined quickly
    with classic Forth stack juggling too. The power of the extension
    becomes more apparent with mixed parameter types and/or more parameters,
    and of course, with some non-trivial algorithm to solve.

    I couldn't have done this in C, but Forth allows you to modify the
    compiler until it suits your work domain.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Mon Jun 23 13:19:38 2025
    From Newsgroup: comp.lang.forth

    On 23/06/2025 7:27 am, minforth wrote:
    On Sun, 22 Jun 2025 14:35:40 +0000, Hans Bezemer wrote:
    You can repair such things by using new stack paradigms. I've added
    several ones, most of 'em inspired by others. E.g

    "swap 3OS with TOS" (SPIN, a b c -- c b a)
    "DUP 2OS" (STOW, a b -- a a b)
    <snip>
    But of course, you have to do the work. If you're incapable or too lazy
    to do the work, yeah, then you will find Forth bites you. Note that C is
    a very nice language as well. Beats Forth performance wise - so, what's
    there not to like :)

    I mostly belong to the lazy kind. Therefore, I prefer to let the
    computer
    do the tedious work before spending time on premature optimizations,
    such as stack ordering.

    So, I made me a small extension to the locals word set. Using your
    example SPIN (abc — cba), I can define it as follows:
    : SPIN { a b c == c b a } ; \ no need for additional code before ;
    or likewise for floats, doubles, strings, matrices
    : FSPIN { f: a b c == c b a } ;
    : DSPIN { d: a b c == c b a } ;
    : "SPIN { s: a b c == c b a } ;
    : MSPIN { m: a b c == c b a } ;
    Code generation and register optimization is the computer's job.

    SPIN/STOW or similar microexamples can, of course, be defined quickly
    with classic Forth stack juggling too. The power of the extension
    becomes more apparent with mixed parameter types and/or more parameters,
    and of course, with some non-trivial algorithm to solve.

    I couldn't have done this in C, but Forth allows you to modify the
    compiler until it suits your work domain.

    Which is as much a personal affair. It's hard to lay claim to features
    other languages show no interest in emulating. Even between one forth
    and another.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Mon Jun 23 05:05:57 2025
    From Newsgroup: comp.lang.forth

    On Sun, 22 Jun 2025 14:35:40 +0000, Hans Bezemer wrote:

    On 20-06-2025 10:46, LIT wrote:
    The claim made 40 years ago was: "Forth's heavy use of the stack for
    parameter passing [...] it is easy for the beginner to run away with
    the idea that the stack operators should be employed at every
    opportunity." The suggestion being there's so much traffic one must
    use stack juggling to solve it.

    How many years ago it was made — it doesn't that matter.
    Pythagorean theorem was made over 2500 years ago, and
    AFAIK it's still actual.

    That's the fear and bogeyman that's regularly trotted out about
    Forth.
    But is it true? None of the colon definitions the authors provide
    in
    their book would indicate it. Each used 0, 1, 2 and occasionally 3
    parameters. Any variables they employed were sparse and global in
    nature.

    How about more comprehensive applications?

    Then just compare the two examples from "my"
    thread "May the numbers speak". Is really the
    solution that uses strings of "r> drop nip s>d"
    etc. more clear and comprehensible? Oh, really?

    It's what we were talking about - not about
    "one of yours that had 154 colon definitions".

    --
    You can repair such things by using new stack paradigms. I've added
    several ones, most of 'em inspired by others. E.g

    "swap 3OS with TOS" (SPIN, a b c -- c b a)
    "DUP 2OS" (STOW, a b -- a a b)

    -- and several Return Stack operators like R'@, R"@ and RDROP. They're
    not just shorthand, but also a template for stack manipulations.

    The R-stack operators are excellently suited to store (almost)
    constants. The D-stack operators document the intentions of the
    programmer.

    I'm sure your example comes from a "clean up" operation. It cleans up
    the stacks. Most probably TOS is a return value, that has to be extended
    to a double word (most likely because it is interfaced with a double
    word word).

    One of the techniques I developed is to figure out which stack diagram
    is most suited for the next set of operations. You do your stuff to get there, document the resulting scheme - and the rest of your stack manipulations are simple and shallow.

    But of course, you have to do the work. If you're incapable or too lazy
    to do the work, yeah, then you will find Forth bites you. Note that C is
    a very nice language as well. Beats Forth performance wise - so, what's
    there not to like :)

    Hans Bezemer

    Mr. FIFO, that Forth of yours bites you from time to time?
    It must have rabies, or something. You may want to take
    it to the nearest vet.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Mon Jun 23 05:18:34 2025
    From Newsgroup: comp.lang.forth

    minforth@gmx.net (minforth) writes:
    So, I made me a small extension to the locals word set. Using your
    example SPIN (abc — cba), I can define it as follows:
    : SPIN { a b c == c b a } ; \ no need for additional code before ;

    What is the advantage of using this extension over the Forth-2012:

    : spin {: a b c :} c b a ;

    ?

    or likewise for floats, doubles, strings, matrices
    : FSPIN { f: a b c == c b a } ;

    Lack of support for other types other than cells is indeed a
    shortcoming of standard locals. In Gforth you could write that as

    : fspin {: f: a f: b f: c :} c b a ;

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2023 proceedings: http://www.euroforth.org/ef23/papers/
    EuroForth 2024 proceedings: http://www.euroforth.org/ef24/papers/
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From mhx@mhx@iae.nl (mhx) to comp.lang.forth on Mon Jun 23 05:40:37 2025
    From Newsgroup: comp.lang.forth

    On Sun, 22 Jun 2025 21:27:40 +0000, minforth wrote:

    [..]
    So, I made me a small extension to the locals word set. Using your
    example SPIN (abc — cba), I can define it as follows:
    : SPIN { a b c == c b a } ; \ no need for additional code before ;
    or likewise for floats, doubles, strings, matrices
    : FSPIN { f: a b c == c b a } ;
    : DSPIN { d: a b c == c b a } ;
    : "SPIN { s: a b c == c b a } ;
    : MSPIN { m: a b c == c b a } ;
    Code generation and register optimization is the computer's job.

    SPIN/STOW or similar microexamples can, of course, be defined quickly
    with classic Forth stack juggling too. The power of the extension
    becomes more apparent with mixed parameter types and/or more parameters,
    and of course, with some non-trivial algorithm to solve.

    Do you mean your compiler automatically handles/allows combinations
    like
    .. 22e-12 69. A{{ ( F: -- a ) ( D: -- b ) ( M: -- c ) SPIN ...

    I found that handling mixed types explodes the code that needs
    to be written for a simple compiler like, e.g., Tiny-KISS . It
    would be great if that can be automated.

    -marcel

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net (minforth) to comp.lang.forth on Mon Jun 23 10:02:44 2025
    From Newsgroup: comp.lang.forth

    On Mon, 23 Jun 2025 5:40:37 +0000, mhx wrote:

    On Sun, 22 Jun 2025 21:27:40 +0000, minforth wrote:

    [..]
    So, I made me a small extension to the locals word set. Using your
    example SPIN (abc — cba), I can define it as follows:
    : SPIN { a b c == c b a } ; \ no need for additional code before ;
    or likewise for floats, doubles, strings, matrices
    : FSPIN { f: a b c == c b a } ;
    : DSPIN { d: a b c == c b a } ;
    : "SPIN { s: a b c == c b a } ;
    : MSPIN { m: a b c == c b a } ;
    Code generation and register optimization is the computer's job.

    SPIN/STOW or similar microexamples can, of course, be defined quickly
    with classic Forth stack juggling too. The power of the extension
    becomes more apparent with mixed parameter types and/or more parameters,
    and of course, with some non-trivial algorithm to solve.

    Do you mean your compiler automatically handles/allows combinations
    like
    ... 22e-12 69. A{{ ( F: -- a ) ( D: -- b ) ( M: -- c ) SPIN ...

    I found that handling mixed types explodes the code that needs
    to be written for a simple compiler like, e.g., Tiny-KISS . It
    would be great if that can be automated.

    I don't know if I got you right, because as previously
    defined, SPIN expects three integers on the data stack.

    However, following your idea, a mixed SPIN could be defined e.g.

    : XSPIN { f: a d: b m: c == c b a } ;

    that can work with

    .. 22e-12 69. A{{ XSPIN ...

    I think gforth has allowed mixed type locals for a long time,
    so they are nothing really special.

    The only new word is == which pushes the locals following
    == on the stack before the word terminates with a ; or EXIT.

    This releaves you of the need to keep track of the data stack.
    A brief stack depth check can also catch some mistakes.

    I always found the conventional syntax wasteful, where
    everything after a -- does nothing but inform the reader.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Mon Jun 23 13:52:13 2025
    From Newsgroup: comp.lang.forth

    On 23-06-2025 07:05, LIT wrote:
    On Sun, 22 Jun 2025 14:35:40 +0000, Hans Bezemer wrote:

    On 20-06-2025 10:46, LIT wrote:
    The claim made 40 years ago was: "Forth's heavy use of the stack for
    parameter passing [...] it is easy for the beginner to run away with
    the idea that the stack operators should be employed at every
    opportunity."  The suggestion being there's so much traffic one must >>  >> use stack juggling to solve it.
    ;
    How many years ago it was made — it doesn't that matter.
    Pythagorean theorem was made over 2500 years ago, and
    AFAIK it's still actual.
    ;
    That's the fear and bogeyman that's regularly trotted out about
    Forth.
    But is it true?  None of the colon definitions the authors provide
    in
    their book would indicate it.  Each used 0, 1, 2 and occasionally 3
    parameters.  Any variables they employed were sparse and global in
    nature.
    ;
    How about more comprehensive applications?
    ;
    Then just compare the two examples from "my"
    thread "May the numbers speak". Is really the
    solution that uses strings of "r> drop nip s>d"
    etc. more clear and comprehensible? Oh, really?
    ;
    It's what we were talking about - not about
    "one of yours that had 154 colon definitions".
    ;
    --
    You can repair such things by using new stack paradigms. I've added
    several ones, most of 'em inspired by others. E.g

    "swap 3OS with TOS" (SPIN, a b c -- c b a)
    "DUP 2OS" (STOW, a b -- a a b)

    -- and several Return Stack operators like R'@, R"@ and RDROP. They're
    not just shorthand, but also a template for stack manipulations.

    The R-stack operators are excellently suited to store (almost)
    constants. The D-stack operators document the intentions of the
    programmer.

    I'm sure your example comes from a "clean up" operation. It cleans up
    the stacks. Most probably TOS is a return value, that has to be extended
    to a double word (most likely because it is interfaced with a double
    word word).

    One of the techniques I developed is to figure out which stack diagram
    is most suited for the next set of operations. You do your stuff to get
    there, document the resulting scheme - and the rest of your stack
    manipulations are simple and shallow.

    But of course, you have to do the work. If you're incapable or too lazy
    to do the work, yeah, then you will find Forth bites you. Note that C is
    a very nice language as well. Beats Forth performance wise - so, what's
    there not to like :)

    Hans Bezemer

    Mr. FIFO, that Forth of yours bites you from time to time?
    It must have rabies, or something. You may want to take
    it to the nearest vet.

    No, I'm a good Forth wrangler after 40 years - given all the atrocities
    I am willing to rewrite into proper Forth. It's there for all people to
    see. I don't cheat. I'm not secretly writing locals infested code.

    No, frankly it was more targeted to those who are obviously unable to
    write proper Forth. Unwilling to admit it - and unwilling to migrate to
    much simpler languages, which are more suited for their limited talents.

    I can only assume they've run into a wall in private, got angry at the language instead of themselves - and then tried to turn it into the abomination they so desperately promote as "the true Forth", which
    actually is nothing more than a flawed C in wrapped in a thin Forth skin.

    It's silly. I know Forth is an elite language - but sometimes you have
    to realize you simply don't belong to that group, not in a million years.

    I pity those people. Really. My prayers are for them. Every night.

    Hans Bezemer



    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Mon Jun 23 12:49:57 2025
    From Newsgroup: comp.lang.forth

    On Mon, 23 Jun 2025 11:52:13 +0000, Hans Bezemer wrote:

    On 23-06-2025 07:05, LIT wrote:
    On Sun, 22 Jun 2025 14:35:40 +0000, Hans Bezemer wrote:

    On 20-06-2025 10:46, LIT wrote:
    The claim made 40 years ago was: "Forth's heavy use of the stack for >>>  >> parameter passing [...] it is easy for the beginner to run away with >>>  >> the idea that the stack operators should be employed at every
    opportunity."  The suggestion being there's so much traffic one must >>>  >> use stack juggling to solve it.
    ;
    How many years ago it was made — it doesn't that matter.
    Pythagorean theorem was made over 2500 years ago, and
    AFAIK it's still actual.
    ;
    That's the fear and bogeyman that's regularly trotted out about
    Forth.
    But is it true?  None of the colon definitions the authors provide >>> in
    their book would indicate it.  Each used 0, 1, 2 and occasionally 3 >>>  >> parameters.  Any variables they employed were sparse and global in >>>  >> nature.
    ;
    How about more comprehensive applications?
    ;
    Then just compare the two examples from "my"
    thread "May the numbers speak". Is really the
    solution that uses strings of "r> drop nip s>d"
    etc. more clear and comprehensible? Oh, really?
    ;
    It's what we were talking about - not about
    "one of yours that had 154 colon definitions".
    ;
    --
    You can repair such things by using new stack paradigms. I've added
    several ones, most of 'em inspired by others. E.g

    "swap 3OS with TOS" (SPIN, a b c -- c b a)
    "DUP 2OS" (STOW, a b -- a a b)

    -- and several Return Stack operators like R'@, R"@ and RDROP. They're
    not just shorthand, but also a template for stack manipulations.

    The R-stack operators are excellently suited to store (almost)
    constants. The D-stack operators document the intentions of the
    programmer.

    I'm sure your example comes from a "clean up" operation. It cleans up
    the stacks. Most probably TOS is a return value, that has to be extended >>> to a double word (most likely because it is interfaced with a double
    word word).

    One of the techniques I developed is to figure out which stack diagram
    is most suited for the next set of operations. You do your stuff to get
    there, document the resulting scheme - and the rest of your stack
    manipulations are simple and shallow.

    But of course, you have to do the work. If you're incapable or too lazy
    to do the work, yeah, then you will find Forth bites you. Note that C is >>> a very nice language as well. Beats Forth performance wise - so, what's
    there not to like :)

    Hans Bezemer

    Mr. FIFO, that Forth of yours bites you from time to time?
    It must have rabies, or something. You may want to take
    it to the nearest vet.

    No, I'm a good Forth wrangler after 40 years - given all the atrocities
    I am willing to rewrite into proper Forth. It's there for all people to
    see. I don't cheat. I'm not secretly writing locals infested code.

    What you mean "you don't cheat"? Since when?
    You cheat all the time:

    "If you wanna win, you gotta cheat ;-)"

    https://www.novabbs.com/devel/article-flat.php?id=29346&group=comp.lang.forth#29346

    No, frankly it was more targeted to those who are obviously unable to
    write proper Forth. Unwilling to admit it - and unwilling to migrate to
    much simpler languages, which are more suited for their limited talents.

    I can only assume they've run into a wall in private, got angry at the language instead of themselves - and then tried to turn it into the abomination they so desperately promote as "the true Forth", which
    actually is nothing more than a flawed C in wrapped in a thin Forth
    skin.

    It's silly. I know Forth is an elite language

    Actually it isn't; it's probably the most "democratic"
    programming language in the world...

    - but sometimes you have
    to realize you simply don't belong to that group, not in a million
    years.

    I pity those people. Really. My prayers are for them. Every night.

    Hans Bezemer

    ..it's just some people try hard to present themselves
    as a "members of (supposed) elite circle" - so at the
    moment they came up with the idea "the best way will
    be when I promote myself as an elite programmer".

    It seems their attempts with every other programming
    language proved something contrary, and that's why
    their decision is: "I'll tell them I'm a Master of Forth
    and this time they'll be unable to verify that!".

    ( "If you wanna win, you gotta cheat ;-)" )

    Of course in fact nobody gives a damn - anyway how
    can such supposed "member of elite" be someone,
    who doesn't even know fundamentals of Forth - I mean
    someone who made a whole YT recording persuading the
    audience, that "Forth uses FIFO stack"? It's like someone
    who pretends to be kind of "supreme general" had no idea,
    which end of the rifle is actually being shot from.
    Unbelievable!
    Or maybe you were going to cheat your audience? :D

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From mhx@mhx@iae.nl (mhx) to comp.lang.forth on Mon Jun 23 13:34:08 2025
    From Newsgroup: comp.lang.forth

    On Mon, 23 Jun 2025 10:02:44 +0000, minforth wrote:

    On Mon, 23 Jun 2025 5:40:37 +0000, mhx wrote:

    On Sun, 22 Jun 2025 21:27:40 +0000, minforth wrote:

    [..]
    Do you mean your compiler automatically handles/allows combinations
    like
    ... 22e-12 69. A{{ ( F: -- a ) ( D: -- b ) ( M: -- c ) SPIN ...

    I found that handling mixed types explodes the code that needs
    to be written for a simple compiler like, e.g., Tiny-KISS . It
    would be great if that can be automated.
    I don't know if I got you right, because as previously
    defined, SPIN expects three integers on the data stack.

    I was indeed too hasty. If items are stacked, no type conversion
    is needed if they are only reordered. (Reordering needs
    no code anyway, as it is a only a memo to the compiler.) The
    problems only arise when an cell must be translated to a complex
    extended float, or when using floats to initialize an arbitrary
    precision matrix.

    Do you really support matrix and string type locals? The former
    I only do for arbitrary precision, the latter can be handled
    with DLOCALS| .

    -marcel

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Mon Jun 23 15:50:13 2025
    From Newsgroup: comp.lang.forth

    On 23-06-2025 14:49, LIT wrote:
    What you mean "you don't cheat"? Since when?
    You cheat all the time:

    "If you wanna win, you gotta cheat ;-)"


    Ooh - another quote out of context. BTW, I also fart loudly at weddings. :)

    https://www.novabbs.com/devel/article-flat.php?id=29346&group=comp.lang.forth#29346

    Thanks for the link. People can now see the quote in full context -
    usually I gotta find out myself!

    Actually it isn't; it's probably the most "democratic"
    programming language in the world...

    If you make a claim, you have to prove it (the burden of proof is on
    your side). However, there is no proof - so what can be asserted without
    proof can be dismissed without proof.

    ..it's just some people try hard to present themselves
    as a "members of (supposed) elite circle" - so at the
    moment they came up with the idea "the best way will
    be when I promote myself as an elite programmer".

    Where EXACTLY did I claim I was "an elite programmer"? But I do thank
    you for putting me into that group! Thanks!! I appreciate it - never
    thought I'd get such a compliment from you! <BLUSH>

    I mean
    someone who made a whole YT recording persuading the
    audience, that "Forth uses FIFO stack"?

    You might want to sing another song. This one is getting old. It might
    not only indicate a severe lack of true arguments, it also clearly
    indicates that your only "arguments" are just logical fallacies of the
    most primitive sort (according to "Grahams triangle of disagreement" - I
    can help you with that one if assistance is required).

    It is as if you never left high school. Because that is where you
    normally observe such infantile behavior. Especially with teenage girls.

    Hans Bezemer
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net (minforth) to comp.lang.forth on Mon Jun 23 15:09:41 2025
    From Newsgroup: comp.lang.forth

    On Mon, 23 Jun 2025 13:34:08 +0000, mhx wrote:

    On Mon, 23 Jun 2025 10:02:44 +0000, minforth wrote:

    On Mon, 23 Jun 2025 5:40:37 +0000, mhx wrote:

    On Sun, 22 Jun 2025 21:27:40 +0000, minforth wrote:

    [..]
    Do you mean your compiler automatically handles/allows combinations
    like
    ... 22e-12 69. A{{ ( F: -- a ) ( D: -- b ) ( M: -- c ) SPIN ...

    I found that handling mixed types explodes the code that needs
    to be written for a simple compiler like, e.g., Tiny-KISS . It
    would be great if that can be automated.
    I don't know if I got you right, because as previously
    defined, SPIN expects three integers on the data stack.

    I was indeed too hasty. If items are stacked, no type conversion
    is needed if they are only reordered. (Reordering needs
    no code anyway, as it is a only a memo to the compiler.) The
    problems only arise when an cell must be translated to a complex
    extended float, or when using floats to initialize an arbitrary
    precision matrix.

    This is too vague for me, but perhaps it's not important anyway.
    In any case, my compiler also supports Z: type complex locals.

    Do you really support matrix and string type locals? The former
    I only do for arbitrary precision, the latter can be handled
    with DLOCALS| .

    I use a matrix stack (a depth of 10-20 items is usually sufficient).
    By default, matrix elements are 32-bit sfloats. Matrix locals
    (and mvalues) are just small structs containing matrix information
    and a pointer to the heap memory allocated for all matrix elements.

    Dynamic strings are simply 1-dimensional character matrices.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Mon Jun 23 18:48:38 2025
    From Newsgroup: comp.lang.forth

    On Mon, 23 Jun 2025 13:50:13 +0000, Hans Bezemer wrote:

    On 23-06-2025 14:49, LIT wrote:
    What you mean "you don't cheat"? Since when?
    You cheat all the time:

    "If you wanna win, you gotta cheat ;-)"


    Ooh - another quote out of context. BTW, I also fart loudly at weddings.
    :)

    https://www.novabbs.com/devel/article-flat.php?id=29346&group=comp.lang.forth#29346

    Thanks for the link. People can now see the quote in full context -
    usually I gotta find out myself!

    Actually it isn't; it's probably the most "democratic"
    programming language in the world...

    If you make a claim, you have to prove it (the burden of proof is on
    your side). However, there is no proof - so what can be asserted without proof can be dismissed without proof.

    ..it's just some people try hard to present themselves
    as a "members of (supposed) elite circle" - so at the
    moment they came up with the idea "the best way will
    be when I promote myself as an elite programmer".

    Where EXACTLY did I claim I was "an elite programmer"? But I do thank
    you for putting me into that group! Thanks!! I appreciate it - never
    thought I'd get such a compliment from you! <BLUSH>

    I mean
    someone who made a whole YT recording persuading the
    audience, that "Forth uses FIFO stack"?

    You might want to sing another song. This one is getting old. It might
    not only indicate a severe lack of true arguments, it also clearly
    indicates that your only "arguments" are just logical fallacies of the
    most primitive sort (according to "Grahams triangle of disagreement" - I
    can help you with that one if assistance is required).

    It is as if you never left high school. Because that is where you
    normally observe such infantile behavior. Especially with teenage girls.

    Hans Bezemer

    You want "another song"? You don't like
    the one mentioned above? No wonder.

    OK, have another song: Mr. FIFO stating that
    "arrays aren't variables" (maybe need a link?).
    Where did they taught you that? At that 'college'
    of yours, "elite programmer"? :D

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net (minforth) to comp.lang.forth on Mon Jun 23 21:03:19 2025
    From Newsgroup: comp.lang.forth

    On Mon, 23 Jun 2025 5:18:34 +0000, Anton Ertl wrote:

    minforth@gmx.net (minforth) writes:
    So, I made me a small extension to the locals word set. Using your
    example SPIN (abc — cba), I can define it as follows:
    : SPIN { a b c == c b a } ; \ no need for additional code before ;

    What is the advantage of using this extension over the Forth-2012:

    : spin {: a b c :} c b a ;

    ?

    Obviously, there is no advantage for such small definitions.

    For me, the small syntax extension is a convenience when working
    with longer definitions. A bit contrived (:= synonym for TO):

    : SOME-APP { a f: b c | temp == n: flag z: freq }
    \ inputs: integer a, floats b c
    \ uninitialized: float temp
    \ outputs: integer flag, complex freq
    <: FUNC < ... calc function ... > ;>
    \ emulated embedded function using { | xt: func }
    < ... calc something ... > := temp
    < ... calc other things ... > := freq / basic formula
    < ... calc other things ... > := flag
    < ... calc correction ... > := freq / better estimation
    ;

    While working on such things, I can focus my eyes on the formulas,
    all local values are visible in one place, and I don't have to
    worry about tracking the data stack(s) for lost/accumulated items.

    As I said, it is nothing spectacular, just helpful. And to my own
    eyes, it looks neater. ;-)

    And before dxf yowls again: it is still Forth. :o)

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Mon Jun 23 23:20:46 2025
    From Newsgroup: comp.lang.forth

    On 23-06-2025 23:03, minforth wrote:
    On Mon, 23 Jun 2025 5:18:34 +0000, Anton Ertl wrote:

    minforth@gmx.net (minforth) writes:
    So, I made me a small extension to the locals word set. Using your
    example SPIN (abc — cba), I can define it as follows:
    : SPIN { a b c == c b a } ; \ no need for additional code before ;

    What is the advantage of using this extension over the Forth-2012:

    : spin {: a b c :} c b a ;

    ?

    Obviously, there is no advantage for such small definitions.

    For me, the small syntax extension is a convenience when working
    with longer definitions. A bit contrived (:= synonym for TO):

    : SOME-APP { a f: b c | temp == n: flag z: freq }
    \ inputs: integer a, floats b c
    \ uninitialized: float temp
    \ outputs: integer flag, complex freq
     <: FUNC < ... calc function ... > ;>
    \ emulated embedded function using { | xt: func }
     < ... calc something ... > := temp
     < ... calc other things ... > := freq  / basic formula
     < ... calc other things ... > := flag
     < ... calc correction ... > := freq  / better estimation
    ;

    While working on such things, I can focus my eyes on the formulas,
    all local values are visible in one place, and I don't have to
    worry about tracking the data stack(s) for lost/accumulated items.

    As I said, it is nothing spectacular, just helpful. And to my own
    eyes, it looks neater.  ;-)

    And before dxf yowls again: it is still Forth. :o)

    Well.. Technically everything written in Forth is Forth. But it is not canonical Forth - because if it were canonical Forth, we would have
    covered locals in "Starting Forth" - and we didn't.

    Now, let's assume we found we were wrong. But there was a chapter in
    "Thinking Forth" called "The stylish stack" - not "The stylish locals".
    As a matter of fact, it states that "the stack is not an array" -
    meaning: not randomly accessible. And what are locals? Right. Randomly accessible.

    So, what is this? It's a feeble imitation of C. It's not part of the
    original design. Because if it were part of the original design, you
    would find out what it means to think differently. This is merely C
    thinking. Nothing else. Certainly not Forth thinking.

    Hans Bezemer

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net (minforth) to comp.lang.forth on Tue Jun 24 00:42:09 2025
    From Newsgroup: comp.lang.forth

    On Mon, 23 Jun 2025 21:20:46 +0000, Hans Bezemer wrote:

    On 23-06-2025 23:03, minforth wrote:
    On Mon, 23 Jun 2025 5:18:34 +0000, Anton Ertl wrote:

    minforth@gmx.net (minforth) writes:
    So, I made me a small extension to the locals word set. Using your
    example SPIN (abc — cba), I can define it as follows:
    : SPIN { a b c == c b a } ; \ no need for additional code before ;

    What is the advantage of using this extension over the Forth-2012:

    : spin {: a b c :} c b a ;

    ?

    Obviously, there is no advantage for such small definitions.

    For me, the small syntax extension is a convenience when working
    with longer definitions. A bit contrived (:= synonym for TO):

    : SOME-APP { a f: b c | temp == n: flag z: freq }
    \ inputs: integer a, floats b c
    \ uninitialized: float temp
    \ outputs: integer flag, complex freq
     <: FUNC < ... calc function ... > ;>
    \ emulated embedded function using { | xt: func }
     < ... calc something ... > := temp
     < ... calc other things ... > := freq  / basic formula
     < ... calc other things ... > := flag
     < ... calc correction ... > := freq  / better estimation
    ;

    While working on such things, I can focus my eyes on the formulas,
    all local values are visible in one place, and I don't have to
    worry about tracking the data stack(s) for lost/accumulated items.

    As I said, it is nothing spectacular, just helpful. And to my own
    eyes, it looks neater.  ;-)

    And before dxf yowls again: it is still Forth. :o)

    Well.. Technically everything written in Forth is Forth. But it is not canonical Forth - because if it were canonical Forth, we would have
    covered locals in "Starting Forth" - and we didn't.

    Now, let's assume we found we were wrong. But there was a chapter in "Thinking Forth" called "The stylish stack" - not "The stylish locals".
    As a matter of fact, it states that "the stack is not an array" -
    meaning: not randomly accessible. And what are locals? Right. Randomly accessible.

    So, what is this? It's a feeble imitation of C. It's not part of the
    original design. Because if it were part of the original design, you
    would find out what it means to think differently. This is merely C
    thinking. Nothing else. Certainly not Forth thinking.


    LOL ... I admit being a very non-canonical old guy :O)

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Tue Jun 24 15:31:45 2025
    From Newsgroup: comp.lang.forth

    On 24/06/2025 10:42 am, minforth wrote:
    On Mon, 23 Jun 2025 21:20:46 +0000, Hans Bezemer wrote:

    On 23-06-2025 23:03, minforth wrote:
    On Mon, 23 Jun 2025 5:18:34 +0000, Anton Ertl wrote:

    minforth@gmx.net (minforth) writes:
    So, I made me a small extension to the locals word set. Using your
    example SPIN (abc — cba), I can define it as follows:
    : SPIN { a b c == c b a } ; \ no need for additional code before ;

    What is the advantage of using this extension over the Forth-2012:

    : spin {: a b c :} c b a ;

    ?

    Obviously, there is no advantage for such small definitions.

    For me, the small syntax extension is a convenience when working
    with longer definitions. A bit contrived (:= synonym for TO):

    : SOME-APP { a f: b c | temp == n: flag z: freq }
    \ inputs: integer a, floats b c
    \ uninitialized: float temp
    \ outputs: integer flag, complex freq
      <: FUNC < ... calc function ... > ;>
    \ emulated embedded function using { | xt: func }
      < ... calc something ... > := temp
      < ... calc other things ... > := freq  / basic formula
      < ... calc other things ... > := flag
      < ... calc correction ... > := freq  / better estimation
    ;

    While working on such things, I can focus my eyes on the formulas,
    all local values are visible in one place, and I don't have to
    worry about tracking the data stack(s) for lost/accumulated items.

    As I said, it is nothing spectacular, just helpful. And to my own
    eyes, it looks neater.  ;-)

    And before dxf yowls again: it is still Forth. :o)

    Well.. Technically everything written in Forth is Forth. But it is not
    canonical Forth - because if it were canonical Forth, we would have
    covered locals in "Starting Forth" - and we didn't.

    Now, let's assume we found we were wrong. But there was a chapter in
    "Thinking Forth" called "The stylish stack" - not "The stylish locals".
    As a matter of fact, it states that "the stack is not an array" -
    meaning: not randomly accessible. And what are locals? Right. Randomly
    accessible.

    So, what is this? It's a feeble imitation of C. It's not part of the
    original design. Because if it were part of the original design, you
    would find out what it means to think differently. This is merely C
    thinking. Nothing else. Certainly not Forth thinking.


    LOL ... I admit being a very non-canonical old guy :O)

    'Look, Ma - I've solved Forth's biggest problem.' ;-)

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Tue Jun 24 11:12:00 2025
    From Newsgroup: comp.lang.forth

    On 23-06-2025 20:48, LIT wrote:

    OK, have another song: Mr. FIFO stating that
    "arrays aren't variables" (maybe need a link?).
    Where did they taught you that? At that 'college'
    of yours, "elite programmer"? :D

    Oh honey, you don't understand? That's not a problem, hon. Go to mummy,
    she will explain it to you. But daddy doesn't have time for you. He's
    talking to the grown ups. Go play with your dolls and be a good girl!

    Hans Bezemer

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Kerr-Mudd, John@admin@127.0.0.1 to comp.lang.forth on Tue Jun 24 10:29:08 2025
    From Newsgroup: comp.lang.forth

    On Tue, 24 Jun 2025 11:12:00 +0200
    Hans Bezemer <the.beez.speaks@gmail.com> wrote:

    On 23-06-2025 20:48, LIT wrote:

    OK, have another song: Mr. FIFO stating that
    "arrays aren't variables" (maybe need a link?).
    Where did they taught you that? At that 'college'
    of yours, "elite programmer"? :D

    Oh honey, you don't understand? That's not a problem, hon. Go to mummy,
    she will explain it to you. But daddy doesn't have time for you. He's talking to the grown ups. Go play with your dolls and be a good girl!

    Please, give up the insults; let your coding skills do the talking.
    --
    Bah, and indeed Humbug.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Tue Jun 24 11:30:35 2025
    From Newsgroup: comp.lang.forth

    On 24-06-2025 07:31, dxf wrote:
    On 24/06/2025 10:42 am, minforth wrote:
    On Mon, 23 Jun 2025 21:20:46 +0000, Hans Bezemer wrote:

    On 23-06-2025 23:03, minforth wrote:
    On Mon, 23 Jun 2025 5:18:34 +0000, Anton Ertl wrote:

    minforth@gmx.net (minforth) writes:
    So, I made me a small extension to the locals word set. Using your >>>>>> example SPIN (abc — cba), I can define it as follows:
    : SPIN { a b c == c b a } ; \ no need for additional code before ;

    What is the advantage of using this extension over the Forth-2012:

    : spin {: a b c :} c b a ;

    ?

    Obviously, there is no advantage for such small definitions.

    For me, the small syntax extension is a convenience when working
    with longer definitions. A bit contrived (:= synonym for TO):

    : SOME-APP { a f: b c | temp == n: flag z: freq }
    \ inputs: integer a, floats b c
    \ uninitialized: float temp
    \ outputs: integer flag, complex freq
      <: FUNC < ... calc function ... > ;>
    \ emulated embedded function using { | xt: func }
      < ... calc something ... > := temp
      < ... calc other things ... > := freq  / basic formula
      < ... calc other things ... > := flag
      < ... calc correction ... > := freq  / better estimation
    ;

    While working on such things, I can focus my eyes on the formulas,
    all local values are visible in one place, and I don't have to
    worry about tracking the data stack(s) for lost/accumulated items.

    As I said, it is nothing spectacular, just helpful. And to my own
    eyes, it looks neater.  ;-)

    And before dxf yowls again: it is still Forth. :o)

    Well.. Technically everything written in Forth is Forth. But it is not
    canonical Forth - because if it were canonical Forth, we would have
    covered locals in "Starting Forth" - and we didn't.

    Now, let's assume we found we were wrong. But there was a chapter in
    "Thinking Forth" called "The stylish stack" - not "The stylish locals".
    As a matter of fact, it states that "the stack is not an array" -
    meaning: not randomly accessible. And what are locals? Right. Randomly
    accessible.

    So, what is this? It's a feeble imitation of C. It's not part of the
    original design. Because if it were part of the original design, you
    would find out what it means to think differently. This is merely C
    thinking. Nothing else. Certainly not Forth thinking.


    LOL ... I admit being a very non-canonical old guy :O)

    'Look, Ma - I've solved Forth's biggest problem.' ;-)

    No really, I'm not kidding. When done properly Forth actually changes
    the way you work. Fundamentally. I explained the sensation at the end of
    "Why Choose Forth". I've been able to tackle things I would never have
    been to tackle with a C mindset. ( https://youtu.be/MXKZPGzlx14 )

    Like I always wanted to do a real programming language - no matter how primitive. Now I've done at least a dozen - and that particular trick
    seems to get easier by the day.

    And IMHO a lot can be traced back to the very simple principles Forth is
    based upon - like a stack. Or the triad "Execute-Number-Error". Or the dictionary. But also the lessons from ThinkForth.

    You'll also find it in my C work. There are a lot more "small functions"
    than in your average C program. It works for me like an "inner API". Not
    to mention uBasic/4tH - There are plenty of "one-liners" in my
    uBasic/4tH programs.

    But that train of thought needs to be maintained - and it can only be maintained by submitting to the very philosophy Forth was built upon. I
    feel like if I would give in to locals, I'd be back to being an average
    C programmer.

    I still do C from time to time - but it's not my prime language. For
    this reason - and because I'm often just plain faster when using Forth.
    It just results in a better program.

    The only thing I can say is, "it works for me". And when I sometimes
    view the works of others - especially when resorting to a C style - I
    feel like it could work for you as well.

    Nine times out of ten one doesn't need the amount of locals which are
    applied. One doesn't need a 16 line word - at least not when you
    actually want to maintain the darn thing. One could tackle the problem
    much more elegant.

    It's that feeling..

    Hans Bezemer

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net (minforth) to comp.lang.forth on Tue Jun 24 11:50:30 2025
    From Newsgroup: comp.lang.forth

    On Tue, 24 Jun 2025 9:30:35 +0000, Hans Bezemer wrote:
    'Look, Ma - I've solved Forth's biggest problem.' ;-)

    No really, I'm not kidding. When done properly Forth actually changes
    the way you work. Fundamentally. I explained the sensation at the end of
    "Why Choose Forth". I've been able to tackle things I would never have
    been to tackle with a C mindset. ( https://youtu.be/MXKZPGzlx14 )

    Like I always wanted to do a real programming language - no matter how primitive. Now I've done at least a dozen - and that particular trick
    seems to get easier by the day.

    And IMHO a lot can be traced back to the very simple principles Forth is based upon - like a stack. Or the triad "Execute-Number-Error". Or the dictionary. But also the lessons from ThinkForth.

    You'll also find it in my C work. There are a lot more "small functions"
    than in your average C program. It works for me like an "inner API". Not
    to mention uBasic/4tH - There are plenty of "one-liners" in my
    uBasic/4tH programs.

    But that train of thought needs to be maintained - and it can only be maintained by submitting to the very philosophy Forth was built upon. I
    feel like if I would give in to locals, I'd be back to being an average
    C programmer.

    I still do C from time to time - but it's not my prime language. For
    this reason - and because I'm often just plain faster when using Forth.
    It just results in a better program.

    The only thing I can say is, "it works for me". And when I sometimes
    view the works of others - especially when resorting to a C style - I
    feel like it could work for you as well.

    Nine times out of ten one doesn't need the amount of locals which are applied. One doesn't need a 16 line word - at least not when you
    actually want to maintain the darn thing. One could tackle the problem
    much more elegant.

    It's that feeling..

    Why make everything so complicated? An electrician's toolbox looks
    different from a horse smith's toolbox. You sound like a horse smith
    who frowns at the electrician's toolbox and the electrician's
    “philosophy”.

    But to each his own - make love not war. :o)

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Tue Jun 24 14:00:19 2025
    From Newsgroup: comp.lang.forth

    On 24-06-2025 11:29, Kerr-Mudd, John wrote:
    On Tue, 24 Jun 2025 11:12:00 +0200
    Hans Bezemer <the.beez.speaks@gmail.com> wrote:

    On 23-06-2025 20:48, LIT wrote:

    OK, have another song: Mr. FIFO stating that
    "arrays aren't variables" (maybe need a link?).
    Where did they taught you that? At that 'college'
    of yours, "elite programmer"? :D

    Oh honey, you don't understand? That's not a problem, hon. Go to mummy,
    she will explain it to you. But daddy doesn't have time for you. He's
    talking to the grown ups. Go play with your dolls and be a good girl!

    Please, give up the insults; let your coding skills do the talking.

    Note I didn't make it personal. I even pointed out it simply constitutes
    a a bunch of logical fallacies - and a violation of "Grahams triangle of disagreement". But school girls are obviously hard of hearing ;-)

    Hans Bezemer

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Tue Jun 24 14:12:08 2025
    From Newsgroup: comp.lang.forth

    On 24-06-2025 13:50, minforth wrote:
    On Tue, 24 Jun 2025 9:30:35 +0000, Hans Bezemer wrote:
    'Look, Ma - I've solved Forth's biggest problem.' ;-)

    No really, I'm not kidding. When done properly Forth actually changes
    the way you work. Fundamentally. I explained the sensation at the end of
    "Why Choose Forth". I've been able to tackle things I would never have
    been to tackle with a C mindset. ( https://youtu.be/MXKZPGzlx14 )

    Like I always wanted to do a real programming language - no matter how
    primitive. Now I've done at least a dozen - and that particular trick
    seems to get easier by the day.

    And IMHO a lot can be traced back to the very simple principles Forth is
    based upon - like a stack. Or the triad "Execute-Number-Error". Or the
    dictionary. But also the lessons from ThinkForth.

    You'll also find it in my C work. There are a lot more "small functions"
    than in your average C program. It works for me like an "inner API". Not
    to mention uBasic/4tH - There are plenty of "one-liners" in my
    uBasic/4tH programs.

    But that train of thought needs to be maintained - and it can only be
    maintained by submitting to the very philosophy Forth was built upon. I
    feel like if I would give in to locals, I'd be back to being an average
    C programmer.

    I still do C from time to time - but it's not my prime language. For
    this reason - and because I'm often just plain faster when using Forth.
    It just results in a better program.

    The only thing I can say is, "it works for me". And when I sometimes
    view the works of others - especially when resorting to a C style - I
    feel like it could work for you as well.

    Nine times out of ten one doesn't need the amount of locals which are
    applied. One doesn't need a 16 line word - at least not when you
    actually want to maintain the darn thing. One could tackle the problem
    much more elegant.

    It's that feeling..

    Why make everything so complicated? An electrician's toolbox looks
    different from a horse smith's toolbox. You sound like a horse smith
    who frowns at the electrician's toolbox and the electrician's “philosophy”.

    Yes, that's why we have languages like Forth and C - each with its own philosophy.

    The point is, I think there is not enough respect for the Forth
    philosophy. It's even publicly denied there is such a philosophy at all.
    Or that there are actual, measurable benefits to that philosophy.

    And that's the core of the issue, I think.

    I'm also puzzled why there is always so emphasis on the "speed" issue. I
    mean - if you want speed, do your program in C -O3 so to say. It'll blow
    any Forth out of the water. Now I know that there are people concerned
    with optimizing Python, but I frown on that as well.

    I don't mean to say you should close every window to optimization, but
    at least admit to one another - it's a secondary problem with Forth.

    But to each his own - make love not war. :o)

    I'm all for a civil discussion, fully agreed! ;-)

    Hans Bezemer

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Tue Jun 24 16:23:19 2025
    From Newsgroup: comp.lang.forth

    Hans Bezemer <the.beez.speaks@gmail.com> writes:
    I'm also puzzled why there is always so emphasis on the "speed" issue. I >mean - if you want speed, do your program in C -O3 so to say. It'll blow
    any Forth out of the water.

    Take a look at the bubble benchmark in Figure 1 of <https://www.complang.tuwien.ac.at/papers/ertl24-interpreter-speed.pdf>. SwiftForth, VFX, and Gforth with all optimizations (the baseline) are
    faster than gcc-12 -O3. The reason for that is:

    |For bubble, gcc -O3 auto-vectorizes, and the result is that there is
    |partial overlap between a store and a following load, which results
    |in the hardware taking a slow path rather than performing one of its |store-to-load forwarding optimizations.

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2023 proceedings: http://www.euroforth.org/ef23/papers/
    EuroForth 2024 proceedings: http://www.euroforth.org/ef24/papers/
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Tue Jun 24 16:37:05 2025
    From Newsgroup: comp.lang.forth

    minforth@gmx.net (minforth) writes:
    On Mon, 23 Jun 2025 5:18:34 +0000, Anton Ertl wrote:

    minforth@gmx.net (minforth) writes:
    So, I made me a small extension to the locals word set. Using your >>>example SPIN (abc — cba), I can define it as follows:
    : SPIN { a b c == c b a } ; \ no need for additional code before ;

    What is the advantage of using this extension over the Forth-2012:

    : spin {: a b c :} c b a ;

    ?

    Obviously, there is no advantage for such small definitions.

    For me, the small syntax extension is a convenience when working
    with longer definitions. A bit contrived (:= synonym for TO):

    : SOME-APP { a f: b c | temp == n: flag z: freq }
    \ inputs: integer a, floats b c
    \ uninitialized: float temp
    \ outputs: integer flag, complex freq
    <: FUNC < ... calc function ... > ;>
    \ emulated embedded function using { | xt: func }
    < ... calc something ... > := temp
    < ... calc other things ... > := freq / basic formula
    < ... calc other things ... > := flag
    < ... calc correction ... > := freq / better estimation
    ;

    That's somewhat like Tevet's idea:

    @Article{tevet89,
    author = "Adin Tevet",
    title = "Symbolic Stack Addressing",
    journal = jfar,
    year = "1989",
    volume = "5",
    number = "3",
    pages = "365--379",
    url = "http://soton.mpeforth.com/flag/jfar/vol5/no3/article2.pdf",
    annote = "A local variable mechanism that uses the data stack
    for storage. The variables are accessed by {\tt PICK}
    and {\tt POST} (its opposite), which means that the
    compiler must keep track of the stack depth. Includes
    source code for 8086 F83."
    }

    However, I find that I don't need to decouple at the start *and* the
    end. If I have a word with the stack effect ( a b c -- d e ), it's
    usually straightforward to write it as:

    : myword1 {: a b c -- d e :}
    ... compute d ... ( d )
    ... compute e ... ( d e ) ;

    And if that is not possible, you can do it as follows:

    : myword3 {: a b c -- d e :}
    ... compute e ... {: e :}
    ... compute d ... ( d ) e ;

    or just

    : myword2 {: a b c -- d e :}
    ... compute e ... ( e )
    ... compute d ... ( e d )
    swap ;

    Or if you really want to make the output explict, you could also write
    it as follows:

    : myword4 {: a b c -- d e :}
    ... compute e ... {: e :}
    ... compute d ... {: d :}
    d e ;

    And of course, there are also many cases where the data flow is simple
    enough that using the stacks is sufficient.

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2023 proceedings: http://www.euroforth.org/ef23/papers/
    EuroForth 2024 proceedings: http://www.euroforth.org/ef24/papers/
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Wed Jun 25 13:27:33 2025
    From Newsgroup: comp.lang.forth

    On 24/06/2025 7:30 pm, Hans Bezemer wrote:
    ...
    You'll also find it in my C work. There are a lot more "small functions" than in your average C program. It works for me like an "inner API". Not to mention uBasic/4tH - There are plenty of "one-liners" in my uBasic/4tH programs.

    But that train of thought needs to be maintained - and it can only be maintained by submitting to the very philosophy Forth was built upon. I feel like if I would give in to locals, I'd be back to being an average C programmer.

    Forth forces an average programmer to adopt a level of organisation sooner than a locals-
    based language. I suspect forthers that promote locals are well aware forth is readable
    and maintainable but are pursuing personal agendas of style which requires implying the
    opposite. Why do I think so? Because even when they use locals they still try to be
    Forth-ish and keep definitions short. They know it's impossible to sell long definitions
    to a Forth programmer.

    I've seen Forth applications written by the proverbial C programmer. Curiously no locals
    were used - perhaps because the programmer was seriously attempting to try out Forth.
    It may have been on the bucket list as he doesn't appear to have pursued it. What gave it
    away was the length of definitions which averaged 20 lines. There were occasional whoppers,
    60 and 200 lines. Even though code had been carefully indented to be readable, it would
    likely horrify the average Forth programmer. In short, it lacked Forth sensibility. And
    I think it's the latter that we're talking about in all these discussions.

    ...
    Nine times out of ten one doesn't need the amount of locals which are applied. One doesn't need a 16 line word - at least not when you actually want to maintain the darn thing. One could tackle the problem much more elegant.

    It's that feeling..

    Agreed

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Paul Rubin@no.email@nospam.invalid to comp.lang.forth on Tue Jun 24 22:38:33 2025
    From Newsgroup: comp.lang.forth

    dxf <dxforth@gmail.com> writes:
    Forth forces an average programmer to adopt a level of organisation
    sooner than a locals- based language. I suspect forthers that promote
    locals are well aware forth is readable and maintainable but are
    pursuing personal agendas of style which requires implying the
    opposite.

    IDK, I've seen some unreadable Forth code that was written by experts.
    Whether locals could have helped, I don't know.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Paul Rubin@no.email@nospam.invalid to comp.lang.forth on Wed Jun 25 00:21:23 2025
    From Newsgroup: comp.lang.forth

    Hans Bezemer <the.beez.speaks@gmail.com> writes:
    Fundamentally. I explained the sensation at the end
    of "Why Choose Forth". I've been able to tackle things I would never
    have been to tackle with a C mindset. ( https://youtu.be/MXKZPGzlx14 )

    I just watched this video and enjoyed it, but I don't understand how a C mindset is different. In C you pass stuff as function parameters
    instead of on the stack: what's the big deal? And particularly, the
    video said nothing about the burning question of locals ;).

    It seems to me all the examples mentioned in the video (parsing CSV
    files or floating point numerals) are what someone called
    micro-problems. Today they much easier with languages like Python, and
    back in Forth's heyday there was Lisp, which occupied a mindspace like
    Python does now.

    I agree that Thinking Forth is a great book.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From albert@albert@spenarnc.xs4all.nl to comp.lang.forth on Wed Jun 25 11:54:44 2025
    From Newsgroup: comp.lang.forth

    In article <nnd$34fd6cd6$25a88dac@ac6bb1addf3a4136>,
    Hans Bezemer <the.beez.speaks@gmail.com> wrote:
    On 24-06-2025 13:50, minforth wrote:
    On Tue, 24 Jun 2025 9:30:35 +0000, Hans Bezemer wrote:
    'Look, Ma - I've solved Forth's biggest problem.' ;-)

    No really, I'm not kidding. When done properly Forth actually changes
    the way you work. Fundamentally. I explained the sensation at the end of >>> "Why Choose Forth". I've been able to tackle things I would never have
    been to tackle with a C mindset. ( https://youtu.be/MXKZPGzlx14 )

    Like I always wanted to do a real programming language - no matter how
    primitive. Now I've done at least a dozen - and that particular trick
    seems to get easier by the day.

    And IMHO a lot can be traced back to the very simple principles Forth is >>> based upon - like a stack. Or the triad "Execute-Number-Error". Or the
    dictionary. But also the lessons from ThinkForth.

    You'll also find it in my C work. There are a lot more "small functions" >>> than in your average C program. It works for me like an "inner API". Not >>> to mention uBasic/4tH - There are plenty of "one-liners" in my
    uBasic/4tH programs.

    But that train of thought needs to be maintained - and it can only be
    maintained by submitting to the very philosophy Forth was built upon. I
    feel like if I would give in to locals, I'd be back to being an average
    C programmer.

    I still do C from time to time - but it's not my prime language. For
    this reason - and because I'm often just plain faster when using Forth.
    It just results in a better program.

    The only thing I can say is, "it works for me". And when I sometimes
    view the works of others - especially when resorting to a C style - I
    feel like it could work for you as well.

    Nine times out of ten one doesn't need the amount of locals which are
    applied. One doesn't need a 16 line word - at least not when you
    actually want to maintain the darn thing. One could tackle the problem
    much more elegant.

    It's that feeling..

    Why make everything so complicated? An electrician's toolbox looks
    different from a horse smith's toolbox. You sound like a horse smith
    who frowns at the electrician's toolbox and the electrician's
    “philosophy”.

    Yes, that's why we have languages like Forth and C - each with its own >philosophy.

    The point is, I think there is not enough respect for the Forth
    philosophy. It's even publicly denied there is such a philosophy at all.
    Or that there are actual, measurable benefits to that philosophy.

    And that's the core of the issue, I think.

    I'm also puzzled why there is always so emphasis on the "speed" issue. I
    mean - if you want speed, do your program in C -O3 so to say. It'll blow
    any Forth out of the water. Now I know that there are people concerned
    with optimizing Python, but I frown on that as well.

    Me too. Many posts post a speed for a program or snippet that they
    don't care to explain what it is good for.

    If you want to optimize (misnomer for "speed up") the word ALLOCATE
    just do
    'ALLOCATE OPTIMISED
    (This is ciforth: write on essay about this is far superior to the phrase "OPTIMISE ALLOCATE" )

    I have been writing an optimiser for some time now.
    It is on the backburner, partly because intel 86 is insane, mainly
    because it is not really needed. It is more of an academic exercise.
    (The byte sieve was optimised to vfxforth level, but honestly not
    much else.)
    Now riscv is the future. I have succeeded in my experimental optimiser
    to get rid of return stack storage (like for loops), and nesting overhead.
    I should use the same technique for the data stack, instead of transforming sequences of Intel instructions to smaller once and trying to get rid
    of the endless pops and pushes that way.

    Now I going to optimise riscv, with much more uniform registers to play
    with. And ditch github (USA) in favour of gitee (Chinese).
    USA is circling the drain.


    I don't mean to say you should close every window to optimization, but
    at least admit to one another - it's a secondary problem with Forth.

    But to each his own - make love not war. :o)

    I'm all for a civil discussion, fully agreed! ;-)

    Hans Bezemer


    Groetjes Albert
    --
    The Chinese government is satisfied with its military superiority over USA.
    The next 5 year plan has as primary goal to advance life expectancy
    over 80 years, like Western Europe.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From albert@albert@spenarnc.xs4all.nl to comp.lang.forth on Wed Jun 25 12:14:30 2025
    From Newsgroup: comp.lang.forth

    In article <87h6041iue.fsf@nightsong.com>,
    Paul Rubin <no.email@nospam.invalid> wrote:
    dxf <dxforth@gmail.com> writes:
    Forth forces an average programmer to adopt a level of organisation
    sooner than a locals- based language. I suspect forthers that promote
    locals are well aware forth is readable and maintainable but are
    pursuing personal agendas of style which requires implying the
    opposite.

    IDK, I've seen some unreadable Forth code that was written by experts. >Whether locals could have helped, I don't know.

    Maybe you are mistaken. I have seen unmaintainable code written by
    some self-proclaimed experts.
    I have not seen unmaintainable code written by real experts.
    I have seen a lot of code. 70% of my 40+ years was spent on removing
    defects or enhancing existing code.

    There is a problem with the word unreadable. The 800 page proof
    of the Fermat theorem is unreadable. At first sight my manx code
    is unreadable. I read children stories in Chinese, to most Westerners
    they are unreadable.

    The story goes that a Boeing doesn't fly until the documentation weight
    rivals that of the airplane. I was in the middle of such a process in
    Dutch railway design where safety matters.
    Pick a document of this gigantic pile and you can't make heads or tails
    of it.
    Or get the deepseek seminal publication. The only thing that most people understand is the "11 million dollars" some how spent.

    Groetjes Albert
    --
    The Chinese government is satisfied with its military superiority over USA.
    The next 5 year plan has as primary goal to advance life expectancy
    over 80 years, like Western Europe.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Paul Rubin@no.email@nospam.invalid to comp.lang.forth on Wed Jun 25 21:01:05 2025
    From Newsgroup: comp.lang.forth

    albert@spenarnc.xs4all.nl writes:
    with. And ditch github (USA) in favour of gitee (Chinese).
    USA is circling the drain.

    Try codeberg.org (Germany) maybe.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Paul Rubin@no.email@nospam.invalid to comp.lang.forth on Wed Jun 25 21:05:15 2025
    From Newsgroup: comp.lang.forth

    albert@spenarnc.xs4all.nl writes:
    Maybe you are mistaken. I have seen unmaintainable code written by
    some self-proclaimed experts.
    I have not seen unmaintainable code written by real experts.

    IDK about unmaintainable by other experts, but I've looked at cmForth
    (written by Moore) and figForth (written I guess by Bill Ragsdale) and
    found both incomprehensible. If those guys aren't experts then the bar
    must be pretty high. I do find eForth readable.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Thu Jun 26 14:48:11 2025
    From Newsgroup: comp.lang.forth

    On 25/06/2025 3:38 pm, Paul Rubin wrote:
    dxf <dxforth@gmail.com> writes:
    Forth forces an average programmer to adopt a level of organisation
    sooner than a locals- based language. I suspect forthers that promote
    locals are well aware forth is readable and maintainable but are
    pursuing personal agendas of style which requires implying the
    opposite.

    IDK, I've seen some unreadable Forth code that was written by experts. Whether locals could have helped, I don't know.

    Define 'unreadable'. In general I don't need to understand the nitty
    gritty of a routine. But should I and no stack commentary exists, I've
    no objections to creating it. It's par for the course in Forth. If it
    bugged me I wouldn't be doing Forth.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From antispam@antispam@fricas.org (Waldek Hebisch) to comp.lang.forth on Thu Jun 26 05:20:13 2025
    From Newsgroup: comp.lang.forth

    Hans Bezemer <the.beez.speaks@gmail.com> wrote:

    No really, I'm not kidding. When done properly Forth actually changes
    the way you work. Fundamentally. I explained the sensation at the end of "Why Choose Forth". I've been able to tackle things I would never have
    been to tackle with a C mindset. ( https://youtu.be/MXKZPGzlx14 )

    I do not look at videos (mostly because they are extremally wasteful
    way of transmiting concepts, with words once can do this faster).
    So I will comment mostly on what you wrote.

    Like I always wanted to do a real programming language - no matter how primitive. Now I've done at least a dozen - and that particular trick
    seems to get easier by the day.

    I am not sure what you mean "do a real programming language".
    I have written compilers. The ones where I did all the work
    I consider to be toys. But I am pretty confident that if
    I wanted I could extend them to a practical language. I also
    work on real compilers, but here majority of work was done by
    other people and I only worked on parts. Still, while in
    a single compiler "my" part (or parts) are minority, they
    together cover all stages of practical compiler.

    I did not write a serious interpreter or even a part of it
    but I looked at code in several interpreters and I think that
    I understand subject well enough to write on if needed.

    And IMHO a lot can be traced back to the very simple principles Forth is based upon - like a stack. Or the triad "Execute-Number-Error". Or the dictionary. But also the lessons from ThinkForth.

    Traditional way to implement Forth is just one way. It is
    relatively simple, so this may be attractive. But I would
    say not the simplest one: bytecode interpreters are less
    clever, so in a sense simpler (at cost of slower execution).
    Compilers generating native code can be simple too, and
    one can argue that they also need less cleverness than Forth
    (but probably more object code).

    You'll also find it in my C work. There are a lot more "small functions" than in your average C program. It works for me like an "inner API". Not
    to mention uBasic/4tH - There are plenty of "one-liners" in my
    uBasic/4tH programs.

    But that train of thought needs to be maintained - and it can only be maintained by submitting to the very philosophy Forth was built upon. I
    feel like if I would give in to locals, I'd be back to being an average
    C programmer.

    I still do C from time to time - but it's not my prime language. For
    this reason - and because I'm often just plain faster when using Forth.
    It just results in a better program.

    My philosophy for developing programs is "follow the problem".
    That is we a problem to solve (task to do). We need to
    understand it, introduce some data structures and specify
    needed computation. This is mostly independent from programming
    language. When problem is not well understood we need
    to do some research. In this experiments may help a lot
    and having interactive programming language in useful
    (so this is plus of Forth compared to C). Once we have
    data structures and know what computation is needed we
    need to encode (represent) this in choosen language.
    I would say that large scale structure of the program
    will be mostly independent of programming language.
    There will be differences at small scale, as different
    languages have different idioms. "Builtin" features of
    language or "standard" libraries may do significant
    part of work. Effort of coding may vary widely,
    depending how much is supported by the language and
    surroundig ecosystem and how much must be newly
    coded. Also, debugging features of programming
    system affect speed of coding.

    Frankly, I do not see how missing language features
    can improve design. I mean, there are people who
    try to use fancy features when thay are not needed.
    But large scale structure of a program should not be
    affected by this. And at smaller scale with some
    experience it is not hard to avoid unneeded features.
    I would say that there are natural way to approach
    given problem and usually best program is one that
    follows natural way. Now, if problem naturally needs
    several interdependent attributes we need to represnt
    them in some way. If dependence is naturaly in stack
    way, than stack is a good fit. If dependence is not
    naturaly in a stack way, using stack may be possible
    after some reorganisation. But may experience is
    that if a given structure does not naturally appear
    after some research, than reorganisation is not
    very likely to lead to such structure. And even if
    one mananges to tweak program to such structure, it
    is not clear if it is a gain. Anyway, there is substantial
    number of problem where stack is unlikely to work in
    natural way. So how to represnt attributes? If they
    are needed only inside a single function, than natural
    way is using local variables. One can use globals, but
    for variables that are not needed outside a function
    this in unnatural. One can use stack juggling, this
    works, but IMO is unnatural. One can collect attributes
    in a single structure dynamically allocated at
    function entry and freed at exit. This works, but
    again is unnatural and needs extra code.

    Of course, sometimes other solutions are possible. Maybe
    instead of separate variables one can recompute attributes
    from something more basic. Maybe some group of attributes
    is needed in several functions, then keeping them as part
    of single structure is natural. But assuming that you
    write program in natural way, you would choose alternative
    what it is natural and choose locals only when thay
    are a good fit.

    You have some point about length of functions. While
    pretty small functions using locals are possible, I
    have a few longer functions where main reason for keeping
    code in one function is because various parts need access
    to the same local variables. But I doubt that eliminating
    locals and splitting such functions leads to better code:
    we get a cluster of function which depend via common
    attibutes. This dependence is there regardless of having
    single bigger function or several smaller ones (and
    regardless how one represents attributes). But with a
    single function dependence is explict, and for me easier
    to manage.

    Avoiding dependence helps, but above I mean unavoidable
    dependence. And in fact, I find locals useful to avoid
    false dependencies (where a buch of functons look like
    they depend on something but in fact they do not).

    I still do C from time to time - but it's not my prime language. For
    this reason - and because I'm often just plain faster when using Forth.
    It just results in a better program.

    The only thing I can say is, "it works for me". And when I sometimes
    view the works of others - especially when resorting to a C style - I
    feel like it could work for you as well.

    Nine times out of ten one doesn't need the amount of locals which are applied. One doesn't need a 16 line word - at least not when you
    actually want to maintain the darn thing. One could tackle the problem
    much more elegant.

    My policy is that variable should be a single logical thing.
    Which means that frequently I have more variables than
    "strictly necessary". That is I do not reuse variable for
    different purpose even if that would be possible. IMO
    saving here are compiler job, and in case when compiler is
    not doing this savings are not worth extra effort (and
    IMO worse program structure). Not that in reasonable program
    we are talking here about something like say 100 words
    or maybe 1000 words which may be significant on a small
    embedded system (but compilers for such system are reasonably
    good at reusing variables), but is irrelevant for bigger systems.
    --
    Waldek Hebisch
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Paul Rubin@no.email@nospam.invalid to comp.lang.forth on Thu Jun 26 00:12:41 2025
    From Newsgroup: comp.lang.forth

    dxf <dxforth@gmail.com> writes:
    Define 'unreadable'. In general I don't need to understand the nitty
    gritty of a routine. But should I and no stack commentary exists, I've
    no objections to creating it. It's par for the course in Forth. If it bugged me I wouldn't be doing Forth.

    Unreadable = I look at the code and have no idea what it's doing. The
    logic is often obscured by stack manipulation. The values in the stack
    are meaningful to the program's operation, but what is the meaning? In
    most languages, meaningful values have names, and the names convey the
    meaning. In Forth, you can write comments for that purpose. Years
    after cmForth was published, someone wrote a set of shadow screens for
    it, and that helped a lot.

    With no named values and no explanatory comments, the program becomes
    opaque.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net (minforth) to comp.lang.forth on Thu Jun 26 17:35:23 2025
    From Newsgroup: comp.lang.forth

    On Thu, 26 Jun 2025 5:20:13 +0000, Waldek Hebisch wrote:
    My philosophy for developing programs is "follow the problem".
    That is we a problem to solve (task to do). We need to
    understand it, introduce some data structures and specify
    needed computation. This is mostly independent from programming
    language. When problem is not well understood we need
    to do some research. In this experiments may help a lot
    and having interactive programming language in useful
    (so this is plus of Forth compared to C). Once we have
    data structures and know what computation is needed we
    need to encode (represent) this in choosen language.
    I would say that large scale structure of the program
    will be mostly independent of programming language.
    There will be differences at small scale, as different
    languages have different idioms. "Builtin" features of
    language or "standard" libraries may do significant
    part of work. Effort of coding may vary widely,
    depending how much is supported by the language and
    surroundig ecosystem and how much must be newly
    coded. Also, debugging features of programming
    system affect speed of coding.

    Frankly, I do not see how missing language features
    can improve design. I mean, there are people who
    try to use fancy features when thay are not needed.
    But large scale structure of a program should not be
    affected by this. And at smaller scale with some
    experience it is not hard to avoid unneeded features.
    I would say that there are natural way to approach
    given problem and usually best program is one that
    follows natural way. Now, if problem naturally needs
    several interdependent attributes we need to represnt
    them in some way. If dependence is naturaly in stack
    way, than stack is a good fit. If dependence is not
    naturaly in a stack way, using stack may be possible
    after some reorganisation. But may experience is
    that if a given structure does not naturally appear
    after some research, than reorganisation is not
    very likely to lead to such structure. And even if
    one mananges to tweak program to such structure, it
    is not clear if it is a gain. Anyway, there is substantial
    number of problem where stack is unlikely to work in
    natural way. So how to represnt attributes? If they
    are needed only inside a single function, than natural
    way is using local variables. One can use globals, but
    for variables that are not needed outside a function
    this in unnatural. One can use stack juggling, this
    works, but IMO is unnatural. One can collect attributes
    in a single structure dynamically allocated at
    function entry and freed at exit. This works, but
    again is unnatural and needs extra code.

    You have some point about length of functions. While
    pretty small functions using locals are possible, I
    have a few longer functions where main reason for keeping
    code in one function is because various parts need access
    to the same local variables. But I doubt that eliminating
    locals and splitting such functions leads to better code:
    we get a cluster of function which depend via common
    attibutes.

    These are my observations as well. It all depends on the problem
    that you are facing. Now there are some guys who behave
    like self-declared Forth mullahs who shout heresy against
    those who don't DUP ROT enough.

    Is theirs the Forth philosophy?? Really?? I thought the main
    Forth principle was "keep it simple". When stack reordering
    is the easier way, do it. When using locals is the easier way,
    do it. If a few helper words make it easier, use them.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Thu Jun 26 18:18:56 2025
    From Newsgroup: comp.lang.forth

    These are my observations as well. It all depends on the problem
    that you are facing. Now there are some guys who behave
    like self-declared Forth mullahs who shout heresy against
    those who don't DUP ROT enough.

    I realizad that (fortunately) long ago - actually
    Stephen Pelc made me realized that (thanks) - see
    the old thread "Vector additon" here:

    https://groups.google.com/g/comp.lang.forth/c/m9xy5k5BfkY/m/qoq664B9IygJ

    ..and in particular this message:

    https://groups.google.com/g/comp.lang.forth/c/m9xy5k5BfkY/m/-SIr9AqdiRsJ

    Anyway if anyone decided to become "the best
    stack acrobat anywhere", in some strange
    belief, that this is "the most correct way
    ('canonical') of Forth programming in the
    world" - and to produce as much "stack noise",
    as possible - it's his problem, not mine.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net (minforth) to comp.lang.forth on Fri Jun 27 00:50:29 2025
    From Newsgroup: comp.lang.forth

    On Thu, 26 Jun 2025 18:18:56 +0000, LIT wrote:

    These are my observations as well. It all depends on the problem
    that you are facing. Now there are some guys who behave
    like self-declared Forth mullahs who shout heresy against
    those who don't DUP ROT enough.

    I realizad that (fortunately) long ago - actually
    Stephen Pelc made me realized that (thanks) - see
    the old thread "Vector additon" here:

    https://groups.google.com/g/comp.lang.forth/c/m9xy5k5BfkY/m/qoq664B9IygJ

    ...and in particular this message:

    https://groups.google.com/g/comp.lang.forth/c/m9xy5k5BfkY/m/-SIr9AqdiRsJ

    Vector addition, particularly dot products (used in matrix
    multiplication),
    can produce nasty results due to rounding error accumulation.

    My solution was to create a special Kahan summation primitive: https://en.wikipedia.org/wiki/Kahan_summation_algorithm

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Fri Jun 27 11:39:43 2025
    From Newsgroup: comp.lang.forth

    On 26/06/2025 5:12 pm, Paul Rubin wrote:
    dxf <dxforth@gmail.com> writes:
    Define 'unreadable'. In general I don't need to understand the nitty
    gritty of a routine. But should I and no stack commentary exists, I've
    no objections to creating it. It's par for the course in Forth. If it
    bugged me I wouldn't be doing Forth.

    Unreadable = I look at the code and have no idea what it's doing. The
    logic is often obscured by stack manipulation. The values in the stack
    are meaningful to the program's operation, but what is the meaning? In
    most languages, meaningful values have names, and the names convey the meaning. In Forth, you can write comments for that purpose. Years
    after cmForth was published, someone wrote a set of shadow screens for
    it, and that helped a lot.

    With no named values and no explanatory comments, the program becomes
    opaque.

    Yet forthers have no problem with this. Take the SwiftForth source code.
    At best you'll get a general comment as to what a function does. How do
    they maintain it - the same way anyone proficient in C maintains C code.
    Albert is correct. Familiarity is key to readability. That's not to say
    code deserving documentation shouldn't have it. OTOH one shouldn't be expecting documentation (including stack commentary) for what's an everyday affair in Forth.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Paul Rubin@no.email@nospam.invalid to comp.lang.forth on Thu Jun 26 21:03:46 2025
    From Newsgroup: comp.lang.forth

    dxf <dxforth@gmail.com> writes:
    Yet forthers have no problem with this. Take the SwiftForth source code.
    At best you'll get a general comment as to what a function does. How do
    they maintain it - the same way anyone proficient in C maintains C code.

    Certainly it was a Forther who found cmForth needed that extra
    documentation, and took the trouble to write it. C code as I mentioned partially self-documents because it uses named variables in places where
    Forth would have the value in an anonymous stack slot.

    I looked at some of the SwiftForth library code (the stuff on their web
    site) and I did find that pretty readable.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From albert@albert@spenarnc.xs4all.nl to comp.lang.forth on Fri Jun 27 15:15:38 2025
    From Newsgroup: comp.lang.forth

    In article <cdc7dfbc45ed94246aba7cb36c7272af7c6ba017@i2pn2.org>,
    dxf <dxforth@gmail.com> wrote:
    On 26/06/2025 5:12 pm, Paul Rubin wrote:
    dxf <dxforth@gmail.com> writes:
    Define 'unreadable'. In general I don't need to understand the nitty
    gritty of a routine. But should I and no stack commentary exists, I've
    no objections to creating it. It's par for the course in Forth. If it
    bugged me I wouldn't be doing Forth.

    Unreadable = I look at the code and have no idea what it's doing. The
    logic is often obscured by stack manipulation. The values in the stack
    are meaningful to the program's operation, but what is the meaning? In
    most languages, meaningful values have names, and the names convey the
    meaning. In Forth, you can write comments for that purpose. Years
    after cmForth was published, someone wrote a set of shadow screens for
    it, and that helped a lot.

    With no named values and no explanatory comments, the program becomes
    opaque.

    Yet forthers have no problem with this. Take the SwiftForth source code.
    At best you'll get a general comment as to what a function does. How do
    they maintain it - the same way anyone proficient in C maintains C code. >Albert is correct. Familiarity is key to readability. That's not to say >code deserving documentation shouldn't have it. OTOH one shouldn't be >expecting documentation (including stack commentary) for what's an everyday >affair in Forth.


    The comment about fig-Forth is incorrect. All snippets of code are
    at most 10 lines long, and the function is documented in the glossary.
    So a minimal comprehension of 8086 code is sufficient.
    OTOH, a Debian developer pointed me to a github archive from him
    as shining example.
    I studied it. Not a single source file contains a header what it
    was about. Moreover a global description was missing. I had no clue
    what the purpose of the program was. I lost a lot of trust in Debian.

    Groetjes Albert
    --
    The Chinese government is satisfied with its military superiority over USA.
    The next 5 year plan has as primary goal to advance life expectancy
    over 80 years, like Western Europe.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Sun Jun 29 15:13:14 2025
    From Newsgroup: comp.lang.forth

    minforth@gmx.net (minforth) writes:
    Now there are some guys who behave
    like self-declared Forth mullahs who shout heresy against
    those who don't DUP ROT enough.

    The more common complaint is that you use some feature they dislike
    (typically locals) when you would otherwise DUP ROT instead. But they
    then like to tell us that real Forthers can refactor the code such
    that the DUP ROT becomes unnecessary. The discussion often stops
    there. But in some cases, we also read the praises of using global
    variables. Why are locals bad in their opinion and global variables
    good?

    Is theirs the Forth philosophy?? Really?? I thought the main
    Forth principle was "keep it simple". When stack reordering
    is the easier way, do it. When using locals is the easier way,
    do it.

    The question here is: What is "it" that one should keep simple.

    One answer: Keep the Forth system simple (even at the cost of making
    Forth source code harder to write).

    Your answer is different: Keep the Forth source code simple (and you
    mean "easy to write").

    I think focusing on only one of these aspects does not minimize the
    overall complexity. And if somebody argues with simplicity but
    ignores the big picture, the argument has no merit.

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2023 proceedings: http://www.euroforth.org/ef23/papers/
    EuroForth 2024 proceedings: http://www.euroforth.org/ef24/papers/
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Sun Jun 29 17:13:45 2025
    From Newsgroup: comp.lang.forth

    The more common complaint is that you use some feature they dislike (typically locals) when you would otherwise DUP ROT instead.

    But aren't 'locals' actually PICK/ROLL in disguise?

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Mon Jun 30 04:49:26 2025
    From Newsgroup: comp.lang.forth

    On 30/06/2025 3:13 am, LIT wrote:
    The more common complaint is that you use some feature they dislike
    (typically locals) when you would otherwise DUP ROT instead.

    But aren't 'locals' actually PICK/ROLL in disguise?

    Do PICK/ROLL skim all the values off the stack and stuff them in
    variables to be later popped on and off the stack like a yo-yo?

    At this point they'll say they've optimized all that away (hopefully
    their compiler did). Moore will then tell them it makes no sense to
    optimize bad practice when one can employ good practice at the start.
    But hey, that'd be interfering with a person's freedom to do as he
    pleased.


    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Sun Jun 29 19:31:16 2025
    From Newsgroup: comp.lang.forth

    The more common complaint is that you use some feature they dislike
    (typically locals) when you would otherwise DUP ROT instead.

    But aren't 'locals' actually PICK/ROLL in disguise?

    Do PICK/ROLL skim all the values off the stack and stuff them in
    variables to be later popped on and off the stack like a yo-yo?

    At this point they'll say they've optimized all that away (hopefully
    their compiler did). Moore will then tell them it makes no sense to
    optimize bad practice when one can employ good practice at the start.
    But hey, that'd be interfering with a person's freedom to do as he
    pleased.

    This isn't an answer to my question. My question was (and is):

    Aren't 'locals' actually PICK/ROLL in disguise?

    I'm not against solving problems/tasks the way
    the particular programmer prefers. While I'm not
    using locals, still I'm not trying to tell anyone
    what to do (unless asked about this ofc.).

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Sun Jun 29 20:25:19 2025
    From Newsgroup: comp.lang.forth

    zbigniew2011@gmail.com (LIT) writes:
    The more common complaint is that you use some feature they dislike
    (typically locals) when you would otherwise DUP ROT instead.

    But aren't 'locals' actually PICK/ROLL in disguise?

    As far as the act of programming is concerned, no. If I would think
    about using PICK and ROLL, I would write the code that way.

    As far as the resulting source code is concerned, no. The code looks
    so different from code using PICK and ROLL, that I don't see any
    relation.

    As far as the compilation of code with locals is concerned, many
    systems put locals on the return stack (at least conceptually), or
    (Gforth) on a separate locals stack. So, if anything it's
    return-stack (or locals-stack) accesses in disguise.

    As far as the resulting code is concerned what that looks like depends
    on the code generator of the Forth system. In particular, ntf/lxf is analytical about the data stack *and* the return stack, and in one
    case (3DUP) compiled code using PICK and code using locals to the same
    machine code. However, even for ntf/lxf you can write code where the conceptual use of the return stack becomes reified.

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2023 proceedings: http://www.euroforth.org/ef23/papers/
    EuroForth 2024 proceedings: http://www.euroforth.org/ef24/papers/
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Paul Rubin@no.email@nospam.invalid to comp.lang.forth on Sun Jun 29 15:26:32 2025
    From Newsgroup: comp.lang.forth

    dxf <dxforth@gmail.com> writes:
    But aren't 'locals' actually PICK/ROLL in disguise?
    Do PICK/ROLL skim all the values off the stack and stuff them in
    variables to be later popped on and off the stack like a yo-yo?

    Locals can be (and I thought usually are) implemented with the
    equivalent of PICK and POST, on either the R stack or a separate L
    stack. ROLL is different, "n ROLL" actually shuffles n items around and
    in most situations seems kind of nuts.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From sean@sean@conman.org to comp.lang.forth on Mon Jun 30 01:43:24 2025
    From Newsgroup: comp.lang.forth

    It was thus said that the Great LIT <zbigniew2011@gmail.com> once stated:
    The more common complaint is that you use some feature they dislike
    (typically locals) when you would otherwise DUP ROT instead.

    But aren't 'locals' actually PICK/ROLL in disguise?

    In my implementation [1], it's a PICK off the return stack (technically,
    from a set point in the return stack) as locals aren't allowed to remain on
    the data stack per the ANS standard.

    -spc

    [1] <https://github.com/spc476/ANS-Forth>, specifically, forth.asm
    starting at line 7793.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Mon Jun 30 13:28:36 2025
    From Newsgroup: comp.lang.forth

    On 30/06/2025 5:31 am, LIT wrote:
    The more common complaint is that you use some feature they dislike
    (typically locals) when you would otherwise DUP ROT instead.

    But aren't 'locals' actually PICK/ROLL in disguise?

    Do PICK/ROLL skim all the values off the stack and stuff them in
    variables to be later popped on and off the stack like a yo-yo?

    At this point they'll say they've optimized all that away (hopefully
    their compiler did).  Moore will then tell them it makes no sense to
    optimize bad practice when one can employ good practice at the start.
    But hey, that'd be interfering with a person's freedom to do as he
    pleased.

    This isn't an answer to my question. My question was (and is):

    Aren't 'locals' actually PICK/ROLL in disguise?

    I'm not against solving problems/tasks the way
    the particular programmer prefers. While I'm not
    using locals, still I'm not trying to tell anyone
    what to do (unless asked about this ofc.).

    I explained how locals differ from PICK/ROLL. In addition there's
    no evidence PICK/ROLL is used frequently or held up as a solution.
    As you appear to see a connection, I was hoping you would explain it.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Mon Jun 30 13:37:43 2025
    From Newsgroup: comp.lang.forth

    On 30/06/2025 8:26 am, Paul Rubin wrote:
    dxf <dxforth@gmail.com> writes:
    But aren't 'locals' actually PICK/ROLL in disguise?
    Do PICK/ROLL skim all the values off the stack and stuff them in
    variables to be later popped on and off the stack like a yo-yo?

    Locals can be (and I thought usually are) implemented with the
    equivalent of PICK and POST, on either the R stack or a separate L
    stack. ROLL is different, "n ROLL" actually shuffles n items around and
    in most situations seems kind of nuts.

    PICK copies a stack item. Agree it and ROLL have limited use. OTOH
    SwiftForth has -ROLL and it was recently added to Mecrisp-Stellaris.
    What is POST ?

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Paul Rubin@no.email@nospam.invalid to comp.lang.forth on Sun Jun 29 23:18:56 2025
    From Newsgroup: comp.lang.forth

    dxf <dxforth@gmail.com> writes:
    What is POST ?

    Opposite of PICK. Overwrites a slot in the middle of the stack. I saw
    that name in another clf post pretty recently, idk if it is commonly implemented. I think I've also seen it called POKE. I'd call it
    barbaric from a stack programming perspective if done in user code, but
    if the compiler does it in some specific implementation, I don't mind.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Mon Jun 30 07:15:23 2025
    From Newsgroup: comp.lang.forth

    I explained how locals differ from PICK/ROLL. In addition there's
    no evidence PICK/ROLL is used frequently or held up as a solution.
    As you appear to see a connection, I was hoping you would explain it.

    Everyone is free to solve their problems
    the way they're most comfortable with - be
    it bezemerish string of DUP-SWAP-ROTs or
    PICK/ROLL.
    As for me, I'm convinced by this recommedation:

    "Pick and Roll are the generic operators which
    treat the data stack as an array. If you find
    you need to use them, you are probably doing
    it wrong. Look for ways to refactor your code
    to be simpler instead."

    In a way this statement can be extended to the
    use of local variables. Still, as I said, it's
    allowed. No need for "too ideological" approach
    if that works for the programmer, neither for
    insisting on "canonical" ways etc.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Mon Jun 30 19:07:35 2025
    From Newsgroup: comp.lang.forth

    On 30/06/2025 5:15 pm, LIT wrote:
    I explained how locals differ from PICK/ROLL.  In addition there's
    no evidence PICK/ROLL is used frequently or held up as a solution.
    As you appear to see a connection, I was hoping you would explain it.

    Everyone is free to solve their problems
    the way they're most comfortable with - be
    it bezemerish string of DUP-SWAP-ROTs or
    PICK/ROLL.
    As for me, I'm convinced by this recommedation:

    "Pick and Roll are the generic operators which
    treat the data stack as an array. If you find
    you need to use them, you are probably doing
    it wrong. Look for ways to refactor your code
    to be simpler instead."

    In a way this statement can be extended to the
    use of local variables. Still, as I said, it's
    allowed. No need for "too ideological" approach
    if that works for the programmer, neither for
    insisting on "canonical" ways etc.

    While many a stack op can be simulated using PICK and ROLL (hence CS-PICK CS-ROLL) I'm unaware of anyone using them in place of. If stack ops are "canonical" it's because nobody has found a more efficient way of programming
    a stack computer. Recognizing this as the fact and the reality, a programmer that's serious will deal with reality and not chase after ideology which is
    the province of thought.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Mon Jun 30 09:33:40 2025
    From Newsgroup: comp.lang.forth

    In a way this statement can be extended to the
    use of local variables. Still, as I said, it's
    allowed. No need for "too ideological" approach
    if that works for the programmer, neither for
    insisting on "canonical" ways etc.

    While many a stack op can be simulated using PICK and ROLL (hence
    CS-PICK
    CS-ROLL) I'm unaware of anyone using them in place of. If stack ops are "canonical" it's because nobody has found a more efficient way of
    programming
    a stack computer. Recognizing this as the fact and the reality, a
    programmer
    that's serious will deal with reality and not chase after ideology which
    is
    the province of thought.

    The stack ops THEMSELVES may be, in a way,
    "canonical" — but not solving "each and every"
    programming task using them "no-matter-what", IMHO.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Paul Rubin@no.email@nospam.invalid to comp.lang.forth on Mon Jun 30 02:44:35 2025
    From Newsgroup: comp.lang.forth

    zbigniew2011@gmail.com (LIT) writes:
    "Pick and Roll are the generic operators which treat the data stack as
    an array. If you find you need to use them, you are probably doing it
    wrong. Look for ways to refactor your code to be simpler instead."

    What is the origin of that quote? PICK treats the stack like an array,
    but ROLL treats it more as a circular shift register.

    Most CPUs these days have a register file, which is essentially an array
    with only immediate-like addressing mode. Presumably that design
    evolved because programmers found it useful.

    PICK afaict is mostly used with literal offsets as well. Having a
    variable offset is suspicious.

    : 3DUP ( a b c -- a b c a b c ) 3 PICK 3 PICK 3 PICK ;

    Seems clearer than some mess of ROT and return stack temporaries.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Mon Jun 30 09:52:41 2025
    From Newsgroup: comp.lang.forth

    On Mon, 30 Jun 2025 9:44:35 +0000, Paul Rubin wrote:

    zbigniew2011@gmail.com (LIT) writes:
    "Pick and Roll are the generic operators which treat the data stack as
    an array. If you find you need to use them, you are probably doing it
    wrong. Look for ways to refactor your code to be simpler instead."

    What is the origin of that quote?

    https://wiki.laptop.org/go/Forth_stack_operators
    (so probably Mitch Bradley must be the author)

    [..]
    : 3DUP ( a b c -- a b c a b c ) 3 PICK 3 PICK 3 PICK ;

    Seems clearer than some mess of ROT and return stack temporaries.

    There is no rule without an exception.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From melahi_ahmed@melahi_ahmed@yahoo.fr (Ahmed) to comp.lang.forth on Mon Jun 30 10:25:46 2025
    From Newsgroup: comp.lang.forth

    On Mon, 30 Jun 2025 9:44:35 +0000, Paul Rubin wrote:



    : 3DUP ( a b c -- a b c a b c ) 3 PICK 3 PICK 3 PICK ;



    I think it must be 2 in lieu of 3, like this:

    : 3DUP ( a b c -- a b c a b c ) 2 PICK 2 PICK 2 PICK ;

    And I think it is for this type of errors, PICK must be used carefully.

    Ahmed

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Mon Jun 30 10:43:13 2025
    From Newsgroup: comp.lang.forth

    : 3DUP ( a b c -- a b c a b c ) 3 PICK 3 PICK 3 PICK ;



    I think it must be 2 in lieu of 3, like this:

    : 3DUP ( a b c -- a b c a b c ) 2 PICK 2 PICK 2 PICK ;

    It depends on the dialect used; at least in Forth-79
    1 PICK was equivalent to DUP.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From albert@albert@spenarnc.xs4all.nl to comp.lang.forth on Mon Jun 30 13:07:53 2025
    From Newsgroup: comp.lang.forth

    In article <0cd5e9d5959101c1efa68a2d6d630e23@www.novabbs.com>,
    Aren't 'locals' actually PICK/ROLL in disguise?

    This is a silly question. "disguise" is actually appearance.
    But the appearance of the code is what this is all about.
    So the important question is "are locals preferable to
    PICK/ROLL in appearance?" Clearly they are.

    [I personnally avoid using any of the two.]

    Groetjes Albert
    --
    The Chinese government is satisfied with its military superiority over USA.
    The next 5 year plan has as primary goal to advance life expectancy
    over 80 years, like Western Europe.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Mon Jun 30 21:55:48 2025
    From Newsgroup: comp.lang.forth

    On 30/06/2025 7:33 pm, LIT wrote:
    In a way this statement can be extended to the
    use of local variables. Still, as I said, it's
    allowed. No need for "too ideological" approach
    if that works for the programmer, neither for
    insisting on "canonical" ways etc.

    While many a stack op can be simulated using PICK and ROLL (hence
    CS-PICK
    CS-ROLL) I'm unaware of anyone using them in place of.  If stack ops are
    "canonical" it's because nobody has found a more efficient way of
    programming
    a stack computer.  Recognizing this as the fact and the reality, a
    programmer
    that's serious will deal with reality and not chase after ideology which
    is
    the province of thought.

    The stack ops THEMSELVES may be, in a way,
    "canonical" — but not solving "each and every"
    programming task using them "no-matter-what", IMHO.

    But such would indicate a deficiency in Forth. Do C programmers reach a
    point at which they can't go forward?

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Mon Jun 30 12:40:09 2025
    From Newsgroup: comp.lang.forth

    The stack ops THEMSELVES may be, in a way,
    "canonical" — but not solving "each and every"
    programming task using them "no-matter-what", IMHO.

    But such would indicate a deficiency in Forth. Do C programmers reach a point at which they can't go forward?

    You may want to raise your question on comp.lang.c

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Mon Jun 30 15:57:28 2025
    From Newsgroup: comp.lang.forth

    On 24-06-2025 18:23, Anton Ertl wrote:
    Hans Bezemer <the.beez.speaks@gmail.com> writes:
    I'm also puzzled why there is always so emphasis on the "speed" issue. I
    mean - if you want speed, do your program in C -O3 so to say. It'll blow
    any Forth out of the water.

    Take a look at the bubble benchmark in Figure 1 of <https://www.complang.tuwien.ac.at/papers/ertl24-interpreter-speed.pdf>. SwiftForth, VFX, and Gforth with all optimizations (the baseline) are
    faster than gcc-12 -O3. The reason for that is:

    |For bubble, gcc -O3 auto-vectorizes, and the result is that there is |partial overlap between a store and a following load, which results
    |in the hardware taking a slow path rather than performing one of its |store-to-load forwarding optimizations.

    - anton

    Well, one single benchmark. Now I know this, I'll try the others as well before settling on an optimization. And since you found the issue, maybe
    it can be fixed.

    To add to this story, I once added support for a GCC extension on 4tH.
    It sped the thing 25% up. Years later I found out that the current GCC compiler slowed it down. So - I defaulted on the previous method. It's
    one of these things.

    Recently someone claimed that token threaded Forths are slow. Well - not
    mine: https://thebeez.home.xs4all.nl/4tH/benchmark.html

    But gee - may be it's all different now. Who knows.

    Still, in general - GCC beats Forth. Although I have to admit I've got a renewed respect for VFX Forth! Kudos!

    Hans Bezemer


    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Mon Jun 30 16:42:48 2025
    From Newsgroup: comp.lang.forth

    On 25-06-2025 09:21, Paul Rubin wrote:
    Hans Bezemer <the.beez.speaks@gmail.com> writes:
    Fundamentally. I explained the sensation at the end
    of "Why Choose Forth". I've been able to tackle things I would never
    have been to tackle with a C mindset. ( https://youtu.be/MXKZPGzlx14 )

    I just watched this video and enjoyed it, but I don't understand how a C mindset is different. In C you pass stuff as function parameters
    instead of on the stack: what's the big deal? And particularly, the
    video said nothing about the burning question of locals ;).

    It seems to me all the examples mentioned in the video (parsing CSV
    files or floating point numerals) are what someone called
    micro-problems. Today they much easier with languages like Python, and
    back in Forth's heyday there was Lisp, which occupied a mindspace like
    Python does now.

    I agree that Thinking Forth is a great book.

    It's hard to illustrate things with a multi-KLOC program IMHO. You can
    only illustrate principles by using examples that are "contained" in a way.

    But I'll try to illustrate a thing or two. Let's say you want to tackle
    a problem. And it doesn't go your way. You have to add this thing and
    that thing - and hold on to that value. You know what I mean.

    When using C, you just add another local. Even *WITHIN* the loop you're
    about to add. Take a look at getopt() - I think that's a good example.
    You can almost see how it grew almost organically by the authors hand.
    He never seemed to think "Hmm, maybe I'll make a separate function of it".

    And when you take a good look, you will see how hard that is. There are
    THREE globals (okay, one static) to take care of, two locals and three parameters. So - if you want to split things off, you might have to pass
    a lot of stuff - bonus points if they have to be altered.

    You will reach that point in Forth *MUCH* earlier. And you cannot
    (easily) create a subroutine that takes a lot of parameters and handles
    them elegantly. Bonus points if you have to transfer stuff from the
    Return Stack as well.

    So - you'll have to use a different approach: what is the minimal thing
    that can handle the majority of the functionality required. Now, how can
    I extend that. Can I make some stuff local in another word so I don't
    have to carry it around. Can I elegantly integrate it in my main word?

    That was wrong - step back. Where did I go wrong and how can I fix it.
    All these things you never ask yourself when doing C - BECAUSE YOU DON'T
    HAVE TO. Everything is conveniently random accessible. You don't have to "clean up" since every local is "auto". That's why you often see
    sequences like "R> DROP R> DROP DROP NIP R> ROT" at the end of a word (exaggerated, but still) ;-)

    There is no price to pay if you pull in more resources. You don't have
    to ask yourself difficult questions and you don't have to do the
    (mental) work (both short-term and long term).

    It's at best intellectually lazy and at worst incompetent. It's these
    people who give Forth a bad name - BECAUSE WHAT THEY'RE WRITING IS AN ABOMINATION OF FORTH.

    It's an imitation. It's not real Forth. It's not a true reflection of
    what Forth can do. If I can write out the C code that was most obvious
    the basis of it without careful thought, it can't be Forth. It's as
    simple as that.

    Hans Bezemer

    float array a
    float array b
    float array c
    float array y

    : tamura-kanada ( n -- fpi )
    >r 1 s>f a f!
    1 s>f 2 s>f fsqrt f/ b f!
    1 s>f 4 s>f f/ c f!
    1 s>f
    r> 1 do
    a f@ fdup y f!
    b f@ f+ 2 s>f f/ a f!
    b f@ y f@ f* fsqrt b f!
    c f@ fover a f@ y f@ f-
    fdup f* f* f- c f! 2 s>f f*
    loop
    fdrop
    a f@ b f@ f+ fdup f* 4 s>f c f@ f* f/
    ;

    5 n = 4
    10 a = 1.0
    20 b = 1/SQR(2)
    30 c = 0.25
    40 d = 1.0
    50 FOR x = 1 TO n
    60 y = a
    70 a = (b+a)/2
    80 b = SQR(b*y)
    90 c = c - (d*(a - y)^2)
    100 d = d*2
    110 NEXT x
    120 PRINT ((a + b)^2)/(4*c)



    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From albert@albert@spenarnc.xs4all.nl to comp.lang.forth on Mon Jun 30 20:47:44 2025
    From Newsgroup: comp.lang.forth

    In article <878qlf179a.fsf@nightsong.com>,
    Paul Rubin <no.email@nospam.invalid> wrote:
    albert@spenarnc.xs4all.nl writes:
    with. And ditch github (USA) in favour of gitee (Chinese).
    USA is circling the drain.

    Try codeberg.org (Germany) maybe.

    USA is no more likely to survive in the near future (taking on
    China), than Germany that believes that they should defend Ukrain.
    They can't, and the result is economic collapse.
    In both cases commercial enterprises (that have "free software" for
    marketing purposes) I deem unreliable.

    OTOH gitee is supported by a government that has technical and
    scientific progress as a first priority. The harmony os (Huawei) is
    hosted there.

    Groetjes Albert
    --
    The Chinese government is satisfied with its military superiority over USA.
    The next 5 year plan has as primary goal to advance life expectancy
    over 80 years, like Western Europe.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From albert@albert@spenarnc.xs4all.nl to comp.lang.forth on Mon Jun 30 21:05:47 2025
    From Newsgroup: comp.lang.forth

    In article <nnd$7a5cfad1$76518ba7@2a4e6190d58511e2>,
    Hans Bezemer <the.beez.speaks@gmail.com> wrote:
    On 25-06-2025 09:21, Paul Rubin wrote:
    Hans Bezemer <the.beez.speaks@gmail.com> writes:
    Fundamentally. I explained the sensation at the end
    of "Why Choose Forth". I've been able to tackle things I would never
    have been to tackle with a C mindset. ( https://youtu.be/MXKZPGzlx14 )

    I just watched this video and enjoyed it, but I don't understand how a C
    mindset is different. In C you pass stuff as function parameters
    instead of on the stack: what's the big deal? And particularly, the
    video said nothing about the burning question of locals ;).

    It seems to me all the examples mentioned in the video (parsing CSV
    files or floating point numerals) are what someone called
    micro-problems. Today they much easier with languages like Python, and
    back in Forth's heyday there was Lisp, which occupied a mindspace like
    Python does now.

    I agree that Thinking Forth is a great book.

    It's hard to illustrate things with a multi-KLOC program IMHO. You can
    only illustrate principles by using examples that are "contained" in a way.

    But I'll try to illustrate a thing or two. Let's say you want to tackle
    a problem. And it doesn't go your way. You have to add this thing and
    that thing - and hold on to that value. You know what I mean.

    about to add. Take a look at getopt() - I think that's a good example.
    You can almost see how it grew almost organically by the authors hand.
    He never seemed to think "Hmm, maybe I'll make a separate function of it".

    getopt is a design error in Forth filosofy. You are writing an interpreter
    and Forth is the only interpreter, first commandment.

    EXAMPLE:

    : option? DROP C@ &- = ;
    : handle-arg 1 ARG[] 2DUP option? IF handle-option ELSE handle-file THEN ;
    : handle-args BEGIN ARGC 1 > WHILE handle-arg REPEAT intel-hex? ;

    \ Execute help directly. We don't want any interference.
    : -h help BYE ;

    : -c arg-number DROP DECIMAL 1000 * frequency ! 1 multiple !
    ARGC 1 <> ABORT" calculate requires 1 argument" ;

    \ Note the `arg-number word is no good for multiple arguments.
    : -m 1 ARG[] 2 <> ABORT" incorrect multiple args"
    SHIFT-ARGS \ rid of -m
    frequency DUP 4 CELLS + SWAP DO
    0. 1 ARG[] >NUMBER 0<> 107 ?ERROR 2DROP
    1000 * I ! SHIFT-ARGS
    1 CELLS +LOOP 4 multiple !
    ARGC 1 <> ABORT" multiple requires 4 arguments"
    ;

    : main
    defaults 0 multiple ! handle-args
    multiple @ 0= IF ." specify -h, -c or -m " CR BYE THEN
    init custom-action init-calibration-flash
    doit
    ;
    --
    The Chinese government is satisfied with its military superiority over USA.
    The next 5 year plan has as primary goal to advance life expectancy
    over 80 years, like Western Europe.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Paul Rubin@no.email@nospam.invalid to comp.lang.forth on Mon Jun 30 13:43:09 2025
    From Newsgroup: comp.lang.forth

    dxf <dxforth@gmail.com> writes:
    The stack ops THEMSELVES may be, in a way, "canonical" — but not
    solving "each and every" programming task using them
    "no-matter-what", IMHO.

    But such would indicate a deficiency in Forth. Do C programmers reach a point at which they can't go forward?

    Assembly language programmers reach a point where they run out of
    machine registers and have to do clumsy things to swap stuff between
    registers and memory. C compilers automate that process. Every C
    compiler with register allocation has to deal with register spilling.
    The programmer doesn't have to deal with it, but it's similar clumsy
    assembly code coming out of the compiler.

    In Forth without using locals, "register allocation" (deciding what is
    in each stack slot) is manual and there are fewer "registers" to begin
    with (basically TOS, NOS, TOR, and the 3rd stack element that you can
    reach with ROT). Modern CPUs by comparison generally have 16 or more addressible registers. The PDP-11 and 8086 had 8 registers and
    programmers found that to be painful.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Mon Jun 30 21:12:39 2025
    From Newsgroup: comp.lang.forth

    The PDP-11 and 8086 had 8 registers and
    programmers found that to be painful.

    Eight registers "painful"? Then how would you
    describe 6502 and its one plus two half-registers?
    :D

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Tue Jul 1 14:00:18 2025
    From Newsgroup: comp.lang.forth

    On 30/06/2025 10:40 pm, LIT wrote:
    The stack ops THEMSELVES may be, in a way,
    "canonical" — but not solving "each and every"
    programming task using them "no-matter-what", IMHO.

    But such would indicate a deficiency in Forth.  Do C programmers reach a
    point at which they can't go forward?

    You may want to raise your question on comp.lang.c

    I can't imagine them answering in the affirmative. C didn't introduce a competing syntax thereby creating schism among its users.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Tue Jul 1 14:22:02 2025
    From Newsgroup: comp.lang.forth

    On 27-06-2025 03:39, dxf wrote:
    Yet forthers have no problem with this. Take the SwiftForth source code.
    At best you'll get a general comment as to what a function does. How do
    they maintain it - the same way anyone proficient in C maintains C code. Albert is correct. Familiarity is key to readability. That's not to say code deserving documentation shouldn't have it. OTOH one shouldn't be expecting documentation (including stack commentary) for what's an everyday affair in Forth.

    I think you and Albert are on the right track here. Familiarity is a
    large part of this "readability" thingy. There are a few notes I want to
    add, though:

    1. "Infix notation" is part of this familiarity. I know I've commented
    every single expression in TEONW, since I understand those "infix"
    expressions much better than all those RPN thingies - and you got
    something to check your code against;

    2. Intentionality. I do this a LOT. E.g. if you find OVER OVER in my
    code, you may be certain those two items have nothing to do with each
    other. If you find 2DUP it's a string, a double number or another
    "addr/count" array. CHOP replaces 1 /STRING. Also: stack patterns can be codified like SPIN or STOW;

    3. Brevity. Short definitions are easier to understand. If you can
    abstract it, put a name of it can spare the performance - split it up.

    4. Naming. I give this a LOT of thought. I prefer reading a name and
    having a pretty good idea of what that code does (especially in the
    context of a library or a program). See: https://sourceforge.net/p/forth-4th/wiki/What%27s%20in%20a%20name%3F/

    Feel free to disagree. It may not work for you, but at least it works
    for me.

    Hans Bezemer


    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Stephen Pelc@stephen@vfxforth.com to comp.lang.forth on Tue Jul 1 13:26:16 2025
    From Newsgroup: comp.lang.forth

    On 30 Jun 2025 at 15:57:28 CEST, "Hans Bezemer" <the.beez.speaks@gmail.com> wrote:

    On 24-06-2025 18:23, Anton Ertl wrote:
    Hans Bezemer <the.beez.speaks@gmail.com> writes:
    I'm also puzzled why there is always so emphasis on the "speed" issue. I >>> mean - if you want speed, do your program in C -O3 so to say. It'll blow >>> any Forth out of the water.

    One of our clients makes a construction estimating package
    https://www.rib-software.com/en/rib-candy

    When ported from MPE's last threaded-code Forth to the early VFX Forth,
    screen redraw for the plan of part of a very large building improved by a factor
    of ten. The client was very pleased - this was a visible change for their users.

    I have also found that fast code enables me not to use progrmming tricks, but to code for readability and the maintenance programmer. I'm still maintaining code I first saw 40 years ago - not much of it, but always a pain to maintain.

    Still, in general - GCC beats Forth. Although I have to admit I've got a renewed respect for VFX Forth! Kudos!

    Thanks ... blush.

    Compiler output performance depends very much on the amunt of time and
    money spent on developing it. The VFX code generator was part of the
    planned output of an EU ESPRIT project.

    Stephen
    --
    Stephen Pelc, stephen@vfxforth.com
    Wodni & Pelc GmbH
    Vienna, Austria
    Tel: +44 (0)7803 903612, +34 649 662 974 http://www.vfxforth.com/downloads/VfxCommunity/
    free VFX Forth downloads
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Tue Jul 1 15:50:27 2025
    From Newsgroup: comp.lang.forth

    On 30-06-2025 21:05, albert@spenarnc.xs4all.nl wrote:
    In article <nnd$7a5cfad1$76518ba7@2a4e6190d58511e2>,
    Hans Bezemer <the.beez.speaks@gmail.com> wrote:
    On 25-06-2025 09:21, Paul Rubin wrote:
    Hans Bezemer <the.beez.speaks@gmail.com> writes:
    Fundamentally. I explained the sensation at the end
    of "Why Choose Forth". I've been able to tackle things I would never
    have been to tackle with a C mindset. ( https://youtu.be/MXKZPGzlx14 )

    I just watched this video and enjoyed it, but I don't understand how a C >>> mindset is different. In C you pass stuff as function parameters
    instead of on the stack: what's the big deal? And particularly, the
    video said nothing about the burning question of locals ;).

    It seems to me all the examples mentioned in the video (parsing CSV
    files or floating point numerals) are what someone called
    micro-problems. Today they much easier with languages like Python, and
    back in Forth's heyday there was Lisp, which occupied a mindspace like
    Python does now.

    I agree that Thinking Forth is a great book.

    It's hard to illustrate things with a multi-KLOC program IMHO. You can
    only illustrate principles by using examples that are "contained" in a way. >>
    But I'll try to illustrate a thing or two. Let's say you want to tackle
    a problem. And it doesn't go your way. You have to add this thing and
    that thing - and hold on to that value. You know what I mean.

    about to add. Take a look at getopt() - I think that's a good example.
    You can almost see how it grew almost organically by the authors hand.
    He never seemed to think "Hmm, maybe I'll make a separate function of it".

    getopt is a design error in Forth filosofy. You are writing an interpreter and Forth is the only interpreter, first commandment.

    Sure, don't take the analogy - attack the metaphor. There is no logical fallacy defined for that one, but for the number of times such attempts
    have been made - it should be.

    Just look at the code - don't take its functionality into consideration.

    Now what SHOULD the pseudo code for that one be:

    : GET-ARGUMENT
    if the option is not the last character in the argument,
    take the remainder of the argument as the option value
    ;

    : PARSE-ARGUMENT
    if the first character isn't a dash, stop the parsing!
    the index points to the next non-option argument;
    loop through the argument string - and execute the word associated
    with the character
    ;

    : PARSE-OPTIONS
    FOR each argument in arguments, PARSE-ARGUMENT
    until an "stop-parsing" code is received
    ;

    Now, what does getopt() look like?

    Hans Bezemer

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Tue Jul 1 18:46:47 2025
    From Newsgroup: comp.lang.forth

    On 30-06-2025 22:43, Paul Rubin wrote:
    dxf <dxforth@gmail.com> writes:
    The stack ops THEMSELVES may be, in a way, "canonical" — but not
    solving "each and every" programming task using them
    "no-matter-what", IMHO.

    But such would indicate a deficiency in Forth. Do C programmers reach a
    point at which they can't go forward?

    Assembly language programmers reach a point where they run out of
    machine registers and have to do clumsy things to swap stuff between registers and memory. C compilers automate that process. Every C
    compiler with register allocation has to deal with register spilling.
    The programmer doesn't have to deal with it, but it's similar clumsy
    assembly code coming out of the compiler.

    In Forth without using locals, "register allocation" (deciding what is
    in each stack slot) is manual and there are fewer "registers" to begin
    with (basically TOS, NOS, TOR, and the 3rd stack element that you can
    reach with ROT). Modern CPUs by comparison generally have 16 or more addressible registers. The PDP-11 and 8086 had 8 registers and
    programmers found that to be painful.

    Another great argument to leave Forth and embrace C! Why painfully
    create kludge to cram into a language that was clearly not created for
    that when you have a language available that was actually DESIGNED with
    those requirements in mind?!

    Is this something that is trendy in Cosmopolitan or something? Whatever!

    Hans Bezemer
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Tue Jul 1 18:53:44 2025
    From Newsgroup: comp.lang.forth

    On 30-06-2025 11:44, Paul Rubin wrote:
    zbigniew2011@gmail.com (LIT) writes:
    "Pick and Roll are the generic operators which treat the data stack as
    an array. If you find you need to use them, you are probably doing it
    wrong. Look for ways to refactor your code to be simpler instead."

    What is the origin of that quote? PICK treats the stack like an array,
    but ROLL treats it more as a circular shift register.

    Most CPUs these days have a register file, which is essentially an array
    with only immediate-like addressing mode. Presumably that design
    evolved because programmers found it useful.

    PICK afaict is mostly used with literal offsets as well. Having a
    variable offset is suspicious.

    : 3DUP ( a b c -- a b c a b c ) 3 PICK 3 PICK 3 PICK ;

    Seems clearer than some mess of ROT and return stack temporaries.

    If I so desperately wanted it I'd make a primitive out of it:

    CODE (3DUP) DSIZE (3); DFREE (3);
    a = DS(3); DPUSH (a);
    a = DS(3); DPUSH (a);
    a = DS(3); DPUSH (a); NEXT;

    However - I use it RARELY. So, it's not worth the trouble to hardcode it.

    $ pp4th -x stackopt.4th abc abcabc
    - Trying a 1 word solution..
    No solutions.
    - Trying a 2 word solution..
    No solutions.
    - Trying a 3 word solution..
    No solutions.
    - Trying a 4 word solution..
    No solutions.
    - Trying a 5 word solution..
    No solutions.
    - Trying a 6 word solution..
    No solutions.
    - Trying a 7 word solution..
    r over over r@ rot rot r>
    $

    That'll do.

    Hans Bezemer
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Tue Jul 1 19:02:12 2025
    From Newsgroup: comp.lang.forth

    On 01-07-2025 15:26, Stephen Pelc wrote:
    On 30 Jun 2025 at 15:57:28 CEST, "Hans Bezemer" <the.beez.speaks@gmail.com> wrote:

    On 24-06-2025 18:23, Anton Ertl wrote:
    Hans Bezemer <the.beez.speaks@gmail.com> writes:
    I'm also puzzled why there is always so emphasis on the "speed" issue. I >>>> mean - if you want speed, do your program in C -O3 so to say. It'll blow >>>> any Forth out of the water.

    One of our clients makes a construction estimating package
    https://www.rib-software.com/en/rib-candy

    When ported from MPE's last threaded-code Forth to the early VFX Forth, screen redraw for the plan of part of a very large building improved by a factor
    of ten. The client was very pleased - this was a visible change for their users.

    "Sometimes" doesn't equal "always" - AKA when I say that speed shouldn't always matter, doesn't mean it NEVER matters. Sure - there are always situations where it does. In that case I (personally) grab a C compiler.
    Which BTW hasn't happened since 1998. But of course, my job isn't your
    job. I'll never deny that.

    I have also found that fast code enables me not to use progrmming tricks, but to code for readability and the maintenance programmer. I'm still maintaining code I first saw 40 years ago - not much of it, but always a pain to maintain.

    It's always nice to have a few horsepower to spare under the hood ;-)

    Still, in general - GCC beats Forth. Although I have to admit I've got a
    renewed respect for VFX Forth! Kudos!

    Thanks ... blush.

    Well, it was earned. I really meant it..

    Compiler output performance depends very much on the amunt of time and
    money spent on developing it. The VFX code generator was part of the
    planned output of an EU ESPRIT project.

    Stephen

    Hans Bezemer

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Tue Jul 1 19:05:20 2025
    From Newsgroup: comp.lang.forth

    On 25-06-2025 09:21, Paul Rubin wrote:
    I just watched this video and enjoyed it, but I don't understand how a C mindset is different. In C you pass stuff as function parameters
    instead of on the stack: what's the big deal? And particularly, the
    video said nothing about the burning question of locals ;).

    Been there, done that:

    https://youtu.be/Y7cax2fDS84

    Hans Bezemer

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Tue Jul 1 19:34:34 2025
    From Newsgroup: comp.lang.forth

    On 26-06-2025 07:20, Waldek Hebisch wrote:
    Frankly, I do not see how missing language features
    can improve design.

    Then what the heck are you doing with Forth? I mean:
    - There are NO types, nor a compiler that holds your hand by checking
    them incessantly ;
    - There is NO expression parser in the sense of a shunting yard
    algorithm that does all the work for you;
    - There is NO calling mechanism in the sense that it transfers all the parameters for you and neatly sets up stack frames;
    - There is NO symbol table that is maintained for you - just a linked list;
    - There are NO namespaces. Just some tools to hook up sub lists to one
    big one.

    You can rent such apartments in Tokyo center.

    Hans Bezemer

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Paul Rubin@no.email@nospam.invalid to comp.lang.forth on Tue Jul 1 11:40:38 2025
    From Newsgroup: comp.lang.forth

    Hans Bezemer <the.beez.speaks@gmail.com> writes:
    But such would indicate a deficiency in Forth. Do C programmers reach a >>> point at which they can't go forward? ...
    Another great argument to leave Forth and embrace C! Why painfully
    create kludge to cram into a language that was clearly not created for
    that when you have a language available that was actually DESIGNED
    with those requirements in mind?!

    I'm not sure what you're getting at here, though I see the sarcasm.

    Is the kludge locals? They don't seem that kludgy to me. Implementing
    them in Forth is straightforward and lots of people have done it.

    The point where one can't go forward is basically "running out of
    registers". In assembly language those are the machine registers, and
    in Forth they're the top few stack slots. In both cases, when you run
    out, you have to resort to contorted code.

    In C that isn't a problem for the programmer. You can use as many
    variables as you like, and if the compiler runs out of registers and has
    to make contorted assembly code, it does so without your having to care.

    In a traditional Forth with locals, the locals are stack allocated so
    accessing them usually costs a memory reference. The programmer gets
    the same convenience as a C programmer. The runtime takes a slowdown
    compared to code from a register-allocating compiler, but such a
    slowdown is already present in a threaded interpreter, so it's fine.

    Finally, a fancy enough Forth compiler can do the same things that a C
    compiler does. Those compilers are difficult to write, but they exist
    (VFX, lxf, etc.). I don't know if locals make writing the compiler more difficult. But the user shouldn't have to care.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net (minforth) to comp.lang.forth on Tue Jul 1 19:36:21 2025
    From Newsgroup: comp.lang.forth

    On Tue, 1 Jul 2025 18:40:38 +0000, Paul Rubin wrote:

    In a traditional Forth with locals, the locals are stack allocated so accessing them usually costs a memory reference. The programmer gets
    the same convenience as a C programmer. The runtime takes a slowdown compared to code from a register-allocating compiler, but such a
    slowdown is already present in a threaded interpreter, so it's fine.


    In all this strange discussion about the ôpure and trueö Forth
    philosophy (on which even Charles Moore once went his own way), the
    human cost of programming time never comes up.

    Nobody seems to care about that time. Instead, the focus seems to be
    primarily on code runtime, even though the difference is only
    microseconds or less.

    This is completely nonsensical for 99% of all cases. Some people seem
    to prefer ôon principleö to help the computer with human work through ôpremature optimizationö to get its stack elements in the right order,
    and to factorize the programming task into digestible chunks, whether
    it is natural for the task or not. In a professional environment, this
    stubborn attitude is completely uneconomical.

    In my world, using locals in appropriate cases gets me done much faster, error-free, and the code is self-documenting. This time gain is
    astronomical when you put it in relation to microseconds of runtime
    difference.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Paul Rubin@no.email@nospam.invalid to comp.lang.forth on Tue Jul 1 12:56:02 2025
    From Newsgroup: comp.lang.forth

    minforth@gmx.net (minforth) writes:
    Nobody seems to care about that time. Instead, the focus seems to be primarily on code runtime, even though the difference is only
    microseconds or less.

    Forth was designed for threaded interpreter implementation and the whole
    notion of an optimizing Forth compiler is at best an abstraction
    inversion. But, supposedly, VFX compiler output runs 10x as fast as
    the same code under an interpreter.

    I think in the Moore era, you got two speedups: 1) interpreted Forth was
    10x faster than its main competitor, interpreted BASIC; and 2) if your
    Forth program was still too slow, you'd identify a few hot spots and
    rewrite those in assembler.

    Today instead of BASIC we have Python, and interpreted Forth is still a
    lot faster than Python. That speed is sufficient for most things, like
    it always was, but even more so on modern hardware.

    So I don't see much legitimate complaint about slowdowns due to Forth
    locals. The objection is based on other considerations, either
    legitimate ones that I don't yet understand, or essentially bogus ones
    that I don't completely see through. Maybe some combination of the two.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From albert@albert@spenarnc.xs4all.nl to comp.lang.forth on Tue Jul 1 23:42:16 2025
    From Newsgroup: comp.lang.forth

    In article <a15c00be7a546d30db84051932b1d22d@www.novabbs.com>,
    LIT <zbigniew2011@gmail.com> wrote:
    The PDP-11 and 8086 had 8 registers and
    programmers found that to be painful.

    Eight registers "painful"? Then how would you
    describe 6502 and its one plus two half-registers?
    :D

    I had a beef with Andrew Tanenbaum, stating that it is hard
    to write a c-compiler for the 6502. In reality the 6502
    is a brilliant design. You must realize that the 6502
    has 128 16 bit registers on the zero page.

    On the other hand the 8086 is not a real 8 bit processor (more 8/16)
    and it has more like 6 registers, and they are not even uniform.

    Groetjes Albert

    --
    --
    The Chinese government is satisfied with its military superiority over USA.
    The next 5 year plan has as primary goal to advance life expectancy
    over 80 years, like Western Europe.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From peter@peter.noreply@tin.it to comp.lang.forth on Tue Jul 1 23:47:05 2025
    From Newsgroup: comp.lang.forth

    On Tue, 01 Jul 2025 11:40:38 -0700
    Paul Rubin <no.email@nospam.invalid> wrote:

    Hans Bezemer <the.beez.speaks@gmail.com> writes:
    But such would indicate a deficiency in Forth. Do C programmers
    reach a point at which they can't go forward? ...
    Another great argument to leave Forth and embrace C! Why painfully
    create kludge to cram into a language that was clearly not created
    for that when you have a language available that was actually
    DESIGNED with those requirements in mind?!

    I'm not sure what you're getting at here, though I see the sarcasm.

    Is the kludge locals? They don't seem that kludgy to me.
    Implementing them in Forth is straightforward and lots of people have
    done it.

    The point where one can't go forward is basically "running out of
    registers". In assembly language those are the machine registers, and
    in Forth they're the top few stack slots. In both cases, when you run
    out, you have to resort to contorted code.

    In C that isn't a problem for the programmer. You can use as many
    variables as you like, and if the compiler runs out of registers and
    has to make contorted assembly code, it does so without your having
    to care.

    In a traditional Forth with locals, the locals are stack allocated so accessing them usually costs a memory reference. The programmer gets
    the same convenience as a C programmer. The runtime takes a slowdown compared to code from a register-allocating compiler, but such a
    slowdown is already present in a threaded interpreter, so it's fine.

    Finally, a fancy enough Forth compiler can do the same things that a C compiler does. Those compilers are difficult to write, but they exist
    (VFX, lxf, etc.). I don't know if locals make writing the compiler
    more difficult. But the user shouldn't have to care.

    The code generator in lxf has no knowledge of what a local is.
    locals are conceptually placed on the return stack. lxf is as smart
    about the return stack as the data stack. that is why it can produce
    very efficient code for simple examples like 3DUP. The actual
    implementation of local in the interpreter is just a few lines of code.
    The difference with locals will be seen when you have a boundary block,
    IF statement, a call etc that require a known state of the stacks.
    The real problem for me with locals is that their scope is to the end
    of the definition. With the stack you end the scope of an item with a
    drop and extend it with a dup, very elegant!
    A multipass compiler can of course find the scope of each local but at
    the cost of more complexity.

    In lxf64 I have introduced a local stack with the same capabilities as
    the data and return stack. I am not sure yet if this is better.

    The nice thing is that I now have >ls ls> and ls@. Compared with the
    return stack this also works across words. One word can put stuff on
    the localstack and another retrieve it. This is sometimes very useful.

    BR
    Peter


    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net to comp.lang.forth on Wed Jul 2 01:26:18 2025
    From Newsgroup: comp.lang.forth

    Am 01.07.2025 um 23:47 schrieb peter:
    On Tue, 01 Jul 2025 11:40:38 -0700
    Paul Rubin <no.email@nospam.invalid> wrote:

    Hans Bezemer <the.beez.speaks@gmail.com> writes:
    But such would indicate a deficiency in Forth. Do C programmers
    reach a point at which they can't go forward? ...
    Another great argument to leave Forth and embrace C! Why painfully
    create kludge to cram into a language that was clearly not created
    for that when you have a language available that was actually
    DESIGNED with those requirements in mind?!

    I'm not sure what you're getting at here, though I see the sarcasm.

    Is the kludge locals? They don't seem that kludgy to me.
    Implementing them in Forth is straightforward and lots of people have
    done it.

    Finally, a fancy enough Forth compiler can do the same things that a C
    compiler does. Those compilers are difficult to write, but they exist
    (VFX, lxf, etc.). I don't know if locals make writing the compiler
    more difficult. But the user shouldn't have to care.

    The code generator in lxf has no knowledge of what a local is.
    locals are conceptually placed on the return stack. lxf is as smart
    about the return stack as the data stack. that is why it can produce
    very efficient code for simple examples like 3DUP. The actual
    implementation of local in the interpreter is just a few lines of code.
    The difference with locals will be seen when you have a boundary block,
    IF statement, a call etc that require a known state of the stacks.
    The real problem for me with locals is that their scope is to the end
    of the definition. With the stack you end the scope of an item with a
    drop and extend it with a dup, very elegant!
    A multipass compiler can of course find the scope of each local but at
    the cost of more complexity.

    In lxf64 I have introduced a local stack with the same capabilities as
    the data and return stack. I am not sure yet if this is better.

    The nice thing is that I now have >ls ls> and ls@. Compared with the
    return stack this also works across words. One word can put stuff on
    the localstack and another retrieve it. This is sometimes very useful.

    In a sense, such locals become global. I am not sure if this opens the
    way inadvertently for hard-to-detect bugs. One rarely discussed property
    of locals is that they offer data encapsulation (or have scope in C terminology).

    Only one useful application comes to my mind: sharing locals between
    quotation and its parent function, i.e. for creating closures. But who
    needs thema anyway?

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net to comp.lang.forth on Wed Jul 2 05:00:21 2025
    From Newsgroup: comp.lang.forth

    Am 01.07.2025 um 21:56 schrieb Paul Rubin:
    minforth@gmx.net (minforth) writes:
    Nobody seems to care about that time. Instead, the focus seems to be
    primarily on code runtime, even though the difference is only
    microseconds or less.

    I think in the Moore era, you got two speedups: 1) interpreted Forth was
    10x faster than its main competitor, interpreted BASIC; and 2) if your
    Forth program was still too slow, you'd identify a few hot spots and
    rewrite those in assembler.

    Today instead of BASIC we have Python, and interpreted Forth is still a
    lot faster than Python. That speed is sufficient for most things, like
    it always was, but even more so on modern hardware.

    Today, you could go insane if you had to write assembler code
    with SSE1/2/3/4/AVX/AES etc. extended CPU commands (or take GPU
    programming...)

    Even chip manufacturers provide C libraries with built-ins and
    intrinsics to handle this complexity, and optimising C compilers
    for selecting the best operations.

    IMO assembler programming in Forth is mostly for retro enthusiasts

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Wed Jul 2 13:39:52 2025
    From Newsgroup: comp.lang.forth

    On 1/07/2025 10:22 pm, Hans Bezemer wrote:
    On 27-06-2025 03:39, dxf wrote:
    Yet forthers have no problem with this.  Take the SwiftForth source code. >> At best you'll get a general comment as to what a function does.  How do
    they maintain it - the same way anyone proficient in C maintains C code.
    Albert is correct.  Familiarity is key to readability.  That's not to say >> code deserving documentation shouldn't have it.  OTOH one shouldn't be
    expecting documentation (including stack commentary) for what's an everyday >> affair in Forth.

    I think you and Albert are on the right track here. Familiarity is a large part of this "readability" thingy. There are a few notes I want to add, though:

    1. "Infix notation" is part of this familiarity. I know I've commented every single expression in TEONW, since I understand those "infix" expressions much better than all those RPN thingies - and you got something to check your code against;

    2. Intentionality. I do this a LOT. E.g. if you find OVER OVER in my code, you may be certain those two items have nothing to do with each other. If you find 2DUP it's a string, a double number or another "addr/count" array. CHOP replaces 1 /STRING. Also: stack patterns can be codified like SPIN or STOW;

    3. Brevity. Short definitions are easier to understand. If you can abstract it, put a name of it can spare the performance - split it up.

    4. Naming. I give this a LOT of thought. I prefer reading a name and having a pretty good idea of what that code does (especially in the context of a library or a program). See: https://sourceforge.net/p/forth-4th/wiki/What%27s%20in%20a%20name%3F/

    Feel free to disagree. It may not work for you, but at least it works for me.

    Recently someone told me about Christianity - how it wasn't meant to be easy - supposed to be, among other things, a denial of the senses. I'm hearing much the same in Forth. That it's a celibate practice in which one denies everyday sensory pleasures including readability and maintainability in order to achieve programming nirvana. Heck, if that's how folks see Forth then perhaps they should stop before the cognitive dissonance sends them crazy or they pop a cork.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net to comp.lang.forth on Wed Jul 2 07:34:16 2025
    From Newsgroup: comp.lang.forth

    Am 02.07.2025 um 05:00 schrieb minforth:
    Am 01.07.2025 um 21:56 schrieb Paul Rubin:
    minforth@gmx.net (minforth) writes:
    Nobody seems to care about that time. Instead, the focus seems to be
    primarily on code runtime, even though the difference is only
    microseconds or less.

    I think in the Moore era, you got two speedups: 1) interpreted Forth was
    10x faster than its main competitor, interpreted BASIC; and 2) if your
    Forth program was still too slow, you'd identify a few hot spots and
    rewrite those in assembler.

    Today instead of BASIC we have Python, and interpreted Forth is still a
    lot faster than Python.  That speed is sufficient for most things, like
    it always was, but even more so on modern hardware.

    Today, you could go insane if you had to write assembler code
    with SSE1/2/3/4/AVX/AES etc. extended CPU commands (or take GPU programming...)

    Even chip manufacturers provide C libraries with built-ins and
    intrinsics to handle this complexity, and optimising C compilers
    for selecting the best operations.

    IMO assembler programming in Forth is mostly for retro enthusiasts


    P.S. I forgot to mention that this is not true for MCUs and embedded
    systems.

    I have the utmost respect for Matthias Koch's Mecrisp Stellaris.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Wed Jul 2 15:59:30 2025
    From Newsgroup: comp.lang.forth

    On 2/07/2025 1:00 pm, minforth wrote:
    Am 01.07.2025 um 21:56 schrieb Paul Rubin:
    minforth@gmx.net (minforth) writes:
    Nobody seems to care about that time. Instead, the focus seems to be
    primarily on code runtime, even though the difference is only
    microseconds or less.

    I think in the Moore era, you got two speedups: 1) interpreted Forth was
    10x faster than its main competitor, interpreted BASIC; and 2) if your
    Forth program was still too slow, you'd identify a few hot spots and
    rewrite those in assembler.

    Today instead of BASIC we have Python, and interpreted Forth is still a
    lot faster than Python.  That speed is sufficient for most things, like
    it always was, but even more so on modern hardware.

    Today, you could go insane if you had to write assembler code
    with SSE1/2/3/4/AVX/AES etc. extended CPU commands (or take GPU programming...)

    Even chip manufacturers provide C libraries with built-ins and
    intrinsics to handle this complexity, and optimising C compilers
    for selecting the best operations.

    IMO assembler programming in Forth is mostly for retro enthusiasts

    Yet Forth commercials continue to provide assemblers which they need
    to generate their own systems and to provide x87 and SSE f/p. One
    of the most interesting things of Acorn BASIC was the built-in 6502
    assembler.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Ruvim@ruvim.pinka@gmail.com to comp.lang.forth on Wed Jul 2 12:53:44 2025
    From Newsgroup: comp.lang.forth

    On 2025-06-24 01:03, minforth wrote:
    [...]

    For me, the small syntax extension is a convenience when working
    with longer definitions. A bit contrived (:= synonym for TO):

    : SOME-APP { a f: b c | temp == n: flag z: freq }
    \ inputs: integer a, floats b c
    \ uninitialized: float temp
    \ outputs: integer flag, complex freq
     <: FUNC < ... calc function ... > ;>

    BTW, why do you prefer the special syntax `<: ... ;>`
    over an extension to the existing words `:` and `;`

    : SOME-APP
    [ : FUNC < ... calc function ... > ; ]
    < ... >
    ;

    In this approach the word `:` knows that it's a nested definition and
    behaves accordingly.


    \ emulated embedded function using { | xt: func }
     < ... calc something ... > := temp
     < ... calc other things ... > := freq  / basic formula
     < ... calc other things ... > := flag
     < ... calc correction ... > := freq  / better estimation
    ;


    --
    Ruvim

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net to comp.lang.forth on Wed Jul 2 11:02:13 2025
    From Newsgroup: comp.lang.forth

    Am 02.07.2025 um 10:53 schrieb Ruvim:
    On 2025-06-24 01:03, minforth wrote:
    [...]

    For me, the small syntax extension is a convenience when working
    with longer definitions. A bit contrived (:= synonym for TO):

    : SOME-APP { a f: b c | temp == n: flag z: freq }
    \ inputs: integer a, floats b c
    \ uninitialized: float temp
    \ outputs: integer flag, complex freq
      <: FUNC < ... calc function ... > ;>

    BTW, why do you prefer the special syntax `<: ... ;>`
    over an extension to the existing words `:` and `;`

      : SOME-APP
         [ : FUNC < ... calc function ... > ; ]
         < ... >
      ;

    In this approach the word `:` knows that it's a nested definition and behaves accordingly.
    Are you sure? gforth test:

    : APP 1 [ : func 2 ; ] func ; ok
    app
    *the terminal*:2:1: error: Invalid memory address
    app<<<
    Backtrace:
    kernel/int.fs:594:10 0 $6FFFFF7FDE28 int-execute

    MinForth 3.6 test:

    # : APP 1 <: func 2 ;> func ; ok
    # app ok
    1 2 #

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Stephen Pelc@stephen@vfxforth.com to comp.lang.forth on Wed Jul 2 09:33:48 2025
    From Newsgroup: comp.lang.forth

    On 2 Jul 2025 at 05:39:52 CEST, "dxf" <dxforth@gmail.com> wrote:

    On 1/07/2025 10:22 pm, Hans Bezemer wrote:
    On 27-06-2025 03:39, dxf wrote:
    Yet forthers have no problem with this. Take the SwiftForth source code. >>> At best you'll get a general comment as to what a function does. How do >>> they maintain it - the same way anyone proficient in C maintains C code. >>> Albert is correct. Familiarity is key to readability. That's not to say >>> code deserving documentation shouldn't have it. OTOH one shouldn't be
    expecting documentation (including stack commentary) for what's an everyday >>> affair in Forth.

    I think you and Albert are on the right track here. Familiarity is a large >> part of this "readability" thingy. There are a few notes I want to add,
    though:

    1. "Infix notation" is part of this familiarity. I know I've commented every >> single expression in TEONW, since I understand those "infix" expressions much
    better than all those RPN thingies - and you got something to check your code
    against;

    2. Intentionality. I do this a LOT. E.g. if you find OVER OVER in my code, >> you may be certain those two items have nothing to do with each other. If you
    find 2DUP it's a string, a double number or another "addr/count" array. CHOP >> replaces 1 /STRING. Also: stack patterns can be codified like SPIN or STOW; >>
    3. Brevity. Short definitions are easier to understand. If you can abstract >> it, put a name of it can spare the performance - split it up.

    4. Naming. I give this a LOT of thought. I prefer reading a name and having a
    pretty good idea of what that code does (especially in the context of a
    library or a program). See:
    https://sourceforge.net/p/forth-4th/wiki/What%27s%20in%20a%20name%3F/

    Feel free to disagree. It may not work for you, but at least it works for me.

    Recently someone told me about Christianity - how it wasn't meant to be easy -
    supposed to be, among other things, a denial of the senses. I'm hearing much the same in Forth. That it's a celibate practice in which one denies everyday
    sensory pleasures including readability and maintainability in order to achieve
    programming nirvana. Heck, if that's how folks see Forth then perhaps they should stop before the cognitive dissonance sends them crazy or they pop a cork.

    IMHO religious belief is not a denial of the senses but a retraining. That
    does not mean that the retraining leads to anything valuable, but it can
    do depending very much on the trainer and trainee.

    Stephen
    --
    Stephen Pelc, stephen@vfxforth.com
    Wodni & Pelc GmbH
    Vienna, Austria
    Tel: +44 (0)7803 903612, +34 649 662 974 http://www.vfxforth.com/downloads/VfxCommunity/
    free VFX Forth downloads
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Wed Jul 2 09:44:13 2025
    From Newsgroup: comp.lang.forth

    I had a beef with Andrew Tanenbaum, stating that it is hard
    to write a c-compiler for the 6502. In reality the 6502
    is a brilliant design.

    https://www.ele.uva.es/~jesus/onthe6502.pdf

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Ruvim@ruvim.pinka@gmail.com to comp.lang.forth on Wed Jul 2 13:50:07 2025
    From Newsgroup: comp.lang.forth

    On 2025-07-02 13:02, minforth wrote:
    Am 02.07.2025 um 10:53 schrieb Ruvim:
    On 2025-06-24 01:03, minforth wrote:
    [...]

    For me, the small syntax extension is a convenience when working
    with longer definitions. A bit contrived (:= synonym for TO):

    : SOME-APP { a f: b c | temp == n: flag z: freq }
    \ inputs: integer a, floats b c
    \ uninitialized: float temp
    \ outputs: integer flag, complex freq
      <: FUNC < ... calc function ... > ;>

    BTW, why do you prefer the special syntax `<: ... ;>`
    over an extension to the existing words `:` and `;`

       : SOME-APP
          [ : FUNC < ... calc function ... > ; ]
          < ... >
       ;

    In this approach the word `:` knows that it's a nested definition and
    behaves accordingly.
    Are you sure? gforth test:

    : APP 1 [ : func 2 ; ] func ;  ok
    app
    *the terminal*:2:1: error: Invalid memory address

    This is not standard, just like `<: ;>`

    My question is why did you introduce `<:` and `;>` instead of extending
    the `:` and `;` behavior?

    Something like this:

    : ( "name" -- colon-sys )
    germ ( xt|0 ) \ the current definition xt or 0
    0= if 0 : exit then
    get-current locals-wodlist set-current :
    ;
    : :noname ( -- xt colon-sys )
    ['] :noname execute-balance 1- n>r 0 nr>
    ;
    : ; ( colon-sys -- )
    postpone ; ( wid|0 )
    ?dup if set-current then
    ;



    --
    Ruvim

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Wed Jul 2 13:16:14 2025
    From Newsgroup: comp.lang.forth

    On 01-07-2025 20:40, Paul Rubin wrote:
    Hans Bezemer <the.beez.speaks@gmail.com> writes:
    I'm not sure what you're getting at here, though I see the sarcasm.

    Sheldon will envy you ;-)

    Is the kludge locals? They don't seem that kludgy to me. Implementing
    them in Forth is straightforward and lots of people have done it.

    Hmm.. LOCALS from scratch? In Forth-2012 terms that's 3-4 screens full
    of code. In my book, that's not "straight forward". That's a massive kludge.

    Note OOP support can be one single screen. Note dynamic strings can be a single screen. Floating point can be a single screen. That is not it.

    Yeah - if you're smart plain locals *CAN* be a single line. But
    Forth-2012 was obviously not smart.

    But still - Forth was made to transfer parameters by the stack. And you
    have to appreciate how incredibly smart that is! You put stuff on the
    stack and call a word. The "parameters" are *immediately* accessible -
    no copying, no stack frame creation, no clean up..

    And just before you're done you put your stuff on the stack and like a
    tiny assembly line it is transported to the next thing. This means that
    the function call overhead is MINIMAL - much less than C.

    The point where one can't go forward is basically "running out of
    registers". In assembly language those are the machine registers, and
    in Forth they're the top few stack slots. In both cases, when you run
    out, you have to resort to contorted code.

    Not necessarily. [a] You could do the thing I did and define R'@ and R"@
    - which gives you two such registers more; [b] You could try and be
    smart. I gave some advise on that in https://www.youtube.com/watch?v=gfE8arB3uWk

    In C that isn't a problem for the programmer. You can use as many
    variables as you like, and if the compiler runs out of registers and has
    to make contorted assembly code, it does so without your having to care.

    And that's not the solution - it's the PROBLEM. You can add loads of complexity without much (immediate) penalty. You're not compelled to
    study - or even *think* about your algorithm. You most probably will end
    up with code that works - without you understanding why.

    And that will either bite you later, or limit your capability to expend
    on that code. I've worked with such code (MY CODE) myself - and later I
    had to do quite a cleanup, so I could actually understand what was going on.

    In a traditional Forth with locals, the locals are stack allocated so accessing them usually costs a memory reference. The programmer gets
    the same convenience as a C programmer. The runtime takes a slowdown compared to code from a register-allocating compiler, but such a
    slowdown is already present in a threaded interpreter, so it's fine.

    Ok, so sometimes speed is the greatest issue - and as a community we
    bend over backwards to prove we're worthy hares - and when not
    convenient "it's fine". Make up your mind!

    Finally, a fancy enough Forth compiler can do the same things that a C compiler does. Those compilers are difficult to write, but they exist
    (VFX, lxf, etc.). I don't know if locals make writing the compiler more difficult. But the user shouldn't have to care.

    I don't need to have the same facilities as in C, because if I wanted
    the same facilities as in C, I'd be using C - and would not bother to
    add kludges to other languages which strengths (by very design) lie
    elsewhere. It - doesn't - make - sense.

    If I want that girl, I'm dating that girl. I don't date another girl, so
    I can spend thousands of dollars of plastic surgery on that girl to make
    her look like a miserable imitation of that other girl. DUH!

    Hans Bezemer

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Wed Jul 2 13:17:36 2025
    From Newsgroup: comp.lang.forth

    On 01-07-2025 21:36, minforth wrote:
    On Tue, 1 Jul 2025 18:40:38 +0000, Paul Rubin wrote:

    In a traditional Forth with locals, the locals are stack allocated so
    accessing them usually costs a memory reference.  The programmer gets
    the same convenience as a C programmer.  The runtime takes a slowdown
    compared to code from a register-allocating compiler, but such a
    slowdown is already present in a threaded interpreter, so it's fine.


    In all this strange discussion about the ôpure and trueö Forth
    philosophy (on which even Charles Moore once went his own way), the
    human cost of programming time never comes up.

    Nobody seems to care about that time. Instead, the focus seems to be primarily on code runtime, even though the difference is only
    microseconds or less.

    This is completely nonsensical for 99% of all cases. Some people seem
    to prefer ôon principleö to help the computer with human work through ôpremature optimizationö to get its stack elements in the right order,
    and to factorize the programming task into digestible chunks, whether
    it is natural for the task or not. In a professional environment, this stubborn attitude is completely uneconomical.

    In my world, using locals in appropriate cases gets me done much faster, error-free, and the code is self-documenting. This time gain is
    astronomical when you put it in relation to microseconds of runtime difference.

    --

    You'd have all those "advantages" when you would be using C - and more. Instead, you have zero of the advantages of Forth.

    Hans Bezemer
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From albert@albert@spenarnc.xs4all.nl to comp.lang.forth on Wed Jul 2 13:37:27 2025
    From Newsgroup: comp.lang.forth

    In article <1042s2o$3d58h$1@dont-email.me>,
    Ruvim <ruvim.pinka@gmail.com> wrote:
    On 2025-06-24 01:03, minforth wrote:
    [...]

    For me, the small syntax extension is a convenience when working
    with longer definitions. A bit contrived (:= synonym for TO):

    : SOME-APP { a f: b c | temp == n: flag z: freq }
    \ inputs: integer a, floats b c
    \ uninitialized: float temp
    \ outputs: integer flag, complex freq
     <: FUNC < ... calc function ... > ;>

    BTW, why do you prefer the special syntax `<: ... ;>`
    over an extension to the existing words `:` and `;`

    : SOME-APP
    [ : FUNC < ... calc function ... > ; ]
    < ... >
    ;

    In this approach the word `:` knows that it's a nested definition and
    behaves accordingly.

    Or it has not even know it, if [ is smart enough to compile a jump to
    after ]. (That was the idea of the 4 brackets of the apocalypse.)
    The advantage that you need not modify any defining word.

    Ruvim

    --
    The Chinese government is satisfied with its military superiority over USA.
    The next 5 year plan has as primary goal to advance life expectancy
    over 80 years, like Western Europe.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Ruvim@ruvim.pinka@gmail.com to comp.lang.forth on Wed Jul 2 16:18:41 2025
    From Newsgroup: comp.lang.forth

    On 2025-07-02 15:37, albert@spenarnc.xs4all.nl wrote:
    In article <1042s2o$3d58h$1@dont-email.me>,
    Ruvim <ruvim.pinka@gmail.com> wrote:
    On 2025-06-24 01:03, minforth wrote:
    [...]

    For me, the small syntax extension is a convenience when working
    with longer definitions. A bit contrived (:= synonym for TO):

    : SOME-APP { a f: b c | temp == n: flag z: freq }
    \ inputs: integer a, floats b c
    \ uninitialized: float temp
    \ outputs: integer flag, complex freq
     <: FUNC < ... calc function ... > ;>

    BTW, why do you prefer the special syntax `<: ... ;>`
    over an extension to the existing words `:` and `;`

    : SOME-APP
    [ : FUNC < ... calc function ... > ; ]
    < ... >
    ;

    In this approach the word `:` knows that it's a nested definition and
    behaves accordingly.

    Or it has not even know it, if [ is smart enough to compile a jump to
    after ].

    This can be tricky because the following should work:

    create foo [ 123 , ] [ 456 ,

    : bar [ ' foo compile, 123 lit, ] ;



    --
    Ruvim

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Wed Jul 2 15:12:00 2025
    From Newsgroup: comp.lang.forth

    Ruvim <ruvim.pinka@gmail.com> writes:
    On 2025-07-02 15:37, albert@spenarnc.xs4all.nl wrote:
    Or it has not even know it, if [ is smart enough to compile a jump to
    after ].

    This can be tricky because the following should work:

    create foo [ 123 , ] [ 456 ,

    : bar [ ' foo compile, 123 lit, ] ;

    Or something. Anyway, [ and ] are used for a variety of purposes and
    trying to smarten them seems fraught with pitfalls. If one really
    wants to have

    : foo ... [ : bar ... ; ] ... ;

    work, it may be better to put the smarts into : and ;. E.g., on a
    system with sections, they could switch to another section and back.

    The benefit of defining a normal colon definition inside another colon definition eludes me, however. Maybe mutual recursion, but the need
    is rare and deferred words handle that well.

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2023 proceedings: http://www.euroforth.org/ef23/papers/
    EuroForth 2024 proceedings: http://www.euroforth.org/ef24/papers/
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Wed Jul 2 15:22:22 2025
    From Newsgroup: comp.lang.forth

    Hans Bezemer <the.beez.speaks@gmail.com> writes:
    And just before you're done you put your stuff on the stack and like a
    tiny assembly line it is transported to the next thing. This means that
    the function call overhead is MINIMAL - much less than C.

    Oh, really? Wasn't it you who wrote
    <nnd$34fd6cd6$25a88dac@ac6bb1addf3a4136>:

    |if you want speed, do your program in C -O3 so to say. It'll blow
    |any Forth out of the water.

    And if we look at the results for fib (a benchmark that performs lots
    of calls) inf Figure 1 of <https://www.complang.tuwien.ac.at/papers/ertl24-interpreter-speed.pdf>,
    gcc -O3 outperforms the fastest Forth system, and gcc -O1 outperforms
    the fastest Forth system by even more.

    And that's not the solution - it's the PROBLEM. You can add loads of >complexity without much (immediate) penalty. You're not compelled to
    study - or even *think* about your algorithm. You most probably will end
    up with code that works - without you understanding why.

    And that will either bite you later, or limit your capability to expend
    on that code.

    Yes, you can expend a lot of effort on code that's hard to write and
    hard to understand, but that's not limited to Forth.

    If you mean that, by making code hard to write, Forth without locals
    makes it easier to extend the code, I very much doubt it. In some
    cases it may not be harder, but in others (where the extension
    requires, e.g., dealing with additional data in existing colon
    definitions) it is harder.

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2023 proceedings: http://www.euroforth.org/ef23/papers/
    EuroForth 2024 proceedings: http://www.euroforth.org/ef24/papers/
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Wed Jul 2 15:44:40 2025
    From Newsgroup: comp.lang.forth

    minforth <minforth@gmx.net> writes:
    Today, you could go insane if you had to write assembler code
    with SSE1/2/3/4/AVX/AES etc. extended CPU commands (or take GPU >programming...)

    Even chip manufacturers provide C libraries with built-ins and
    intrinsics to handle this complexity, and optimising C compilers
    for selecting the best operations.

    Not really. Each AVX intrinsic corresponds to an instruction, and I
    expect the compiler to produce that instruction. The benefit of the
    intrinsics is that you can mix this assembly language with C code, and
    the C compiler will do the register allocation for you, but normally
    not a "better" operation. That being said, I have seen a case where
    an AVX256 intrinsic was translated to two AVX128 or SSE2 instructions
    because that sequence was suppsed to be faster on some Intel CPU (and
    it's Intel who writes the code for AVX intrinsics).

    In any case, given that there is one intrinsic for each SIMD
    instruction, you go just as insane with the plethora of intrinsics as
    with the plethora of SIMD instructions.

    The C way to dealing with SIMD instructions is auto-vectorization. It
    does not work particularly well, however, but given that it works on
    existing benchmarks, it has an unsurmountable advantage over explicit
    (manual) vecorization.

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2023 proceedings: http://www.euroforth.org/ef23/papers/
    EuroForth 2024 proceedings: http://www.euroforth.org/ef24/papers/
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net to comp.lang.forth on Wed Jul 2 18:15:56 2025
    From Newsgroup: comp.lang.forth

    Am 02.07.2025 um 11:50 schrieb Ruvim:
    On 2025-07-02 13:02, minforth wrote:
    Am 02.07.2025 um 10:53 schrieb Ruvim:
    On 2025-06-24 01:03, minforth wrote:
    [...]

    For me, the small syntax extension is a convenience when working
    with longer definitions. A bit contrived (:= synonym for TO):

    : SOME-APP { a f: b c | temp == n: flag z: freq }
    \ inputs: integer a, floats b c
    \ uninitialized: float temp
    \ outputs: integer flag, complex freq
      <: FUNC < ... calc function ... > ;>

    BTW, why do you prefer the special syntax `<: ... ;>`
    over an extension to the existing words `:` and `;`

       : SOME-APP
          [ : FUNC < ... calc function ... > ; ]
          < ... >
       ;

    In this approach the word `:` knows that it's a nested definition and
    behaves accordingly.
    Are you sure? gforth test:

    : APP 1 [ : func 2 ; ] func ;  ok
    app
    *the terminal*:2:1: error: Invalid memory address

    This is not standard, just like `<: ;>`

    My question is why did you introduce `<:` and `;>` instead of extending
    the `:` and `;` behavior?


    It came naturally and cheaply once I had XT: type locals.
    BTW, Gforth has them too.

    When called, normal locals push their value onto the stack.
    XT: locals also execute their pushed xt.

    Then, with quotations, embedded functions can be emulated:

    [: ... calc function ... ;] { xt: func } ...

    Whenever you subsequently call "func" within the enclosing parent
    word, the quotation is executed. The embedded function header is
    temporary and it does not occupy dictionary space after the end
    of the parent function.

    For the sake of my tired eyes, I just added some syntactic sugar:

    <: FUNC ... calc function ... ;> ...

    which does the same thing behind the scenes.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net to comp.lang.forth on Wed Jul 2 18:34:00 2025
    From Newsgroup: comp.lang.forth

    Am 02.07.2025 um 17:12 schrieb Anton Ertl:
    Ruvim <ruvim.pinka@gmail.com> writes:
    On 2025-07-02 15:37, albert@spenarnc.xs4all.nl wrote:
    Or it has not even know it, if [ is smart enough to compile a jump to
    after ].

    This can be tricky because the following should work:

    create foo [ 123 , ] [ 456 ,

    : bar [ ' foo compile, 123 lit, ] ;

    The benefit of defining a normal colon definition inside another colon definition eludes me, however. Maybe mutual recursion, but the need
    is rare and deferred words handle that well.


    Many roads lead to Rome. By accident, my quotations have read/write
    access to the locals of the parent function, but not vice versa.

    Apart from function encapsulation, the benefit is that I don't
    have to pass all quotation parameters over the stack, which makes
    the code very straightforward and readable.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Wed Jul 2 16:07:11 2025
    From Newsgroup: comp.lang.forth

    minforth <minforth@gmx.net> writes:
    Am 01.07.2025 um 23:47 schrieb peter:
    In lxf64 I have introduced a local stack with the same capabilities as
    the data and return stack. I am not sure yet if this is better.

    The nice thing is that I now have >ls ls> and ls@. Compared with the
    return stack this also works across words. One word can put stuff on
    the localstack and another retrieve it. This is sometimes very useful.

    In a sense, such locals become global. I am not sure if this opens the
    way inadvertently for hard-to-detect bugs.

    This stack combines some properties of the data stack (it not
    disturbed by calls) with some of the return stack (you put stuff there
    and remove it explicitly, which most words not doing anything
    permanent there). However, the interaction of explicit use with use
    through locals will mean restrictions; we have a similar situation
    with the return stack and counted loops and calls and returns, and we
    have learned to deal with that.

    Only one useful application comes to my mind: sharing locals between >quotation and its parent function, i.e. for creating closures.

    This does not create closures; for some limited usage it behaves like
    a closure would behave, but in other uses it does not. Such problems
    already plagued Algol 60 compilers, and Knuth wrote the man-or-boy
    test to check for them.

    But who
    needs thema anyway?

    Since we implemented closures in 2018 [ertl&paysan18], we have finally
    found a compelling use of closures:

    We have an actor-like model for letting tasks (threads) talk to each
    other, inspired by Heinz Schnitter's Open Network Forth. One task
    sends a word to another task, and that task executes that word at some
    point. Now we want to send parameterized words to another task (e.g.,
    do not just print "hello" in the other task, print something that may
    reflect data from the sending task). To do this, we create a one-shot
    closure that passes data along with the executed code to the receiving
    task and burns (deletes) itself after execution; see <file:///home/anton/gforth/doc/gforth/Message-queues.html>.

    We originally had a separate mechanism for passing data, but once we
    had closures, this became superfluous and was simplified away.

    @InProceedings{ertl&paysan18,
    author = {M. Anton Ertl and Bernd Paysan},
    title = {Closures --- the {Forth} way},
    crossref = {euroforth18},
    pages = {17--30},
    url = {https://www.complang.tuwien.ac.at/papers/ertl%26paysan.pdf},
    url2 = {http://www.euroforth.org/ef18/papers/ertl.pdf},
    slides-url = {http://www.euroforth.org/ef18/papers/ertl-slides.pdf},
    video = {https://wiki.forth-ev.de/doku.php/events:ef2018:closures},
    OPTnote = {refereed},
    abstract = {In Forth 200x, a quotation cannot access a local
    defined outside it, and therefore cannot be
    parameterized in the definition that produces its
    execution token. We present Forth closures; they
    lift this restriction with minimal implementation
    complexity. They are based on passing parameters on
    the stack when producing the execution token. The
    programmer has to explicitly manage the memory of
    the closure. We show a number of usage examples.
    We also present the current implementation, which
    takes 109~source lines of code (including some extra
    features). The programmer can mechanically convert
    lexical scoping (accessing a local defined outside)
    into code using our closures, by applying assignment
    conversion and flat-closure conversion. The result
    can do everything one expects from closures,
    including passing Knuth's man-or-boy test and living
    beyond the end of their enclosing definitions.}
    }

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2023 proceedings: http://www.euroforth.org/ef23/papers/
    EuroForth 2024 proceedings: http://www.euroforth.org/ef24/papers/
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Ruvim@ruvim.pinka@gmail.com to comp.lang.forth on Wed Jul 2 20:58:17 2025
    From Newsgroup: comp.lang.forth

    On 2025-07-02 19:12, Anton Ertl wrote:
    Ruvim <ruvim.pinka@gmail.com> writes:
    On 2025-07-02 15:37, albert@spenarnc.xs4all.nl wrote:
    Or it has not even know it, if [ is smart enough to compile a jump to
    after ].

    This can be tricky because the following should work:

    create foo [ 123 , ] [ 456 ,

    : bar [ ' foo compile, 123 lit, ] ;

    Or something. Anyway, [ and ] are used for a variety of purposes and
    trying to smarten them seems fraught with pitfalls. If one really
    wants to have

    : foo ... [ : bar ... ; ] ... ;

    work, it may be better to put the smarts into : and ;. E.g., on a
    system with sections, they could switch to another section and back.

    Yes, and I wonder why introducing new words like `<:` and `;>` is better
    than putting the smarts into `:` and `;`.


    The benefit of defining a normal colon definition inside another colon definition eludes me, however. Maybe mutual recursion, but the need
    is rare and deferred words handle that well.

    As I can see, the idea is that the name of a nested definition has the
    limited scope — the same as a local variable, and it is not visible
    outside of the containing definition.


    So, the program like:

    : foo
    ...
    [ : bar ... ; ]
    ...
    bar
    ...
    ;

    Is equivalent to:

    get-current wordlist push-order definitions

    : bar ... ;

    set-current
    : foo
    ...
    bar
    ...
    ;
    previous




    --
    Ruvim

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Wed Jul 2 16:41:44 2025
    From Newsgroup: comp.lang.forth

    Paul Rubin <no.email@nospam.invalid> writes:
    Forth was designed for threaded interpreter implementation and the whole >notion of an optimizing Forth compiler is at best an abstraction
    inversion.

    Looking at <https://en.wikipedia.org/wiki/Abstraction_inversion>, I
    don't see that at all. Or if it is, it's at least as bad for
    optimizing compilers for other languages. I cannot invoke any innards
    of C optimizing compilers, whereas in Forth we at least have LITERAL
    COMPILE, etc. to generate code. In Gforth (development version) you
    also can invoke SET-OPTIMIZER to specify how a given word is
    optimized.

    But, supposedly, VFX compiler output runs 10x as fast as
    the same code under an interpreter.

    You can see some data in Figure 1 of <https://www.complang.tuwien.ac.at/papers/ertl24-interpreter-speed.pdf>

    I think in the Moore era, you got two speedups: 1) interpreted Forth was
    10x faster than its main competitor, interpreted BASIC

    Not sure what you mean with Moore era; he has been active for many
    decades.

    Maybe on home computers, Forth's main competitor was interpreted
    BASIC, but in the environment where Moore discovered Forth
    (minicomputers like the IBM 1130 and the PDP-11), it wasn't. If you
    read up on the history of Forth, BASIC is not even mentioned. Fortran
    and Algol are.

    So I don't see much legitimate complaint about slowdowns due to Forth
    locals. The objection is based on other considerations, either
    legitimate ones that I don't yet understand, or essentially bogus ones
    that I don't completely see through.

    Those who have a Forth system that implements locals don't object to
    the use of locals, those whose Forth system does not implement them,
    do. Looks like the objections are sour-grapes arguments.

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2023 proceedings: http://www.euroforth.org/ef23/papers/
    EuroForth 2024 proceedings: http://www.euroforth.org/ef24/papers/
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Wed Jul 2 19:52:50 2025
    From Newsgroup: comp.lang.forth

    On 02-07-2025 17:22, Anton Ertl wrote:

    And that's not the solution - it's the PROBLEM. You can add loads of
    complexity without much (immediate) penalty. You're not compelled to
    study - or even *think* about your algorithm. You most probably will end
    up with code that works - without you understanding why.

    And that will either bite you later, or limit your capability to expend
    on that code.

    Yes, you can expend a lot of effort on code that's hard to write and
    hard to understand, but that's not limited to Forth.

    If you mean that, by making code hard to write, Forth without locals
    makes it easier to extend the code, I very much doubt it. In some
    cases it may not be harder, but in others (where the extension
    requires, e.g., dealing with additional data in existing colon
    definitions) it is harder.

    No, I mean the inverse - if you can add all kinds of complexity without penalty (like C) *that's* the point where you create unmaintainable
    code. But it *still* works.

    You can't get away with such code in Forth - since it will be
    unmaintainable long before that point. AKA - it *won't* work. Not even remotely.

    Hans Bezemer

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Paul Rubin@no.email@nospam.invalid to comp.lang.forth on Wed Jul 2 12:02:01 2025
    From Newsgroup: comp.lang.forth

    albert@spenarnc.xs4all.nl writes:
    I had a beef with Andrew Tanenbaum, stating that it is hard to write a c-compiler for the 6502. In reality the 6502 is a brilliant
    design. You must realize that the 6502 has 128 16 bit registers on the
    zero page.

    It's even hard to write compact assembly code, which is why Steve
    Wozniak wrote SWEET16.

    I briefly used Aztec C on the Apple II, IIRC. I think it generated
    bytecode for an interpreter, but am not sure.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Paul Rubin@no.email@nospam.invalid to comp.lang.forth on Wed Jul 2 12:07:05 2025
    From Newsgroup: comp.lang.forth

    peter <peter.noreply@tin.it> writes:
    The nice thing is that I now have >ls ls> and ls@. Compared with the
    return stack this also works across words. One word can put stuff on
    the localstack and another retrieve it. This is sometimes very useful.

    As I remember, Flashforth also has a 3rd stack like that, without having locals. It's called P so you have >P etc.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Thu Jul 3 00:09:44 2025
    From Newsgroup: comp.lang.forth

    On 02-07-2025 18:41, Anton Ertl wrote:
    Those who have a Forth system that implements locals don't object to
    the use of locals, those whose Forth system does not implement them,
    do. Looks like the objections are sour-grapes arguments.
    Oooh - I've seen a *LOT* of bad and ill-informed arguments on c.l.f.
    but this most certainly makes the top 10! :)

    1. Adding general locals is trivial. It takes just one single line of
    Forth. Sure, you don't got the badly designed and much too heavy
    Forth-2012 implementation, but it works just as well. It also proves
    that IF Chuck had wanted locals, that it would be a trivial addition.

    2. It also means the resistance is *NOT* due to the difficulty of implementation. 4tH v3.64.2 will even support a *MUCH* lighter, but
    fully conformant Forth-2012 LOCALS implementation. And if I can do it,
    so can others I suppose (Forth-2012 or not). So that argument is moot.

    3. "Looks like the objections are sour-grapes arguments." No, I have
    given far more arguments than you have. I'm not gonna repeat them in a
    forum that has already archived them. If anything, yours is a prime
    example of a "sour grape argument".

    Your turn!

    Hans Bezemer
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Paul Rubin@no.email@nospam.invalid to comp.lang.forth on Wed Jul 2 16:59:34 2025
    From Newsgroup: comp.lang.forth

    Hans Bezemer <the.beez.speaks@gmail.com> writes:
    1. Adding general locals is trivial. It takes just one single line of
    Forth.

    I don't see how to do it in one line, and trivial is a subjective term.
    I'd say in any case that it's not too difficult, but one line seems overoptimistic. Particularly, you need something like (LOCAL) in the
    VM. The rest is just some extensions to the colon compiler. Your
    mention of it taking 3-4 screens sounded within reason to me, and I
    don't consider that to be a lot of code.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net to comp.lang.forth on Thu Jul 3 03:14:54 2025
    From Newsgroup: comp.lang.forth

    Am 03.07.2025 um 01:59 schrieb Paul Rubin:
    Hans Bezemer <the.beez.speaks@gmail.com> writes:
    1. Adding general locals is trivial. It takes just one single line of
    Forth.

    I don't see how to do it in one line, and trivial is a subjective term.
    I'd say in any case that it's not too difficult, but one line seems overoptimistic. Particularly, you need something like (LOCAL) in the
    VM. The rest is just some extensions to the colon compiler. Your
    mention of it taking 3-4 screens sounded within reason to me, and I
    don't consider that to be a lot of code.

    I would not implement locals for simple integers only. Forth has enough
    stack gymnastics words for that.

    IMO locals only make sense if you can at least additionally handle
    floats and dynamic strings, preferably also structs and arrays.
    Such an implementation is certainly not trivial.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Thu Jul 3 08:34:26 2025
    From Newsgroup: comp.lang.forth

    Ruvim <ruvim.pinka@gmail.com> writes:
    On 2025-07-02 19:12, Anton Ertl wrote:
    The benefit of defining a normal colon definition inside another colon
    definition eludes me, however. Maybe mutual recursion, but the need
    is rare and deferred words handle that well.

    As I can see, the idea is that the name of a nested definition has the >limited scope — the same as a local variable, and it is not visible >outside of the containing definition.

    I have found the limited scope to be a hindrance, not a help: When I
    want to debug, I want to call the word, but if it is not visible,
    that's hard. There is a compromise: The scope recognizer allows to
    invoke a word X in a vocabulary V with the syntax V:X:

    vocabulary foo ok
    also foo definitions ok
    create foo1 ok
    previous definitions ok
    foo1
    *the terminal*:9:1: error: Undefined word
    foo1<<<
    Backtrace:
    kernel/recognizer.fs:89:21: 0 $7FCA47A12FF8 throw
    foo:foo1 hex. \ output: $7FCA47AA0DE8 ok

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2023 proceedings: http://www.euroforth.org/ef23/papers/
    EuroForth 2024 proceedings: http://www.euroforth.org/ef24/papers/
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Thu Jul 3 08:43:38 2025
    From Newsgroup: comp.lang.forth

    Hans Bezemer <the.beez.speaks@gmail.com> writes:
    1. Adding general locals is trivial. It takes just one single line of
    Forth. Sure, you don't got the badly designed and much too heavy
    Forth-2012 implementation,

    There is no Forth-2012 implementation of locals. The proposal
    includes a referece implementation, but that is based on a
    non-standard word BUILDLV and is therefore not included in <http://www.forth200x.org/reference-implementations/>; instead, you
    find there two implementations written in Forth-94:

    http://www.forth200x.org/reference-implementations/locals.fs http://www.forth200x.org/reference-implementations/extended-locals.fs

    Of these two the locals.fs implementation is the shorter and nicer
    one. You can read about these two implementations in <2021Mar3.171350@mips.complang.tuwien.ac.at>.

    However, looking at
    <https://forth-standard.org/standard/locals/bColon>, it seems that the
    editor included a variation of extensed-locals.fs.

    4tH v3.64.2 will even support a *MUCH* lighter, but
    fully conformant Forth-2012 LOCALS implementation.

    Great! How good that Forth-2012 is not an implementation standard.

    If anything, yours is a prime
    example of a "sour grape argument".

    Which grapes do you suppose that I am unable to reach?

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2023 proceedings: http://www.euroforth.org/ef23/papers/
    EuroForth 2024 proceedings: http://www.euroforth.org/ef24/papers/
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Thu Jul 3 13:06:09 2025
    From Newsgroup: comp.lang.forth

    On 03-07-2025 10:43, Anton Ertl wrote:
    Hans Bezemer <the.beez.speaks@gmail.com> writes:
    1. Adding general locals is trivial. It takes just one single line of
    Forth. Sure, you don't got the badly designed and much too heavy
    Forth-2012 implementation,

    There is no Forth-2012 implementation of locals. The proposal
    includes a referece implementation, but that is based on a
    non-standard word BUILDLV and is therefore not included in <http://www.forth200x.org/reference-implementations/>;

    Okay - technically you are right. That's the beauty of Forth - there are
    so many standards, there is always one that fits your taste. But none
    the less, this site *DOES* contain another, somewhat shorter implementation:

    https://forth-standard.org/standard/locals

    instead, you
    find there two implementations written in Forth-94:

    http://www.forth200x.org/reference-implementations/locals.fs http://www.forth200x.org/reference-implementations/extended-locals.fs

    Of these two the locals.fs implementation is the shorter and nicer
    one. You can read about these two implementations in <2021Mar3.171350@mips.complang.tuwien.ac.at>.

    The smaller one is *TWO* screens - and is dependent on the LOCALS
    wordset. I don't consider that "short". But everyone has his own
    standards. My "short" is a screen.

    However, looking at
    <https://forth-standard.org/standard/locals/bColon>, it seems that the
    editor included a variation of extensed-locals.fs.

    4tH v3.64.2 will even support a *MUCH* lighter, but
    fully conformant Forth-2012 LOCALS implementation.

    Great! How good that Forth-2012 is not an implementation standard.

    I beg to differ, but that's another discussion. I don't intend to use
    it, though. It's just there to make a point.

    If anything, yours is a prime
    example of a "sour grape argument".

    Which grapes do you suppose that I am unable to reach?

    I'm a lot of things, but not a mind reader. I'm not even trying. If
    you'd like to project the image of the mysterious and elusive "3rd man",
    be my guest.

    I'm more the kind of guy who says what he means and who means what he says.

    Hans Bezemer
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Thu Jul 3 13:14:32 2025
    From Newsgroup: comp.lang.forth

    On 03-07-2025 01:59, Paul Rubin wrote:
    Hans Bezemer <the.beez.speaks@gmail.com> writes:
    1. Adding general locals is trivial. It takes just one single line of
    Forth.

    I don't see how to do it in one line, and trivial is a subjective term.
    I'd say in any case that it's not too difficult, but one line seems overoptimistic. Particularly, you need something like (LOCAL) in the
    VM. The rest is just some extensions to the colon compiler. Your
    mention of it taking 3-4 screens sounded within reason to me, and I
    don't consider that to be a lot of code.

    "Short" in my dictionary is. One. Single. Screen. No more. No less (pun intended).

    And this one is one single screen. Even with the dependencies. https://youtu.be/FH4tWf9vPrA

    Typical use:

    variable a
    variable b

    : divide
    local a
    local b

    b ! a ! a @ b @ / ;

    Does recursion, the whole enchilada. One line.
    Thanks to Fred Behringer - and Albert, who condensed it to a single
    single line definition. Praise is where praise is due.

    Hans Bezemer
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From albert@albert@spenarnc.xs4all.nl to comp.lang.forth on Thu Jul 3 13:54:54 2025
    From Newsgroup: comp.lang.forth

    In article <87ikkaxhy1.fsf@nightsong.com>,
    Paul Rubin <no.email@nospam.invalid> wrote:
    Hans Bezemer <the.beez.speaks@gmail.com> writes:
    1. Adding general locals is trivial. It takes just one single line of
    Forth.

    I don't see how to do it in one line, and trivial is a subjective term.
    I'd say in any case that it's not too difficult, but one line seems >overoptimistic. Particularly, you need something like (LOCAL) in the
    VM. The rest is just some extensions to the colon compiler. Your
    mention of it taking 3-4 screens sounded within reason to me, and I
    don't consider that to be a lot of code.

    Not one line, but short leaning on existing words.
    Also these LOCAL's are not usable in recursed definition.
    Example in the context of ciforth.

    WANT VALUE [{
    : LOCAL
    POSTPONE [{ _ VALUE }] POSTPONE TO LATEST >LFA @
    POSTPONE LITERAL POSTPONE EXECUTE
    ; IMMEDIATE

    Groetjes Albert
    --
    The Chinese government is satisfied with its military superiority over USA.
    The next 5 year plan has as primary goal to advance life expectancy
    over 80 years, like Western Europe.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From albert@albert@spenarnc.xs4all.nl to comp.lang.forth on Thu Jul 3 14:13:02 2025
    From Newsgroup: comp.lang.forth

    In article <mcm3seFnagtU1@mid.individual.net>,
    minforth <minforth@gmx.net> wrote:
    Am 03.07.2025 um 01:59 schrieb Paul Rubin:
    Hans Bezemer <the.beez.speaks@gmail.com> writes:
    1. Adding general locals is trivial. It takes just one single line of
    Forth.

    I don't see how to do it in one line, and trivial is a subjective term.
    I'd say in any case that it's not too difficult, but one line seems
    overoptimistic. Particularly, you need something like (LOCAL) in the
    VM. The rest is just some extensions to the colon compiler. Your
    mention of it taking 3-4 screens sounded within reason to me, and I
    don't consider that to be a lot of code.

    I would not implement locals for simple integers only. Forth has enough
    stack gymnastics words for that.

    IMO locals only make sense if you can at least additionally handle
    floats and dynamic strings, preferably also structs and arrays.
    Such an implementation is certainly not trivial.


    Second that. iforth sports not only LOCAL (values), but also
    FLOCAL DLOCAL DFLOCAL. You end up establishing a whole menagery
    of shadow Forth words.

    It is much simpler to allow definitions in a [ .. ] sequence.

    Groetjes Albert
    --
    The Chinese government is satisfied with its military superiority over USA.
    The next 5 year plan has as primary goal to advance life expectancy
    over 80 years, like Western Europe.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From albert@albert@spenarnc.xs4all.nl to comp.lang.forth on Thu Jul 3 14:17:08 2025
    From Newsgroup: comp.lang.forth

    In article <nnd$57e17bcd$463b2e07@d86e5bbc05746f06>,
    Hans Bezemer <the.beez.speaks@gmail.com> wrote:
    On 03-07-2025 01:59, Paul Rubin wrote:
    Hans Bezemer <the.beez.speaks@gmail.com> writes:
    1. Adding general locals is trivial. It takes just one single line of
    Forth.

    I don't see how to do it in one line, and trivial is a subjective term.
    I'd say in any case that it's not too difficult, but one line seems
    overoptimistic. Particularly, you need something like (LOCAL) in the
    VM. The rest is just some extensions to the colon compiler. Your
    mention of it taking 3-4 screens sounded within reason to me, and I
    don't consider that to be a lot of code.

    "Short" in my dictionary is. One. Single. Screen. No more. No less (pun >intended).

    And this one is one single screen. Even with the dependencies. >https://youtu.be/FH4tWf9vPrA

    Typical use:

    variable a
    variable b

    : divide
    local a
    local b

    b ! a ! a @ b @ / ;

    Does recursion, the whole enchilada. One line.
    Thanks to Fred Behringer - and Albert, who condensed it to a single
    single line definition. Praise is where praise is due.

    Although 'local variables' like this are much preferred (superior) ,
    LOCAL (value) is what is asked for.
    If you don't have the akward, forward parsing TO already defined, you
    are bound to do more work.


    Hans Bezemer

    Groetjes Albert
    --
    The Chinese government is satisfied with its military superiority over USA.
    The next 5 year plan has as primary goal to advance life expectancy
    over 80 years, like Western Europe.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From albert@albert@spenarnc.xs4all.nl to comp.lang.forth on Thu Jul 3 14:27:02 2025
    From Newsgroup: comp.lang.forth

    In article <87pleixvhi.fsf@nightsong.com>,
    Paul Rubin <no.email@nospam.invalid> wrote:
    peter <peter.noreply@tin.it> writes:
    The nice thing is that I now have >ls ls> and ls@. Compared with the
    return stack this also works across words. One word can put stuff on
    the localstack and another retrieve it. This is sometimes very useful.

    As I remember, Flashforth also has a 3rd stack like that, without having >locals. It's called P so you have >P etc.

    Most Marcel Hendrix Forths has a 3rd stack called "system stack"
    S S> S@ (apart from LOCAL stacks).

    Groetjes Albert
    --
    The Chinese government is satisfied with its military superiority over USA.
    The next 5 year plan has as primary goal to advance life expectancy
    over 80 years, like Western Europe.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Thu Jul 3 22:42:48 2025
    From Newsgroup: comp.lang.forth

    On 3/07/2025 8:09 am, Hans Bezemer wrote:
    On 02-07-2025 18:41, Anton Ertl wrote:
    Those who have a Forth system that implements locals don't object to
    the use of locals, those whose Forth system does not implement them,
    do.  Looks like the objections are sour-grapes arguments.
     Oooh - I've seen a *LOT* of bad and ill-informed arguments on c.l.f. but this most certainly makes the top 10! :)

    1. Adding general locals is trivial. It takes just one single line of Forth. Sure, you don't got the badly designed and much too heavy Forth-2012 implementation, but it works just as well. It also proves that IF Chuck had wanted locals, that it would be a trivial addition.

    2. It also means the resistance is *NOT* due to the difficulty of implementation. 4tH v3.64.2 will even support a *MUCH* lighter, but fully conformant Forth-2012 LOCALS implementation. And if I can do it, so can others I suppose (Forth-2012 or not). So that argument is moot.

    3. "Looks like the objections are sour-grapes arguments." No, I have given far more arguments than you have. I'm not gonna repeat them in a forum that has already archived them. If anything, yours is a prime example of a "sour grape argument".

    Your turn!

    Ask Google. Enter 'Forth and locals' with AI enabled. It pretty much tells you locals are ok. How does Google know? Well, it mentions Gforth :)

    FWIW DX-Forth comes with locals. It was made it as fast as possible for
    the express purpose of letting users compare.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From albert@albert@spenarnc.xs4all.nl to comp.lang.forth on Thu Jul 3 14:51:38 2025
    From Newsgroup: comp.lang.forth

    In article <2025Jul2.172222@mips.complang.tuwien.ac.at>,
    Anton Ertl <anton@mips.complang.tuwien.ac.at> wrote:
    Hans Bezemer <the.beez.speaks@gmail.com> writes:
    And just before you're done you put your stuff on the stack and like a
    tiny assembly line it is transported to the next thing. This means that
    the function call overhead is MINIMAL - much less than C.

    Oh, really? Wasn't it you who wrote ><nnd$34fd6cd6$25a88dac@ac6bb1addf3a4136>:

    |if you want speed, do your program in C -O3 so to say. It'll blow
    |any Forth out of the water.

    And if we look at the results for fib (a benchmark that performs lots
    of calls) inf Figure 1 of ><https://www.complang.tuwien.ac.at/papers/ertl24-interpreter-speed.pdf>,
    gcc -O3 outperforms the fastest Forth system, and gcc -O1 outperforms
    the fastest Forth system by even more.

    I'm with Knuth here. No algorithms he describes use recursion, only
    explicit stacks.
    Don't try to optimise recurse functions,
    use an explicit stack.
    : FIB >R 1 0 R> 0 ?DO SWAP OVER + LOOP NIP ;


    And that's not the solution - it's the PROBLEM. You can add loads of >>complexity without much (immediate) penalty. You're not compelled to
    study - or even *think* about your algorithm. You most probably will end
    up with code that works - without you understanding why.

    And that will either bite you later, or limit your capability to expend
    on that code.

    Yes, you can expend a lot of effort on code that's hard to write and
    hard to understand, but that's not limited to Forth.

    If you mean that, by making code hard to write, Forth without locals
    makes it easier to extend the code, I very much doubt it. In some
    cases it may not be harder, but in others (where the extension
    requires, e.g., dealing with additional data in existing colon
    definitions) it is harder.

    I like to remind of the youtube FORTH2020 of Wagner. This concerns
    motions of aircraft, position speed, pitch roll and yaw etc.
    Terribly complicated, no LOCAL's. There was a question whether LOCAL's
    could have made Wagners code easier.
    He stated the ideal (paraphrased by me) that "code is its own comment"

    My most involved programs are ciasdis and manx. No LOCAL's in sight.
    I don't want to imply that these or Wagner's programs are easy to write,
    but the effort pays off.

    If Beez wants to say that Forth without locals tend to be more
    architectural sound, and therefore easier to extend, I agree.


    - anton

    Groetjes Albert
    --
    The Chinese government is satisfied with its military superiority over USA.
    The next 5 year plan has as primary goal to advance life expectancy
    over 80 years, like Western Europe.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From albert@albert@spenarnc.xs4all.nl to comp.lang.forth on Thu Jul 3 15:11:09 2025
    From Newsgroup: comp.lang.forth

    In article <1043831$3ggg9$1@dont-email.me>,
    Ruvim <ruvim.pinka@gmail.com> wrote:
    On 2025-07-02 15:37, albert@spenarnc.xs4all.nl wrote:
    In article <1042s2o$3d58h$1@dont-email.me>,
    Ruvim <ruvim.pinka@gmail.com> wrote:
    On 2025-06-24 01:03, minforth wrote:
    [...]

    For me, the small syntax extension is a convenience when working
    with longer definitions. A bit contrived (:= synonym for TO):

    : SOME-APP { a f: b c | temp == n: flag z: freq }
    \ inputs: integer a, floats b c
    \ uninitialized: float temp
    \ outputs: integer flag, complex freq
     <: FUNC < ... calc function ... > ;>

    BTW, why do you prefer the special syntax `<: ... ;>`
    over an extension to the existing words `:` and `;`

    : SOME-APP
    [ : FUNC < ... calc function ... > ; ]
    < ... >
    ;

    In this approach the word `:` knows that it's a nested definition and
    behaves accordingly.

    Or it has not even know it, if [ is smart enough to compile a jump to
    after ].

    This can be tricky because the following should work:

    create foo [ 123 , ] [ 456 ,

    : bar [ ' foo compile, 123 lit, ] ;

    If this bothers you, rename it in [[ ]].

    Once we enhance [ ] to do things prohibited by the standard,
    (adding nested definitions) I can't be bothered with this too much.
    --
    Ruvim

    Groetjes Albert
    --
    The Chinese government is satisfied with its military superiority over USA.
    The next 5 year plan has as primary goal to advance life expectancy
    over 80 years, like Western Europe.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Ruvim@ruvim.pinka@gmail.com to comp.lang.forth on Thu Jul 3 20:47:07 2025
    From Newsgroup: comp.lang.forth

    On 2025-07-03 17:11, albert@spenarnc.xs4all.nl wrote:
    In article <1043831$3ggg9$1@dont-email.me>,
    Ruvim <ruvim.pinka@gmail.com> wrote:
    On 2025-07-02 15:37, albert@spenarnc.xs4all.nl wrote:
    In article <1042s2o$3d58h$1@dont-email.me>,
    Ruvim <ruvim.pinka@gmail.com> wrote:
    On 2025-06-24 01:03, minforth wrote:
    [...]

    For me, the small syntax extension is a convenience when working
    with longer definitions. A bit contrived (:= synonym for TO):

    : SOME-APP { a f: b c | temp == n: flag z: freq }
    \ inputs: integer a, floats b c
    \ uninitialized: float temp
    \ outputs: integer flag, complex freq
     <: FUNC < ... calc function ... > ;>

    BTW, why do you prefer the special syntax `<: ... ;>`
    over an extension to the existing words `:` and `;`

    : SOME-APP
    [ : FUNC < ... calc function ... > ; ]
    < ... >
    ;

    In this approach the word `:` knows that it's a nested definition and
    behaves accordingly.

    Or it has not even know it, if [ is smart enough to compile a jump to
    after ].

    This can be tricky because the following should work:

    create foo [ 123 , ] [ 456 ,

    : bar [ ' foo compile, 123 lit, ] ;

    If this bothers you, rename it in [[ ]].

    Once we enhance [ ] to do things prohibited by the standard,
    (adding nested definitions) I can't be bothered with this too much.


    The standard does not prohibit a system from supporting nested
    definitions in whichever way that does not violate the standard behavior.


    Yes, something like "private[ ... ]private" is a possible approach, and
    its implementation seems simpler than adding the smarts to `:` and `;`
    (and other defining words, if any).

    The advantage of this approach over "<: ... ;>" is that you can define
    not only colon-definitions, but also constants, variables, immediate
    words, one-time macros, etc.


    : foo ( F: r.coefficient -- r.result )
    private[
    variable cnt
    0e fvalue k
    : [x] ... ; immediate
    ]private
    to k 0 cnt !
    ...
    ;

    It's also possible to associated the word list of private words with the containing word xt for debugging purposes.


    --
    Ruvim

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From peter@peter.noreply@tin.it to comp.lang.forth on Thu Jul 3 19:42:02 2025
    From Newsgroup: comp.lang.forth

    On Thu, 3 Jul 2025 20:47:07 +0400
    Ruvim <ruvim.pinka@gmail.com> wrote:
    On 2025-07-03 17:11, albert@spenarnc.xs4all.nl wrote:
    In article <1043831$3ggg9$1@dont-email.me>,
    Ruvim <ruvim.pinka@gmail.com> wrote:
    On 2025-07-02 15:37, albert@spenarnc.xs4all.nl wrote:
    In article <1042s2o$3d58h$1@dont-email.me>,
    Ruvim <ruvim.pinka@gmail.com> wrote:
    On 2025-06-24 01:03, minforth wrote:
    [...]

    For me, the small syntax extension is a convenience when working
    with longer definitions. A bit contrived (:= synonym for TO):

    : SOME-APP { a f: b c | temp == n: flag z: freq }
    \ inputs: integer a, floats b c
    \ uninitialized: float temp
    \ outputs: integer flag, complex freq
    <: FUNC < ... calc function ... > ;>

    BTW, why do you prefer the special syntax `<: ... ;>`
    over an extension to the existing words `:` and `;`

    : SOME-APP
    [ : FUNC < ... calc function ... > ; ]
    < ... >
    ;

    In this approach the word `:` knows that it's a nested
    definition and behaves accordingly.

    Or it has not even know it, if [ is smart enough to compile a
    jump to after ].

    This can be tricky because the following should work:

    create foo [ 123 , ] [ 456 ,

    : bar [ ' foo compile, 123 lit, ] ;

    If this bothers you, rename it in [[ ]].

    Once we enhance [ ] to do things prohibited by the standard,
    (adding nested definitions) I can't be bothered with this too much.


    The standard does not prohibit a system from supporting nested
    definitions in whichever way that does not violate the standard
    behavior.


    Yes, something like "private[ ... ]private" is a possible approach,
    and its implementation seems simpler than adding the smarts to `:`
    and `;` (and other defining words, if any).

    The advantage of this approach over "<: ... ;>" is that you can
    define not only colon-definitions, but also constants, variables,
    immediate words, one-time macros, etc.


    : foo ( F: r.coefficient -- r.result )
    private[
    variable cnt
    0e fvalue k
    : [x] ... ; immediate
    ]private
    to k 0 cnt !
    ...
    ;

    It's also possible to associated the word list of private words with
    the containing word xt for debugging purposes.


    --
    Ruvim

    In lxf I have module, private, public, end-module
    your example would be
    module
    private
    variable cnt
    0e fvalue k
    : [x] ... ; immediate
    public
    : foo ( F: r.coefficient -- r.result )
    to k 0 cnt !
    ...
    ;
    end-module
    end-module will remove all headers from the private words in the module
    I am not found of mixing definitions inside others.
    BR
    Peter

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net (minforth) to comp.lang.forth on Thu Jul 3 18:46:35 2025
    From Newsgroup: comp.lang.forth

    On Thu, 3 Jul 2025 17:42:02 +0000, peter wrote:

    In lxf I have module, private, public, end-module
    your example would be

    module
    private

    variable cnt
    0e fvalue k
    : [x] ... ; immediate

    public

    : foo ( F: r.coefficient -- r.result )
    to k 0 cnt !
    ...
    ;

    end-module

    end-module will remove all headers from the private words in the module
    I am not fond of mixing definitions inside others.


    Section 3.4.5 of the standard document is very clear on this.
    On the other hand, quotations do not fall under this verdict
    because neither namespace nor search order management is
    required.

    My <: func .. ;> emulation uses quotations. No big deal.
    I find it useful every now and then.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From albert@albert@spenarnc.xs4all.nl to comp.lang.forth on Thu Jul 3 20:57:22 2025
    From Newsgroup: comp.lang.forth

    In article <1046c6b$8gru$1@dont-email.me>,
    Ruvim <ruvim.pinka@gmail.com> wrote:
    <SNIP>
    The standard does not prohibit a system from supporting nested
    definitions in whichever way that does not violate the standard behavior.

    You are right. Same mistake again.
    <SNIP>
    It's also possible to associated the word list of private words with the >containing word xt for debugging purposes.

    Easier, after debugging just smudge (HIDE) those definitions.

    If you use a a separate wordlist PRIME for a facility:

    FROM PRIME IMPORT INIT-SIEVE PRIME?

    (Whatever is in the wordlist PRIME , only keep ALIAS for INIT-SIEVE and
    PRIME? in CURRENT.)


    --
    Ruvim

    --
    The Chinese government is satisfied with its military superiority over USA.
    The next 5 year plan has as primary goal to advance life expectancy
    over 80 years, like Western Europe.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Ruvim@ruvim.pinka@gmail.com to comp.lang.forth on Thu Jul 3 23:47:14 2025
    From Newsgroup: comp.lang.forth

    On 2025-07-03 22:46, minforth wrote:
    On Thu, 3 Jul 2025 17:42:02 +0000, peter wrote:
    [...]

    I am not fond of mixing definitions inside others.


    Section 3.4.5 of the standard document is very clear on this.

    <https://forth-standard.org/standard/usage#subsection.3.4.5>

    This section applies to standard *programs*, not systems.

    A standard system may provide facilities for nested compilation, and a system-dependent program may use these facilities.


    On the other hand, quotations do not fall under this verdict
    because neither namespace nor search order management is
    required.

    Yes. There are three categories whose members are prohibited from being executed in a standard program when the current definition exists:
    - a definition that allocates data space,
    - a defining word,
    - `:NONAME` (note that this word is not a defining word).

    And the word `[:` does not fall into any of these categories.

    NB: "current definition" is a formal term,
    see at <https://forth-standard.org/standard/notation#notation:terms>



    My <: func .. ;> emulation uses quotations.

    I think this should be treated as a nested definition.


    No big deal.
    I find it useful every now and then.



    --
    Ruvim
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Ruvim@ruvim.pinka@gmail.com to comp.lang.forth on Fri Jul 4 00:11:51 2025
    From Newsgroup: comp.lang.forth

    On 2025-07-03 21:42, peter wrote:
    On Thu, 3 Jul 2025 20:47:07 +0400
    Ruvim <ruvim.pinka@gmail.com> wrote:

    Yes, something like "private[ ... ]private" is a possible approach,
    and its implementation seems simpler than adding the smarts to `:`
    and `;` (and other defining words, if any).

    The advantage of this approach over "<: ... ;>" is that you can
    define not only colon-definitions, but also constants, variables,
    immediate words, one-time macros, etc.


    : foo ( F: r.coefficient -- r.result )
    private[
    variable cnt
    0e fvalue k
    : [x] ... ; immediate
    ]private
    to k 0 cnt !
    ...
    ;

    It's also possible to associated the word list of private words with
    the containing word xt for debugging purposes.




    In lxf I have module, private, public, end-module
    your example would be

    module
    private

    variable cnt
    0e fvalue k
    : [x] ... ; immediate

    public

    : foo ( F: r.coefficient -- r.result )
    to k 0 cnt !
    ...
    ;

    end-module

    I usually take this approach too.
    But in some cases it seems too wordy or long.

    Usage of construct "<: ... ;>"


    end-module will remove all headers from the private words in the module


    I am not found of mixing definitions inside others.

    By the way, local variables slightly break this principle. Also,
    conceptually, a module definition contains definitions of other words
    and possibly nested modules. And, conceptually, there is nothing wrong
    with defining a module as a colon-definition.


    --
    Ruvim

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Fri Jul 4 13:16:31 2025
    From Newsgroup: comp.lang.forth

    On 2/07/2025 7:33 pm, Stephen Pelc wrote:
    On 2 Jul 2025 at 05:39:52 CEST, "dxf" <dxforth@gmail.com> wrote:

    On 1/07/2025 10:22 pm, Hans Bezemer wrote:
    On 27-06-2025 03:39, dxf wrote:
    Yet forthers have no problem with this. Take the SwiftForth source code. >>>> At best you'll get a general comment as to what a function does. How do >>>> they maintain it - the same way anyone proficient in C maintains C code. >>>> Albert is correct. Familiarity is key to readability. That's not to say >>>> code deserving documentation shouldn't have it. OTOH one shouldn't be >>>> expecting documentation (including stack commentary) for what's an everyday
    affair in Forth.

    I think you and Albert are on the right track here. Familiarity is a large >>> part of this "readability" thingy. There are a few notes I want to add,
    though:

    1. "Infix notation" is part of this familiarity. I know I've commented every
    single expression in TEONW, since I understand those "infix" expressions much
    better than all those RPN thingies - and you got something to check your code
    against;

    2. Intentionality. I do this a LOT. E.g. if you find OVER OVER in my code, >>> you may be certain those two items have nothing to do with each other. If you
    find 2DUP it's a string, a double number or another "addr/count" array. CHOP
    replaces 1 /STRING. Also: stack patterns can be codified like SPIN or STOW; >>>
    3. Brevity. Short definitions are easier to understand. If you can abstract >>> it, put a name of it can spare the performance - split it up.

    4. Naming. I give this a LOT of thought. I prefer reading a name and having a
    pretty good idea of what that code does (especially in the context of a
    library or a program). See:
    https://sourceforge.net/p/forth-4th/wiki/What%27s%20in%20a%20name%3F/

    Feel free to disagree. It may not work for you, but at least it works for me.

    Recently someone told me about Christianity - how it wasn't meant to be easy -
    supposed to be, among other things, a denial of the senses. I'm hearing much
    the same in Forth. That it's a celibate practice in which one denies everyday
    sensory pleasures including readability and maintainability in order to achieve
    programming nirvana. Heck, if that's how folks see Forth then perhaps they >> should stop before the cognitive dissonance sends them crazy or they pop a >> cork.

    IMHO religious belief is not a denial of the senses but a retraining. That does not mean that the retraining leads to anything valuable, but it can
    do depending very much on the trainer and trainee.

    Yet every historical character claimed as enlightened (the Buddha etc) were themselves never taught. It puts into question the whole teacher/pupil/ methodological system that organized religion and various gurus employ. If several thousand years has shown anything, it is the utter failure of the approach.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Fri Jul 4 13:31:38 2025
    From Newsgroup: comp.lang.forth

    On 3/07/2025 10:51 pm, albert@spenarnc.xs4all.nl wrote:
    ...
    I like to remind of the youtube FORTH2020 of Wagner. This concerns
    motions of aircraft, position speed, pitch roll and yaw etc.
    Terribly complicated, no LOCAL's. There was a question whether LOCAL's
    could have made Wagners code easier.
    He stated the ideal (paraphrased by me) that "code is its own comment"

    That was an interesting video even if more a rundown of his (long) history
    as a professional forth programmer. Here's the link for anyone curious:

    https://youtu.be/V9ES9UZHaag

    He said he uses the hardware fp stack for speed. Is he really only
    using 8 levels of stack?


    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Fri Jul 4 13:48:40 2025
    From Newsgroup: comp.lang.forth

    On 3/07/2025 9:59 am, Paul Rubin wrote:
    Hans Bezemer <the.beez.speaks@gmail.com> writes:
    1. Adding general locals is trivial. It takes just one single line of
    Forth.

    I don't see how to do it in one line, and trivial is a subjective term.
    I'd say in any case that it's not too difficult, but one line seems overoptimistic. Particularly, you need something like (LOCAL) in the
    VM. The rest is just some extensions to the colon compiler. Your
    mention of it taking 3-4 screens sounded within reason to me, and I
    don't consider that to be a lot of code.

    Here's mine which is probably typical. Users load it on demand - though
    as yet I've not seen anyone do so.

    https://pastebin.com/QCJHyJXK

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Fri Jul 4 06:06:20 2025
    From Newsgroup: comp.lang.forth

    dxf <dxforth@gmail.com> writes:
    He said he uses the hardware fp stack for speed. Is he really only
    using 8 levels of stack?

    An 8-deep FP stack. Yes, SwiftForth users do:

    SwiftForth x64-Linux 4.0.0-RC89 15-Jul-2024
    : foo f+ f* ; ok
    : bar f@ f@ f@ execute f! ; ok fvariable a ok
    fvariable b
    B isn't unique. ok
    fvariable c ok
    fvariable d ok
    2e a f! ok 3e b f! ok
    4e c f! ok
    d ' foo c b a bar ok d f@ f. 14.00000000 ok
    see foo
    4519B7 ST(0) ST(1) FADDP DEC1
    4519B9 ST(0) ST(1) FMULP DEC9
    4519BB RET C3 ok
    see bar
    4519D3 0 [RBX] TBYTE FLD DB2B
    4519D5 0 [RBP] RBX MOV 488B5D00
    4519D9 8 [RBP] RBP LEA 488D6D08
    4519DD 0 [RBX] TBYTE FLD DB2B
    4519DF 0 [RBP] RBX MOV 488B5D00
    4519E3 8 [RBP] RBP LEA 488D6D08
    4519E7 0 [RBX] TBYTE FLD DB2B
    4519E9 0 [RBP] RBX MOV 488B5D00
    4519ED 8 [RBP] RBP LEA 488D6D08
    4519F1 4028CB ( EXECUTE ) CALL E8D50EFBFF
    4519F6 0 [RBX] TBYTE FSTP DB3B
    4519F8 0 [RBP] RBX MOV 488B5D00
    4519FC 8 [RBP] RBP LEA 488D6D08
    451A00 RET C3 ok

    No saving of FP values elsewhere around the EXECUTE in BAR, and no
    loading of FP values from elsewhere in FOO. So yes, on SwiftForth, if
    you push more than 8 FP stack values at the same time, you are in
    trouble.

    On VFX with the default FP package, it's the same, but VFX has
    alternative FP packages for those who cannot live with this
    limitation.

    As long as you use the FP stack just withing a colon definition and
    for parameter passing, i.e., not as temporary storage while calling
    another word, that limitation should not be particularly onerous.
    Moore uses 6 data stack items on his hardware since the uP20, and
    that's not just the FP stack.

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2023 proceedings: http://www.euroforth.org/ef23/papers/
    EuroForth 2024 proceedings: http://www.euroforth.org/ef24/papers/
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From albert@albert@spenarnc.xs4all.nl to comp.lang.forth on Fri Jul 4 12:01:51 2025
    From Newsgroup: comp.lang.forth

    In article <300ba9a1581bea9a01ab85d5d361e6eaeedbf23a@i2pn2.org>,
    dxf <dxforth@gmail.com> wrote:
    On 3/07/2025 10:51 pm, albert@spenarnc.xs4all.nl wrote:
    ...
    I like to remind of the youtube FORTH2020 of Wagner. This concerns
    motions of aircraft, position speed, pitch roll and yaw etc.
    Terribly complicated, no LOCAL's. There was a question whether LOCAL's
    could have made Wagners code easier.
    He stated the ideal (paraphrased by me) that "code is its own comment"

    That was an interesting video even if more a rundown of his (long) history
    as a professional forth programmer. Here's the link for anyone curious:

    https://youtu.be/V9ES9UZHaag

    He said he uses the hardware fp stack for speed. Is he really only
    using 8 levels of stack?

    8 level is plenty as long as you refrain from recursion that in
    Wagners context would be not even remotely useful.

    Groetjes Albert


    --
    The Chinese government is satisfied with its military superiority over USA.
    The next 5 year plan has as primary goal to advance life expectancy
    over 80 years, like Western Europe.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Sat Jul 5 12:25:08 2025
    From Newsgroup: comp.lang.forth

    On 4/07/2025 8:01 pm, albert@spenarnc.xs4all.nl wrote:
    In article <300ba9a1581bea9a01ab85d5d361e6eaeedbf23a@i2pn2.org>,
    dxf <dxforth@gmail.com> wrote:
    On 3/07/2025 10:51 pm, albert@spenarnc.xs4all.nl wrote:
    ...
    I like to remind of the youtube FORTH2020 of Wagner. This concerns
    motions of aircraft, position speed, pitch roll and yaw etc.
    Terribly complicated, no LOCAL's. There was a question whether LOCAL's
    could have made Wagners code easier.
    He stated the ideal (paraphrased by me) that "code is its own comment"

    That was an interesting video even if more a rundown of his (long) history >> as a professional forth programmer. Here's the link for anyone curious:

    https://youtu.be/V9ES9UZHaag

    He said he uses the hardware fp stack for speed. Is he really only
    using 8 levels of stack?

    8 level is plenty as long as you refrain from recursion that in
    Wagners context would be not even remotely useful.

    Puzzling because of a thread here not long ago in which scientific users
    appear to suggest the opposite. Such concerns have apparently been around
    a long time:

    https://groups.google.com/g/comp.lang.forth/c/CApt6AiFkxo/m/wwZmc_Tr1PcJ


    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Sat Jul 5 18:02:14 2025
    From Newsgroup: comp.lang.forth

    On 3/07/2025 10:17 pm, albert@spenarnc.xs4all.nl wrote:
    In article <nnd$57e17bcd$463b2e07@d86e5bbc05746f06>,
    Hans Bezemer <the.beez.speaks@gmail.com> wrote:
    On 03-07-2025 01:59, Paul Rubin wrote:
    Hans Bezemer <the.beez.speaks@gmail.com> writes:
    1. Adding general locals is trivial. It takes just one single line of
    Forth.

    I don't see how to do it in one line, and trivial is a subjective term.
    I'd say in any case that it's not too difficult, but one line seems
    overoptimistic. Particularly, you need something like (LOCAL) in the
    VM. The rest is just some extensions to the colon compiler. Your
    mention of it taking 3-4 screens sounded within reason to me, and I
    don't consider that to be a lot of code.

    "Short" in my dictionary is. One. Single. Screen. No more. No less (pun
    intended).

    And this one is one single screen. Even with the dependencies.
    https://youtu.be/FH4tWf9vPrA

    Typical use:

    variable a
    variable b

    : divide
    local a
    local b

    b ! a ! a @ b @ / ;

    Does recursion, the whole enchilada. One line.
    Thanks to Fred Behringer - and Albert, who condensed it to a single
    single line definition. Praise is where praise is due.

    Although 'local variables' like this are much preferred (superior) ,
    LOCAL (value) is what is asked for.
    If you don't have the akward, forward parsing TO already defined, you
    are bound to do more work.

    OTOH those that use locals will likely be wanting the 'standard' one.
    When ANS didn't deliver the locals users wanted all hell broke loose.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Sat Jul 5 08:49:22 2025
    From Newsgroup: comp.lang.forth

    dxf <dxforth@gmail.com> writes:
    [8 stack items on the FP stack]
    Puzzling because of a thread here not long ago in which scientific users >appear to suggest the opposite. Such concerns have apparently been around
    a long time:

    https://groups.google.com/g/comp.lang.forth/c/CApt6AiFkxo/m/wwZmc_Tr1PcJ

    I have read through the thread. It's unclear to me which scientific
    users you have in mind. My impression is that 8 stack items was
    deemed sufficient by many, and preferable (on 387) for efficiency
    reasons.

    Certainly, of the two points this thread is about, there was a
    Forth200x proposal for standardizing a separate FP stack, and this
    proposal was accepted. There was no proposal for increasing the
    minimum size of the FP stack; Forth-2012 still says:

    |The size of a floating-point stack shall be at least 6 items.

    One interesting aspect is that VFX 5.x finally includes an FP package
    by default, and it started by including an SSE2-based FP package which
    supports a deep FP stack. However, MPE received customer complaints
    about the lower number of significant digits in SSE2 (binary64)
    vs. 387 (80-bit FP values), so they switched the default to the
    387-based FP package that only has 8 FP stack items. Apparently no
    MPE customer complains about that limitation.

    OTOH, iForth-5.1-mini uses the 387 instructions, but stores FP stack
    items in memory at least on call boundaries. Maybe Marcel Hendrix can
    give some insight into what made him take this additional
    implementation effort.


    FORTH> : foo f+ f* ; ok
    FORTH> : bar f@ f@ f@ execute f! ; ok
    FORTH> ' foo idis
    $10226000 : foo 488BC04883ED088F4500 H.@H.m..E. $1022600A fld [r13 0 +] tbyte41DB6D00 A[m. $1022600E fld [r13 #16 +] tbyte
    41DB6D10 A[m. $10226012 fxch ST(2) D9CA YJ
    $10226014 lea r13, [r13 #32 +] qword
    4D8D6D20 M.m $10226018 faddp ST(1), ST DEC1 ^A
    $1022601A fxch ST(1) D9C9 YI
    $1022601C fpopswap, 41DB6D00D9CA4D8D6D10 A[m.YJM.m. $10226026 fmulp ST(1), ST DEC9 ^I
    $10226028 fpush, 4D8D6DF0D9C941DB7D00 M.mpYIA[}. $10226032 ; 488B45004883C508FFE0 H.E.H.E..` ok FORTH> ' bar idis
    $10226080 : bar 488BC04883ED088F4500 H.@H.m..E. $1022608A pop rbx 5B [
    $1022608B fld [rbx] tbyte DB2B [+
    $1022608D pop rbx 5B [
    $1022608E fld [rbx] tbyte DB2B [+
    $10226090 pop rbx 5B [
    $10226091 fld [rbx] tbyte DB2B [+
    $10226093 lea r13, [r13 #-48 +] qword
    4D8D6DD0 M.mP $10226097 fxch ST(3) D9CB YK
    $10226099 fstp [r13 #32 +] tbyte
    41DB7D20 A[} $1022609D fstp [r13 0 +] tbyte41DB7D00 A[}. $102260A1 fstp [r13 #16 +] tbyte
    41DB7D10 A[}. $102260A5 pop rbx 5B [
    $102260A6 or rbx, rbx 4809DB H.[
    $102260A9 je $102260B1 offset NEAR
    0F8402000000 ...... $102260AF call rbx FFD3 .S
    $102260B1 pop rbx 5B [
    $102260B2 fpop, 41DB6D00D9C94D8D6D10 A[m.YIM.m. $102260BC fstp [rbx] tbyte DB3B [;
    $102260BE ; 488B45004883C508FFE0 H.E.H.E..` ok

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2023 proceedings: http://www.euroforth.org/ef23/papers/
    EuroForth 2024 proceedings: http://www.euroforth.org/ef24/papers/
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From albert@albert@spenarnc.xs4all.nl to comp.lang.forth on Sat Jul 5 14:21:44 2025
    From Newsgroup: comp.lang.forth

    In article <2025Jul5.104922@mips.complang.tuwien.ac.at>,
    Anton Ertl <anton@mips.complang.tuwien.ac.at> wrote:
    <SNIP>
    One interesting aspect is that VFX 5.x finally includes an FP package
    by default, and it started by including an SSE2-based FP package which >supports a deep FP stack. However, MPE received customer complaints
    about the lower number of significant digits in SSE2 (binary64)
    vs. 387 (80-bit FP values), so they switched the default to the
    387-based FP package that only has 8 FP stack items. Apparently no
    MPE customer complains about that limitation.

    Interesting indeed! I would rather expect customers to complain
    about not IEEE compliance.


    OTOH, iForth-5.1-mini uses the 387 instructions, but stores FP stack
    items in memory at least on call boundaries. Maybe Marcel Hendrix can
    give some insight into what made him take this additional
    implementation effort.

    Once an assembler is in place, using only the internal stack
    fp merely costs 23 screens in ciforth. This includes transcendental
    functions, that are mostly a wrapper around an assembler instruction:
    CODE FCOS FCOS, NEXT, END-CODE
    The most involved are hyperbolic sine etc, that must be constructed
    by combining exponentials and demands ranges.

    I investigated the instruction set, and I found no way to detect
    if the 8 registers stack is full.
    This would offer the possibility to spill registers to memory only
    if it is needed.

    - anton
    --
    The Chinese government is satisfied with its military superiority over USA.
    The next 5 year plan has as primary goal to advance life expectancy
    over 80 years, like Western Europe.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net to comp.lang.forth on Sat Jul 5 14:41:11 2025
    From Newsgroup: comp.lang.forth

    Am 05.07.2025 um 14:21 schrieb albert@spenarnc.xs4all.nl:
    I investigated the instruction set, and I found no way to detect
    if the 8 registers stack is full.
    This would offer the possibility to spill registers to memory only
    if it is needed.


    IIRC signaling and handling fp-stack overflow is not an easy task.
    At most, the computer would crash.
    IOW, spilling makes sense.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net to comp.lang.forth on Sat Jul 5 16:24:37 2025
    From Newsgroup: comp.lang.forth

    Am 05.07.2025 um 14:41 schrieb minforth:
    Am 05.07.2025 um 14:21 schrieb albert@spenarnc.xs4all.nl:
    I investigated the instruction set, and I found no way to detect
    if the 8 registers stack is full.
    This would offer the possibility to spill registers to memory only
    if it is needed.


    IIRC signaling and handling fp-stack overflow is not an easy task.
    At most, the computer would crash.
    IOW, spilling makes sense.

    A deep dive into the manual

    .. the C1 condition code flag is used for a variety of functions.
    When both the IE and SF flags in the x87 FPU status word are set,
    indicating a stack overflow or underflow exception (#IS), the C1
    flag distinguishes between overflow (C1=1) and underflow (C1=0).

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Sat Jul 5 14:28:02 2025
    From Newsgroup: comp.lang.forth

    minforth <minforth@gmx.net> writes:
    Am 05.07.2025 um 14:21 schrieb albert@spenarnc.xs4all.nl:
    I investigated the instruction set, and I found no way to detect
    if the 8 registers stack is full.
    This would offer the possibility to spill registers to memory only
    if it is needed.


    IIRC signaling and handling fp-stack overflow is not an easy task.

    The stopry I read is that Kahan and the 8087 architects intended to
    support extending the 8087 stack into memory with an exception
    handler, but that part of the specification did not get implemented as intended, and it was then extremely hard or impossible to implement
    that feature. The problem was not noticed until after it was too
    late; apparently 8 stack items was sufficient for most uses also
    outside the Forth context, too.

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2023 proceedings: http://www.euroforth.org/ef23/papers/
    EuroForth 2024 proceedings: http://www.euroforth.org/ef24/papers/
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Sun Jul 6 12:52:37 2025
    From Newsgroup: comp.lang.forth

    On 5/07/2025 6:49 pm, Anton Ertl wrote:
    dxf <dxforth@gmail.com> writes:
    [8 stack items on the FP stack]
    Puzzling because of a thread here not long ago in which scientific users
    appear to suggest the opposite. Such concerns have apparently been around >> a long time:

    https://groups.google.com/g/comp.lang.forth/c/CApt6AiFkxo/m/wwZmc_Tr1PcJ

    I have read through the thread. It's unclear to me which scientific
    users you have in mind. My impression is that 8 stack items was
    deemed sufficient by many, and preferable (on 387) for efficiency
    reasons.

    AFAICS both Skip Carter (proponent) and Julian Noble were suggesting the
    6 level minimum were inadequate. A similar sentiment was expressed here
    only several months ago. AFAIK all major forths supporting x87 hardware
    offer software stack options.

    Certainly, of the two points this thread is about, there was a
    Forth200x proposal for standardizing a separate FP stack, and this
    proposal was accepted. There was no proposal for increasing the
    minimum size of the FP stack; Forth-2012 still says:

    |The size of a floating-point stack shall be at least 6 items.

    Only because nothing further was heard. What became of the review
    Elizabeth announced I've no idea.

    One interesting aspect is that VFX 5.x finally includes an FP package
    by default, and it started by including an SSE2-based FP package which supports a deep FP stack. However, MPE received customer complaints
    about the lower number of significant digits in SSE2 (binary64)
    vs. 387 (80-bit FP values), so they switched the default to the
    387-based FP package that only has 8 FP stack items. Apparently no
    MPE customer complains about that limitation.
    ...

    AFAIK x87 hardware stack was always MPE's main and best supported FP
    package. As for SSE2 it wouldn't exist if industry didn't consider double-precision adequate. My impression of MPE's SSE2 implementation
    is that it's 'a work in progress'. The basic precision is there but transcendentals appear to be limited to single-precision. That'd be
    the reason I'd stick with MPE's x87 package. Other reason is it's now
    quite difficult and error-prone to switch FP packages as it involves
    rebuilding the system. The old scheme was simpler and idiot-proof.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Sun Jul 6 07:50:13 2025
    From Newsgroup: comp.lang.forth

    Recently someone told me about Christianity - how it wasn't meant to be
    easy - supposed to be, among other things, a denial of the senses.

    "...I wished to be quite fair then, and I wish to be quite fair now;
    and I did not conclude that the attack on Christianity was all wrong.
    I only concluded that if Christianity was wrong, it was very
    wrong indeed. Such hostile horrors might be combined in one thing,
    but that thing must be very strange and solitary. There are men
    who are misers, and also spendthrifts; but they are rare. There are
    men sensual and also ascetic; but they are rare. But if this mass
    of mad contradictions really existed, quakerish and bloodthirsty,
    too gorgeous and too thread-bare, austere, yet pandering preposterously
    to the lust of the eye, the enemy of women and their foolish refuge,
    a solemn pessimist and a silly optimist, if this evil existed,
    then there was in this evil something quite supreme and unique.
    For I found in my rationalist teachers no explanation of such
    exceptional corruption. Christianity (theoretically speaking)
    was in their eyes only one of the ordinary myths and errors of mortals.
    THEY gave me no key to this twisted and unnatural badness.
    Such a paradox of evil rose to the stature of the supernatural.
    It was, indeed, almost as supernatural as the infallibility of the Pope.
    An historic institution, which never went right, is really quite
    as much of a miracle as an institution that cannot go wrong.
    The only explanation which immediately occurred to my mind was that Christianity did not come from heaven, but from hell. Really, if Jesus
    of Nazareth was not Christ, He must have been Antichrist.

    And then in a quiet hour a strange thought struck me like a still thunderbolt. There had suddenly come into my mind another explanation.
    Suppose we heard an unknown man spoken of by many men. Suppose we
    were puzzled to hear that some men said he was too tall and some
    too short; some objected to his fatness, some lamented his leanness;
    some thought him too dark, and some too fair. One explanation (as
    has been already admitted) would be that he might be an odd shape.
    But there is another explanation. He might be the right shape.
    Outrageously tall men might feel him to be short. Very short men
    might feel him to be tall. Old bucks who are growing stout might
    consider him insufficiently filled out; old beaux who were growing
    thin might feel that he expanded beyond the narrow lines of elegance.
    Perhaps Swedes (who have pale hair like tow) called him a dark man,
    while negroes considered him distinctly blonde. Perhaps (in short)
    this extraordinary thing is really the ordinary thing; at least
    the normal thing, the centre. Perhaps, after all, it is Christianity
    that is sane and all its critics that are mad -- in various ways.
    I tested this idea by asking myself whether there was about any
    of the accusers anything morbid that might explain the accusation.
    I was startled to find that this key fitted a lock. For instance,
    it was certainly odd that the modern world charged Christianity
    at once with bodily austerity and with artistic pomp. But then
    it was also odd, very odd, that the modern world itself combined
    extreme bodily luxury with an extreme absence of artistic pomp.
    The modern man thought Becket's robes too rich and his meals too poor.
    But then the modern man was really exceptional in history; no man before
    ever ate such elaborate dinners in such ugly clothes. The modern man
    found the church too simple exactly where modern life is too complex;
    he found the church too gorgeous exactly where modern life is too dingy.
    The man who disliked the plain fasts and feasts was mad on entrees.
    The man who disliked vestments wore a pair of preposterous trousers.
    And surely if there was any insanity involved in the matter at all it
    was in the trousers, not in the simply falling robe. If there was any
    insanity at all, it was in the extravagant entrees, not in the bread
    and wine.

    I went over all the cases, and I found the key fitted so far."

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Stephen Pelc@stephen@vfxforth.com to comp.lang.forth on Sun Jul 6 08:46:53 2025
    From Newsgroup: comp.lang.forth

    On 6 Jul 2025 at 04:52:37 CEST, "dxf" <dxforth@gmail.com> wrote:

    On 5/07/2025 6:49 pm, Anton Ertl wrote:
    dxf <dxforth@gmail.com> writes:
    [8 stack items on the FP stack]
    Puzzling because of a thread here not long ago in which scientific users >>> appear to suggest the opposite. Such concerns have apparently been around >>> a long time:

    https://groups.google.com/g/comp.lang.forth/c/CApt6AiFkxo/m/wwZmc_Tr1PcJ

    I have read through the thread. It's unclear to me which scientific
    users you have in mind. My impression is that 8 stack items was
    deemed sufficient by many, and preferable (on 387) for efficiency
    reasons.

    AFAICS both Skip Carter (proponent) and Julian Noble were suggesting the
    6 level minimum were inadequate. A similar sentiment was expressed here
    only several months ago. AFAIK all major forths supporting x87 hardware offer software stack options.

    Certainly, of the two points this thread is about, there was a
    Forth200x proposal for standardizing a separate FP stack, and this
    proposal was accepted. There was no proposal for increasing the
    minimum size of the FP stack; Forth-2012 still says:

    |The size of a floating-point stack shall be at least 6 items.

    Only because nothing further was heard. What became of the review
    Elizabeth announced I've no idea.

    One interesting aspect is that VFX 5.x finally includes an FP package
    by default, and it started by including an SSE2-based FP package which
    supports a deep FP stack. However, MPE received customer complaints
    about the lower number of significant digits in SSE2 (binary64)
    vs. 387 (80-bit FP values), so they switched the default to the
    387-based FP package that only has 8 FP stack items. Apparently no
    MPE customer complains about that limitation.
    ...

    AFAIK x87 hardware stack was always MPE's main and best supported FP
    package. As for SSE2 it wouldn't exist if industry didn't consider double-precision adequate. My impression of MPE's SSE2 implementation
    is that it's 'a work in progress'. The basic precision is there but transcendentals appear to be limited to single-precision. That'd be
    the reason I'd stick with MPE's x87 package. Other reason is it's now
    quite difficult and error-prone to switch FP packages as it involves rebuilding the system. The old scheme was simpler and idiot-proof.

    You do not have to rebuild the system to switch. Just read the manual.

    "The old scheme was simpler and idiot-proof." Yes, that's why we
    did it that way, but a certain "guru" who only does testing kept
    moaning. If people would prefer us to go back to the old scheme,
    VFX 6 still has time for changes. The whole idea that compiling
    one file is improper is very non-Forth, or even anti-Forth.

    I may be getting grumpier as I get older.

    Stephen
    --
    Stephen Pelc, stephen@vfxforth.com
    Wodni & Pelc GmbH
    Vienna, Austria
    Tel: +44 (0)7803 903612, +34 649 662 974 http://www.vfxforth.com/downloads/VfxCommunity/
    free VFX Forth downloads
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Sun Jul 6 20:29:01 2025
    From Newsgroup: comp.lang.forth

    On 6/07/2025 6:46 pm, Stephen Pelc wrote:
    On 6 Jul 2025 at 04:52:37 CEST, "dxf" <dxforth@gmail.com> wrote:

    On 5/07/2025 6:49 pm, Anton Ertl wrote:
    ...
    One interesting aspect is that VFX 5.x finally includes an FP package
    by default, and it started by including an SSE2-based FP package which
    supports a deep FP stack. However, MPE received customer complaints
    about the lower number of significant digits in SSE2 (binary64)
    vs. 387 (80-bit FP values), so they switched the default to the
    387-based FP package that only has 8 FP stack items. Apparently no
    MPE customer complains about that limitation.
    ...

    AFAIK x87 hardware stack was always MPE's main and best supported FP
    package. As for SSE2 it wouldn't exist if industry didn't consider
    double-precision adequate. My impression of MPE's SSE2 implementation
    is that it's 'a work in progress'. The basic precision is there but
    transcendentals appear to be limited to single-precision. That'd be
    the reason I'd stick with MPE's x87 package. Other reason is it's now
    quite difficult and error-prone to switch FP packages as it involves
    rebuilding the system. The old scheme was simpler and idiot-proof.

    You do not have to rebuild the system to switch. Just read the manual.

    If you mean:

    integers
    remove-FP-pack
    include FPSSE64S.fth

    That works - however everything that was defined after VFXFORTH is gone.
    In the case of Windows at least it leaves the system in a fragile state.
    I did find a way to recompile the forgotten stuff but it involved editing
    paths and files etc.


    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Sun Jul 6 20:58:42 2025
    From Newsgroup: comp.lang.forth

    On 6/07/2025 5:50 pm, LIT wrote:
    Recently someone told me about Christianity - how it wasn't meant to be
    easy - supposed to be, among other things, a denial of the senses.
    ...

    One can only imagine the dinner conversation in heaven with Chesterton,
    Wilde and Paul the Apostle present.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Sun Jul 6 11:30:27 2025
    From Newsgroup: comp.lang.forth

    dxf <dxforth@gmail.com> writes:
    On 5/07/2025 6:49 pm, Anton Ertl wrote:
    dxf <dxforth@gmail.com> writes:
    [8 stack items on the FP stack]
    Puzzling because of a thread here not long ago in which scientific users >>> appear to suggest the opposite. Such concerns have apparently been around >>> a long time:

    https://groups.google.com/g/comp.lang.forth/c/CApt6AiFkxo/m/wwZmc_Tr1PcJ

    I have read through the thread. It's unclear to me which scientific
    users you have in mind. My impression is that 8 stack items was
    deemed sufficient by many, and preferable (on 387) for efficiency
    reasons.

    AFAICS both Skip Carter (proponent) and Julian Noble were suggesting the
    6 level minimum were inadequate.

    Skip Carter did not post in this thread, but given that he proposed
    the change, he probably found 6 to be too few; or maybe it was just a phenomenon that we also see elsewhere as range anxiety. In any case,
    he made no such proposal to Forth-200x, so apparently the need was not pressing.

    Julian Noble ignored the FP stack size issue in his first posting in
    this thread, unlike the separate FP stack size issue, which he
    supported. So it seems that he did not care about a larger FP stack
    size. In the other posting he endorsed moving FP stack items to the
    data stack, but he did not write why; for all we know he might have
    wanted that as a first step for getting the mantissa, exponent and
    sign of the FP value as integer (and the other direction for
    synthesizing FP numbers from these parts).

    AFAIK all major forths supporting x87 hardware
    offer software stack options.

    Certainly on SwiftForth-4.0 I find no such option, it apparently
    proved unnecessary. The manual mentions fpconfig.f, but no such file
    exists in a SwiftForth-4.0 directory in the versions I have installed.

    There exists such a file on various SwiftForth-3.x versions, but on
    most of our machines SwiftForth-3.x segfaults (I have not investigated
    why; it used to work). Ok, so I found an old system where it does not segfault, but trying to load FP on that system produced no joy:

    [k8:~:118696] sf-3.11.0
    SwiftForth i386-Linux 3.11.0 23-Feb-2021
    require fpmath File not found

    [k8:~:118699] sf-3.11.0 "include /nfs/nfstmp/anton/SwiftForth-3.11.0/lib/options/fpmath.f"
    /nfs/nfstmp/anton/SwiftForth-3.11.0/lib/options/fpmath.f
    49: REQUIRES fpconfig >>> File not found

    [k8:~:118700] sf-3.11.0 "include /nfs/nfstmp/anton/SwiftForth-3.11.0/lib/options/linux/fpconfig.f include /nfs/nfstmp/anton/SwiftForth-3.11.0/lib/options/fpmath.f"
    /nfs/nfstmp/anton/SwiftForth-3.11.0/lib/options/fpmath.f
    49: REQUIRES fpconfig >>> File not found

    [k8:~:118702] sf-3.11.0 "include /nfs/nfstmp/anton/SwiftForth-3.11.0/lib/options/linux/fpconfig.f"
    ok
    include /nfs/nfstmp/anton/SwiftForth-3.11.0/lib/options/fpmath.f /nfs/nfstmp/anton/SwiftForth-3.11.0/lib/options/fpmath.f
    49: REQUIRES fpconfig >>> File not found

    Certainly, of the two points this thread is about, there was a
    Forth200x proposal for standardizing a separate FP stack, and this
    proposal was accepted. There was no proposal for increasing the
    minimum size of the FP stack; Forth-2012 still says:

    |The size of a floating-point stack shall be at least 6 items.

    Only because nothing further was heard. What became of the review
    Elizabeth announced I've no idea.

    The ANS Forth committee gave up after a price increase by the
    origanization under whose umbrella they did their work (it's a
    Tom-Sawyer-like business model: You work for them, and they charge you
    money for that).

    Several years later, we started Forth-200x, and we started with dpANS6/Forth-94, not with whatever the state their revision was in
    when they gave up. Concerning these two issues, the separate FP stack
    was proposed and accepted; the larger stack depth was not even
    proposed, not by Skip Carter, and not by anyone else. If you think
    that a larger number of guaranteed FP stack items is necessary,
    propose it.

    The old scheme was simpler and idiot-proof.

    Maybe for using a different FP package which is something I have used
    only once (IIRC I modified the 387 package to do store and load FP
    values in 8 byes, in order to investigate whether that explains a
    performance difference). But thinking about it, no, it was everything
    but simple. I had to find the VFX manual every time, then look up the
    name of the FP package (which is named as unmemorizable as possible
    without going to random names), then search for that package in the
    files on the system, and finally cut and paste the path of that file.

    A typical sequence of commands was:

    locate -i vfx|grep pdf
    xpdf /usr/share/doc/VfxForth/VfxLin.pdf
    bg
    locate ndp387.fth
    locate p387.fth
    vfxlin "include /usr/local/VfxLinEval/Lib/x86/Ndp387.fth"

    If I want to switch from the default FP package to a different
    package, I essentially have to take the same steps, I only have to add
    two additional commands before including the FP package; the last
    command for including the SSE implementation becomes:

    vfx64 "integers remove-FP-pack include /nfs/nfstmp/anton/VfxForth64Lin-5.43/Lib/x64/FPSSE64S.fth"

    (A special twist here is that the documentation says that the file is
    called FPSSE64.fth (with only 2 S characters), so I needed a few more
    locate invocations to find the right one).

    If you find the former simple, why not the latter (apart from the
    documentation mistake)?

    In any case, in almost all cases I use the default FP pack, and here
    the VFX-5 and SwiftForth-4 approach is unbeatable in simplicity.
    Instead of performing the sequence of commands shown above, I just
    start the Forth system, and FP words are ready.

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2023 proceedings: http://www.euroforth.org/ef23/papers/
    EuroForth 2024 proceedings: http://www.euroforth.org/ef24/papers/
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From mhx@mhx@iae.nl (mhx) to comp.lang.forth on Mon Jul 7 00:05:14 2025
    From Newsgroup: comp.lang.forth

    On Sat, 5 Jul 2025 14:24:37 +0000, minforth wrote:

    Am 05.07.2025 um 14:41 schrieb minforth:
    Am 05.07.2025 um 14:21 schrieb albert@spenarnc.xs4all.nl:
    I investigated the instruction set, and I found no way to detect
    if the 8 registers stack is full.
    This would offer the possibility to spill registers to memory only
    if it is needed.


    IIRC signaling and handling fp-stack overflow is not an easy task.
    At most, the computer would crash.
    IOW, spilling makes sense.

    A deep dive into the manual

    ... the C1 condition code flag is used for a variety of functions.
    When both the IE and SF flags in the x87 FPU status word are set,
    indicating a stack overflow or underflow exception (#IS), the C1
    flag distinguishes between overflow (C1=1) and underflow (C1=0).

    This definitely does not work (I tried it). That manual is fabulating.

    iForth has its FP stack in memory. However, inside colon definitions
    the compiler tracks the hardware stack. Only when inlining is not
    possible, or would lead to excessive size, HW stack items are
    flushed/reloaded to/from memory. Anyway, a software stack is necessary
    when calling C libraries or the OS.

    The mental cost of writing the FP compiler was insane, but I
    found it justified.

    BTW, the transputer had the same problem (and solution).

    -marcel

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Mon Jul 7 13:48:16 2025
    From Newsgroup: comp.lang.forth

    On 6/07/2025 9:30 pm, Anton Ertl wrote:
    dxf <dxforth@gmail.com> writes:
    On 5/07/2025 6:49 pm, Anton Ertl wrote:
    dxf <dxforth@gmail.com> writes:
    [8 stack items on the FP stack]
    Puzzling because of a thread here not long ago in which scientific users >>>> appear to suggest the opposite. Such concerns have apparently been around >>>> a long time:

    https://groups.google.com/g/comp.lang.forth/c/CApt6AiFkxo/m/wwZmc_Tr1PcJ >>>
    I have read through the thread. It's unclear to me which scientific
    users you have in mind. My impression is that 8 stack items was
    deemed sufficient by many, and preferable (on 387) for efficiency
    reasons.

    AFAICS both Skip Carter (proponent) and Julian Noble were suggesting the
    6 level minimum were inadequate.

    Skip Carter did not post in this thread, but given that he proposed
    the change, he probably found 6 to be too few; or maybe it was just a phenomenon that we also see elsewhere as range anxiety. In any case,
    he made no such proposal to Forth-200x, so apparently the need was not pressing.

    Julian Noble ignored the FP stack size issue in his first posting in
    this thread, unlike the separate FP stack size issue, which he
    supported. So it seems that he did not care about a larger FP stack
    size. In the other posting he endorsed moving FP stack items to the
    data stack, but he did not write why; for all we know he might have
    wanted that as a first step for getting the mantissa, exponent and
    sign of the FP value as integer (and the other direction for
    synthesizing FP numbers from these parts).

    He appears to dislike the idea of standard-imposed minimums (e.g. Carter's suggestion of 16) but suggested:

    a) the user can offload to memory if necessary from
    fpu hardware;

    b) an ANS FLOATING and FLOATING EXT wordset includes
    the necessary hooks to extend the fp stack.

    AFAICS the above are in direct response to hardware-imposed minimums.

    AFAIK all major forths supporting x87 hardware
    offer software stack options.

    Certainly on SwiftForth-4.0 I find no such option, it apparently
    proved unnecessary. The manual mentions fpconfig.f, but no such file
    exists in a SwiftForth-4.0 directory in the versions I have installed.

    There exists such a file on various SwiftForth-3.x versions, but on
    most of our machines SwiftForth-3.x segfaults (I have not investigated
    why; it used to work). Ok, so I found an old system where it does not segfault, but trying to load FP on that system produced no joy:
    ...

    Did you report the issues? SwiftForth for Linux was a late addition.
    AFAIK SwiftForth 4 isn't officially released. How the Windows and
    Linux versions may vary, I've no idea.

    ...
    If I want to switch from the default FP package to a different
    package, I essentially have to take the same steps, I only have to add
    two additional commands before including the FP package; the last
    command for including the SSE implementation becomes:

    vfx64 "integers remove-FP-pack include /nfs/nfstmp/anton/VfxForth64Lin-5.43/Lib/x64/FPSSE64S.fth"

    (A special twist here is that the documentation says that the file is
    called FPSSE64.fth (with only 2 S characters), so I needed a few more
    locate invocations to find the right one).

    If you find the former simple, why not the latter (apart from the documentation mistake)?

    Because the fp (in Win at least) is located in the midst of the dictionary
    and that has consequences. The other thing is choice. Why embed an fp
    package not everyone will necessarily like? AFAICS the 387 hw stack
    limitation is definitely something some folks would rather not deal with.
    The only reason for embedding an fp is when the user can't load the fp
    of their choice and save the result. An example would be a trial product
    in which save is disabled.

    In any case, in almost all cases I use the default FP pack, and here
    the VFX-5 and SwiftForth-4 approach is unbeatable in simplicity.
    Instead of performing the sequence of commands shown above, I just
    start the Forth system, and FP words are ready.

    When doing devel work with VFX fp some years back I really appreciated
    the ease with which I could just 'include' the various fp packages of
    my choice without fear of something going wrong. SwiftForth was a bit
    tricky in this regard as there was one file with multiple settings and
    this sometimes caused grief. IMO separate fp files are the way to go.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From albert@albert@spenarnc.xs4all.nl to comp.lang.forth on Mon Jul 7 11:30:10 2025
    From Newsgroup: comp.lang.forth

    In article <2025Jul6.133027@mips.complang.tuwien.ac.at>,
    Anton Ertl <anton@mips.complang.tuwien.ac.at> wrote:
    <SNIP>
    Skip Carter did not post in this thread, but given that he proposed
    the change, he probably found 6 to be too few; or maybe it was just a >phenomenon that we also see elsewhere as range anxiety. In any case,
    he made no such proposal to Forth-200x, so apparently the need was not >pressing.

    Note that the vast experience Wagner has, trumps the anxiety others
    may or may not have.

    <SNIP>
    In any case, in almost all cases I use the default FP pack, and here
    the VFX-5 and SwiftForth-4 approach is unbeatable in simplicity.
    Instead of performing the sequence of commands shown above, I just
    start the Forth system, and FP words are ready.

    And even
    WANT -fp-
    is not much of a hassle in ciforth.

    <SNIP>


    - anton

    Groetjes Albert
    --
    The Chinese government is satisfied with its military superiority over USA.
    The next 5 year plan has as primary goal to advance life expectancy
    over 80 years, like Western Europe.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Mon Jul 7 13:21:36 2025
    From Newsgroup: comp.lang.forth

    On 07-07-2025 05:48, dxf wrote:
    On 6/07/2025 9:30 pm, Anton Ertl wrote:
    dxf <dxforth@gmail.com> writes:
    On 5/07/2025 6:49 pm, Anton Ertl wrote:
    dxf <dxforth@gmail.com> writes:
    [8 stack items on the FP stack]
    Puzzling because of a thread here not long ago in which scientific users >>>>> appear to suggest the opposite. Such concerns have apparently been around
    a long time:

    https://groups.google.com/g/comp.lang.forth/c/CApt6AiFkxo/m/wwZmc_Tr1PcJ >>>>
    I have read through the thread. It's unclear to me which scientific
    users you have in mind. My impression is that 8 stack items was
    deemed sufficient by many, and preferable (on 387) for efficiency
    reasons.

    AFAICS both Skip Carter (proponent) and Julian Noble were suggesting the >>> 6 level minimum were inadequate.

    Skip Carter did not post in this thread, but given that he proposed
    the change, he probably found 6 to be too few; or maybe it was just a
    phenomenon that we also see elsewhere as range anxiety. In any case,
    he made no such proposal to Forth-200x, so apparently the need was not
    pressing.

    Julian Noble ignored the FP stack size issue in his first posting in
    this thread, unlike the separate FP stack size issue, which he
    supported. So it seems that he did not care about a larger FP stack
    size. In the other posting he endorsed moving FP stack items to the
    data stack, but he did not write why; for all we know he might have
    wanted that as a first step for getting the mantissa, exponent and
    sign of the FP value as integer (and the other direction for
    synthesizing FP numbers from these parts).

    He appears to dislike the idea of standard-imposed minimums (e.g. Carter's suggestion of 16) but suggested:

    a) the user can offload to memory if necessary from
    fpu hardware;

    b) an ANS FLOATING and FLOATING EXT wordset includes
    the necessary hooks to extend the fp stack.

    In 4tH, there are two (highlevel) FP-systems - with 6 predetermined configurations. Configs number 0-2 don't have an FP stack, they use the datastack. 3-5 have a separate FP stack - and double the precision. The standard FP stacksize is 16, you can extend it by defining a constant
    before including the FP libs.

    Hans Bezemer

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Hans Bezemer@the.beez.speaks@gmail.com to comp.lang.forth on Mon Jul 7 14:31:03 2025
    From Newsgroup: comp.lang.forth

    On 03-07-2025 18:47, Ruvim wrote:
    On 2025-07-03 17:11, albert@spenarnc.xs4all.nl wrote:
    In article <1043831$3ggg9$1@dont-email.me>,
    Ruvim  <ruvim.pinka@gmail.com> wrote:
    On 2025-07-02 15:37, albert@spenarnc.xs4all.nl wrote:
    In article <1042s2o$3d58h$1@dont-email.me>,
    Ruvim  <ruvim.pinka@gmail.com> wrote:
    On 2025-06-24 01:03, minforth wrote:
    [...]

    For me, the small syntax extension is a convenience when working
    with longer definitions. A bit contrived (:= synonym for TO):

    : SOME-APP { a f: b c | temp == n: flag z: freq }
    \ inputs: integer a, floats b c
    \ uninitialized: float temp
    \ outputs: integer flag, complex freq
        <: FUNC < ... calc function ... > ;>

    BTW, why do you prefer the special syntax `<: ... ;>`
    over an extension to the existing words `:` and `;`

        : SOME-APP
           [ : FUNC < ... calc function ... > ; ]
           < ... >
        ;

    In this approach the word `:` knows that it's a nested definition and >>>>> behaves accordingly.

    Or it has not even know it, if [ is smart enough to compile a jump to
    after ].

    This can be tricky because the following should work:

       create foo [ 123 , ] [ 456 ,

       : bar  [ ' foo compile, 123 lit, ] ;

    If this bothers you, rename it in [[ ]].

    Once we enhance [ ] to do things prohibited by the standard,
    (adding nested definitions) I can't be bothered with this too much.


    The standard does not prohibit a system from supporting nested
    definitions in whichever way that does not violate the standard behavior.


    Yes, something like "private[ ... ]private" is a possible approach, and
    its implementation seems simpler than adding the smarts to `:` and `;`
    (and other defining words, if any).

    The advantage of this approach over "<: ... ;>" is that you can define
    not only colon-definitions, but also constants, variables, immediate
    words, one-time macros, etc.


      : foo ( F: r.coefficient -- r.result )
        private[
          variable cnt
          0e fvalue k
          : [x] ... ; immediate
        ]private
        to k   0 cnt !
        ...
      ;

    It's also possible to associated the word list of private words with the containing word xt for debugging purposes.

    4tH has always allowed it, since it considered : and ; as branches -
    like AHEAD. Since [: and ;] are just :NONAME and ; aliases they work essentially the same.

    I never used it, because it would cause portability issues - and I
    considered it "bad style".

    The same goes for allocation (VARIABLE, VALUE, STRING, ARRAY). These are
    in 4tH basically just directives - NOTHING IS ACTUALLY ALLOCATED. That
    works just fine.

    So the whole shebang would practically work out of the box. But of
    course, to follow the complete example, I had to do the FP stuff as well
    - and I wanted to do a bit of protecting the words between the tags.

    In short, that boils down to this (for FOO):

    1018| branch 1036 foo
    1019| literal 1020
    1020| branch 1030 <== jump after opcode 1030
    1021| literal 0 <== mantissa 0
    1022| literal 0 <== exponent 0
    1023| variable 2 *k_f
    1024| call 0 2!
    1025| branch 1027 k <== DOES> definition
    1026| variable 2 *k_f
    1027| branch 7 2@ <== end DOES> def.
    1028| branch 1029 [x]
    1029| exit 0
    1030| exit 0 <== end of "private"
    1031| drop 0 <== drop the XT
    1032| variable 2 *k_f
    1033| call 0 2!
    1034| literal 0
    1035| to 1 cnt
    1036| exit 0

    Which is the compilant of this (preprocessor) code:

    :macro ... ;
    :macro private[ [: ;
    :macro ]private ;] drop ;
    :macro 0e 0 S>F ;

    include lib/fp1.4th
    include 4pp/lib/fvalue.4pp

    : foo ( F: r.coefficient -- r.result )
    private[
    variable cnt
    0e fvalue k
    : [x] ... ; immediate
    ]private
    fto k 0 cnt !
    ...
    ;

    100 s>f foo k f. cnt ? cr

    The weird code generated from 1021 - 1027 is the result of this code (generated by the preprocessor):

    0 S>F FLOAT ARRAY k
    AKA k *k_f LATEST F! :REDO k F@ ;

    1. FP "zero" is thrown on the stack;
    2. A variable with the capacity of a "float" is created (FVARIABLE);
    3. Copy that symbol in the symbol table;
    4. Initialize the FP variable;
    5. Create a "DOES>" definition that fetches that value.

    But it *does* work as advertised..

    Hans Bezemer
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Tue Jul 8 13:17:28 2025
    From Newsgroup: comp.lang.forth

    On 7/07/2025 9:21 pm, Hans Bezemer wrote:
    On 07-07-2025 05:48, dxf wrote:
    ...
    He appears to dislike the idea of standard-imposed minimums (e.g. Carter's >> suggestion of 16) but suggested:

       a) the user can offload to memory if necessary from
       fpu hardware;

       b) an ANS FLOATING and FLOATING EXT wordset includes
       the necessary hooks to extend the fp stack.

    In 4tH, there are two (highlevel) FP-systems - with 6 predetermined configurations. Configs number 0-2 don't have an FP stack, they use the datastack. 3-5 have a separate FP stack - and double the precision. The standard FP stacksize is 16, you can extend it by defining a constant before including the FP libs.

    Given the ANS minimum of 6 and recognizing that merely displaying an fp number can
    consume several positions I added another 5 as headroom. I organized it such that
    if the interpreter or ?STACK was invoked, anything more than 6 would report the overflow:

    DX-Forth 4.60 2025-06-25

    Software floating-point (separate stack)

    1e 2e 3e 4e 5e 6e .s 1. 2. 3. 4. 5. 6.000001 <f ok

    7e 7e f-stack?

    Whether it was worth it is hard to say. OTOH users are free to patch those limits
    to anything they like and do a COLD or SAVE-SYSTEM to enact the change.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Paul Rubin@no.email@nospam.invalid to comp.lang.forth on Wed Jul 9 15:10:30 2025
    From Newsgroup: comp.lang.forth

    dxf <dxforth@gmail.com> writes:
    As for SSE2 it wouldn't exist if industry didn't consider
    double-precision adequate.

    SSE2 is/was first and foremost a vectorizing extension, and it has been superseded quite a few times, indicating it was never all that
    adequate. I don't know whether any of its successors support extended precision though.

    W. Kahan was a big believer in extended precision (that's why the 8087
    had it from the start). I believes IEEE specifies both 80 bit and 128
    bit formats in addition to 64 bit. The RISC-V spec includes encodings
    for 128 bit IEEE but I don't know if any RISC-V hardware actually
    implements it. I think there are some IBM mainframe CPUs that have it.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net to comp.lang.forth on Thu Jul 10 02:18:50 2025
    From Newsgroup: comp.lang.forth

    Am 10.07.2025 um 00:10 schrieb Paul Rubin:
    dxf <dxforth@gmail.com> writes:
    As for SSE2 it wouldn't exist if industry didn't consider
    double-precision adequate.

    SSE2 is/was first and foremost a vectorizing extension, and it has been superseded quite a few times, indicating it was never all that
    adequate. I don't know whether any of its successors support extended precision though.

    You don't need 64-bit doubles for signal or image processing.
    Most vector/matrix operations on streaming data don't require
    them either. Whether SSE2 is adequate or not to handle such data
    depends on the application. "Industry" can manage well with 32-bit
    floats or even smaller with non-standard number formats.

    The AVX extension introduced YMM registers that can do simultaneous
    math on four 64-bit double-precision floating-point numbers.
    The intended application domain was scientific computing.

    The determining factors are data througput and storage space.
    Today, with GPUs, speed and power consumption, driven by AI.


    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Thu Jul 10 14:16:18 2025
    From Newsgroup: comp.lang.forth

    On 10/07/2025 8:10 am, Paul Rubin wrote:
    dxf <dxforth@gmail.com> writes:
    As for SSE2 it wouldn't exist if industry didn't consider
    double-precision adequate.

    SSE2 is/was first and foremost a vectorizing extension, and it has been superseded quite a few times, indicating it was never all that
    adequate. I don't know whether any of its successors support extended precision though.

    W. Kahan was a big believer in extended precision (that's why the 8087
    had it from the start). I believes IEEE specifies both 80 bit and 128
    bit formats in addition to 64 bit. The RISC-V spec includes encodings
    for 128 bit IEEE but I don't know if any RISC-V hardware actually
    implements it. I think there are some IBM mainframe CPUs that have it.

    I suspect IEEE simply standardized what had become common practice among implementers. By using 80 bits /internally/ Intel went a long way to
    achieving IEEE's spec for double precision.

    What little I know about SSE2 it's not as well thought out or organized
    as Intel's original effort. E.g. doing something as simple as changing
    sign of an fp number is a pain when NANs are factored in. With the x87,
    Intel 'got it right the first time'. Except for the stack size and
    efforts to fix it.


    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Paul Rubin@no.email@nospam.invalid to comp.lang.forth on Wed Jul 9 21:32:42 2025
    From Newsgroup: comp.lang.forth

    minforth <minforth@gmx.net> writes:
    You don't need 64-bit doubles for signal or image processing.
    Most vector/matrix operations on streaming data don't require
    them either. Whether SSE2 is adequate or not to handle such data
    depends on the application.

    Sure, and for that matter, AI inference uses 8 bit and even 4 bit
    floating point. Kahan on the other hand was interested in engineering
    and scientific applications like PDE solvers (airfoils, fluid dynamics,
    FEM, etc.). That's an area where roundoff error builds up after many iterations, thus extended precision.

    "Industry" can manage well with 32-bit floats or even smaller with non-standard number formats.

    Depends on your notion of "industry".
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Paul Rubin@no.email@nospam.invalid to comp.lang.forth on Wed Jul 9 21:35:20 2025
    From Newsgroup: comp.lang.forth

    dxf <dxforth@gmail.com> writes:
    I suspect IEEE simply standardized what had become common practice among implementers.

    No, it was really new and interesting. https://people.eecs.berkeley.edu/~wkahan/ieee754status/754story.html

    What little I know about SSE2 it's not as well thought out or organized
    as Intel's original effort. E.g. doing something as simple as changing
    sign of an fp number is a pain when NANs are factored in.

    I wonder if later SSE/AVX/whatever versions fixed this stuff.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net to comp.lang.forth on Thu Jul 10 07:37:02 2025
    From Newsgroup: comp.lang.forth

    Am 10.07.2025 um 06:32 schrieb Paul Rubin:
    minforth <minforth@gmx.net> writes:
    You don't need 64-bit doubles for signal or image processing.
    Most vector/matrix operations on streaming data don't require
    them either. Whether SSE2 is adequate or not to handle such data
    depends on the application.

    Sure, and for that matter, AI inference uses 8 bit and even 4 bit
    floating point.

    Or fuzzy control for instance.

    Kahan on the other hand was interested in engineering
    and scientific applications like PDE solvers (airfoils, fluid dynamics,
    FEM, etc.). That's an area where roundoff error builds up after many iterations, thus extended precision.


    That's why I use Kahan summation for dot products. It is slow but
    rounding error accumulation remains small. A while ago I read an
    article about this issue in which the author(s) performed extensive tests
    of different dot product calculation algorithms on many serial
    data sets from finance, geology, oil industry, meteorology etc.
    Their target criterion was to find an acceptable balance between
    computational speed and minimal error.

    The 'winner' was a chained fused-multiply-add algorithm (many
    CPUs/GPUs can perform FMA in hardware) which makes for shorter code
    (good for caching). And it supports speed improvement by
    parallelization (recursive halving of the sets until manageable
    vector size followed by parallel computation).

    I don't do parallelization, but I was still surprised by the good
    results using FMA. In other words, increasing floating-point number
    size is not always the way to go. Anyhow, first step is to select
    the best fp rounding method ....
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Thu Jul 10 15:56:30 2025
    From Newsgroup: comp.lang.forth

    On 10/07/2025 2:35 pm, Paul Rubin wrote:
    dxf <dxforth@gmail.com> writes:
    I suspect IEEE simply standardized what had become common practice among
    implementers.

    No, it was really new and interesting. https://people.eecs.berkeley.edu/~wkahan/ieee754status/754story.html

    What little I know about SSE2 it's not as well thought out or organized
    as Intel's original effort. E.g. doing something as simple as changing
    sign of an fp number is a pain when NANs are factored in.

    I wonder if later SSE/AVX/whatever versions fixed this stuff.

    Actually I was wrong. x87 FCHS (aka FNEGATE) changes the sign bit of a NAN. IEEE doesn't consider NANs to be signed even though x87 implementations may display them that way. The catch with SSE is there's nothing like FCHS or FABS so depending on how one implements them, results vary across implementations.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Paul Rubin@no.email@nospam.invalid to comp.lang.forth on Wed Jul 9 22:59:00 2025
    From Newsgroup: comp.lang.forth

    minforth <minforth@gmx.net> writes:
    I don't do parallelization, but I was still surprised by the good
    results using FMA. In other words, increasing floating-point number
    size is not always the way to go.

    Kahan was an expert in clever numerical algorithms that avoid roundoff
    errors, Kahan summation being one such algorithm. But he realized that
    most programmers don't have the numerics expertise to come up with
    schemes like that. A simpler and usually effective way to avoid
    roundoff error swamping the result is simply to use double or extended precision. So that is what he often suggested.

    Here's an example of a FEM calculation that works well with 80 bit but
    poorly with 64 bit FP:

    https://people.eecs.berkeley.edu/~wkahan/Cantilever.pdf

    Anyhow, first step is to select the best fp rounding method ....

    Kahan advised compiling the program three times, once for each IEEE
    rounding mode. Run all three programs and see if the outputs differ by
    enough to care about. If they do, you have some precision loss to deal
    with somehow, possibly by use of wider floats.

    https://people.eecs.berkeley.edu/~wkahan/Mindless.pdf
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Thu Jul 10 07:47:23 2025
    From Newsgroup: comp.lang.forth

    Paul Rubin <no.email@nospam.invalid> writes:
    dxf <dxforth@gmail.com> writes:
    As for SSE2 it wouldn't exist if industry didn't consider
    double-precision adequate.

    SSE2 is/was first and foremost a vectorizing extension, and it has been >superseded quite a few times, indicating it was never all that
    adequate.

    But SSE2 was also the way to finally implement mainstream floating
    point: double precision instead of extended precision (with its
    double-rounding woes when trying to implement double precision) and
    registers (for which register allocation algorithms have been worked
    on for a long time) instead of the stack. So starting with AMD64
    (which was guaranteed to include SSE2) SSE2 became the preferred
    scalar floating point instruction set, which is also reflected in the
    ABIs on AMD64. And in this function SSE2 has not been superseded.

    Concerning vectors, AVX allows 256 bits of width, eliminates the
    alignment brain damage of SSE/SSE2, and gives us three-address
    instructions. AVX2 gives us integer instructions. The various
    AVX-512 extensions are a mess of overlapping extensions (to be unified
    by AVX10) that generally provide up to 512 bits of width and control
    of individual lanes with mask registers.

    I don't know whether any of its successors support extended
    precision though.

    No.

    W. Kahan was a big believer in extended precision (that's why the 8087
    had it from the start). I believes IEEE specifies both 80 bit and 128
    bit formats in addition to 64 bit.

    Not 80-bit format. binary128 and binary256 are specified.

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2023 proceedings: http://www.euroforth.org/ef23/papers/
    EuroForth 2024 proceedings: http://www.euroforth.org/ef24/papers/
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Thu Jul 10 08:07:02 2025
    From Newsgroup: comp.lang.forth

    dxf <dxforth@gmail.com> writes:
    I suspect IEEE simply standardized what had become common practice among >implementers.

    Not at all. There was no common practice at the time.

    While there was some sentiment to standardize the VAX FP stuff, and as
    far as number formats are concerned, they almost did (IEEE binary32
    uses the same format as the VAX F, IEEE binary64 uses the same format
    as VAX G, and IEEE binary128 uses the same format as VAX H), if we
    ignore the perverse byte order of the VAX formats. However, IEEE FP
    uses a different bias for the exponent, requires implementing denormal
    numbers, infinities and NaNs.

    So actually none of the hardware manufacturers implemented IEEE FP at
    the time, not DEC, not IBM, and not Cray. And yet, industry accepted
    IEEE FP and within a few years all new architectures supported IEEE
    FP, and new models of existing hardware usually also implemented IEEE
    FP.

    By using 80 bits /internally/ Intel went a long way to
    achieving IEEE's spec for double precision.

    The 8087 did not just use 80 bits internally, it exposed them to
    programmers. When Intel released the 8087, IEEE 754 was not finished.
    But Kahan was both active in the standardization community and in the
    8087 development, so you can find his ideas in both. His and Intel's
    idea was that the 8087 would be IEEE standard-conforming, but given
    that the standard came out later, that was not quite the case.

    E.g. doing something as simple as changing
    sign of an fp number is a pain when NANs are factored in.

    I don't see that. When you change the sign of a NaN, it's still a
    NaN.

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2023 proceedings: http://www.euroforth.org/ef23/papers/
    EuroForth 2024 proceedings: http://www.euroforth.org/ef24/papers/
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Thu Jul 10 08:35:49 2025
    From Newsgroup: comp.lang.forth

    dxf <dxforth@gmail.com> writes:
    The catch with SSE is there's nothing like FCHS or FABS
    so depending on how one implements them, results vary across implementations.

    You can see in Gforth how to implement FNEGATE and FABS with SSE2:

    see fnegate
    Code fnegate
    0x000055e6a78a8274: add $0x8,%rbx
    0x000055e6a78a8278: xorpd 0x24d8f(%rip),%xmm15 # 0x55e6a78cd010
    0x000055e6a78a8281: mov %r15,%r9
    0x000055e6a78a8284: mov (%rbx),%rax
    0x000055e6a78a8287: jmp *%rax
    end-code
    ok
    0x55e6a78cd010 16 dump
    55E6A78CD010: 00 00 00 00 00 00 00 80 - 00 00 00 00 00 00 00 00
    ok
    see fabs
    Code fabs
    0x000055e6a78a84fe: add $0x8,%rbx
    0x000055e6a78a8502: andpd 0x24b15(%rip),%xmm15 # 0x55e6a78cd020
    0x000055e6a78a850b: mov %r15,%r9
    0x000055e6a78a850e: mov (%rbx),%rax
    0x000055e6a78a8511: jmp *%rax
    end-code
    ok
    0x55e6a78cd020 16 dump
    55E6A78CD020: FF FF FF FF FF FF FF 7F - 00 00 00 00 00 00 00 00

    The actual implementation is the xorpd instruction for FNEGATE, and in
    the andpd instruction for FABS. The memory locations contain masks:
    for FNEGATE only the sign bit is set, for FABS everything but the sign
    bit is set.

    Sure you can implement FNEGATE and FABS in more complicated ways, but
    you can also implement them in more complicated ways if you use the
    387 instruction set. Here's an example of more complicated
    implementations:

    see fnegate
    FNEGATE
    ( 004C4010 4833C0 ) XOR RAX, RAX
    ( 004C4013 F34D0F7EC8 ) MOVQ XMM9, XMM8
    ( 004C4018 664C0F6EC0 ) MOVQ XMM8, RAX
    ( 004C401D F2450F5CC1 ) SUBSD XMM8, XMM9
    ( 004C4022 C3 ) RET/NEXT
    ( 19 bytes, 5 instructions )
    ok
    see fabs
    FABS
    ( 004C40B0 E8FBEFFFFF ) CALL 004C30B0 FS@
    ( 004C40B5 4885DB ) TEST RBX, RBX
    ( 004C40B8 488B5D00 ) MOV RBX, [RBP]
    ( 004C40BC 488D6D08 ) LEA RBP, [RBP+08]
    ( 004C40C0 0F8D05000000 ) JNL/GE 004C40CB
    ( 004C40C6 E845FFFFFF ) CALL 004C4010 FNEGATE
    ( 004C40CB C3 ) RET/NEXT
    ( 28 bytes, 7 instructions )

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2023 proceedings: http://www.euroforth.org/ef23/papers/
    EuroForth 2024 proceedings: http://www.euroforth.org/ef24/papers/
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Stephen Pelc@stephen@vfxforth.com to comp.lang.forth on Thu Jul 10 08:50:43 2025
    From Newsgroup: comp.lang.forth

    On 10 Jul 2025 at 02:18:50 CEST, "minforth" <minforth@gmx.net> wrote:

    "Industry" can manage well with 32-bit
    floats or even smaller with non-standard number formats.

    My customers beg to differ and some use 128 bit numbers for
    their work. In a construction estimate for one runway for the
    new Hong Kong airport, the cost difference between a 64 bit FP
    calculation and the integer calculation was US 10 million dollars.
    This was for pile capping which involves a large quantity of relatively
    small differences.

    Stephen
    --
    Stephen Pelc, stephen@vfxforth.com
    Wodni & Pelc GmbH
    Vienna, Austria
    Tel: +44 (0)7803 903612, +34 649 662 974 http://www.vfxforth.com/downloads/VfxCommunity/
    free VFX Forth downloads
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net to comp.lang.forth on Thu Jul 10 12:14:24 2025
    From Newsgroup: comp.lang.forth

    Am 10.07.2025 um 10:50 schrieb Stephen Pelc:
    On 10 Jul 2025 at 02:18:50 CEST, "minforth" <minforth@gmx.net> wrote:

    "Industry" can manage well with 32-bit
    floats or even smaller with non-standard number formats.

    My customers beg to differ and some use 128 bit numbers for
    their work. In a construction estimate for one runway for the
    new Hong Kong airport, the cost difference between a 64 bit FP
    calculation and the integer calculation was US 10 million dollars.
    This was for pile capping which involves a large quantity of relatively
    small differences.

    You are right. "Industry" is one of those non-words that should be
    used with care, or avoided altogether, before it becomes a tautology.

    IIRC I only had one real application for 128-bit floats: simulation
    of heat propagation through thick-walled tubes. The simulation
    involved numerical integration which can be prone to error accumulation.
    One variant of MinForth's fp-number wordset can be built with gcc's
    libquadmath library. It is slower, but speed is not always important.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Thu Jul 10 21:09:21 2025
    From Newsgroup: comp.lang.forth

    On 10/07/2025 6:35 pm, Anton Ertl wrote:
    dxf <dxforth@gmail.com> writes:
    The catch with SSE is there's nothing like FCHS or FABS
    so depending on how one implements them, results vary across implementations.

    You can see in Gforth how to implement FNEGATE and FABS with SSE2:

    see fnegate
    Code fnegate
    0x000055e6a78a8274: add $0x8,%rbx
    0x000055e6a78a8278: xorpd 0x24d8f(%rip),%xmm15 # 0x55e6a78cd010
    0x000055e6a78a8281: mov %r15,%r9
    0x000055e6a78a8284: mov (%rbx),%rax
    0x000055e6a78a8287: jmp *%rax
    end-code
    ok
    0x55e6a78cd010 16 dump
    55E6A78CD010: 00 00 00 00 00 00 00 80 - 00 00 00 00 00 00 00 00
    ok
    see fabs
    Code fabs
    0x000055e6a78a84fe: add $0x8,%rbx
    0x000055e6a78a8502: andpd 0x24b15(%rip),%xmm15 # 0x55e6a78cd020
    0x000055e6a78a850b: mov %r15,%r9
    0x000055e6a78a850e: mov (%rbx),%rax
    0x000055e6a78a8511: jmp *%rax
    end-code
    ok
    0x55e6a78cd020 16 dump
    55E6A78CD020: FF FF FF FF FF FF FF 7F - 00 00 00 00 00 00 00 00

    The actual implementation is the xorpd instruction for FNEGATE, and in
    the andpd instruction for FABS. The memory locations contain masks:
    for FNEGATE only the sign bit is set, for FABS everything but the sign
    bit is set.

    Sure you can implement FNEGATE and FABS in more complicated ways, but
    you can also implement them in more complicated ways if you use the
    387 instruction set. Here's an example of more complicated
    implementations:

    see fnegate
    FNEGATE
    ( 004C4010 4833C0 ) XOR RAX, RAX
    ( 004C4013 F34D0F7EC8 ) MOVQ XMM9, XMM8
    ( 004C4018 664C0F6EC0 ) MOVQ XMM8, RAX
    ( 004C401D F2450F5CC1 ) SUBSD XMM8, XMM9
    ( 004C4022 C3 ) RET/NEXT
    ( 19 bytes, 5 instructions )
    ok
    see fabs
    FABS
    ( 004C40B0 E8FBEFFFFF ) CALL 004C30B0 FS@
    ( 004C40B5 4885DB ) TEST RBX, RBX
    ( 004C40B8 488B5D00 ) MOV RBX, [RBP]
    ( 004C40BC 488D6D08 ) LEA RBP, [RBP+08]
    ( 004C40C0 0F8D05000000 ) JNL/GE 004C40CB
    ( 004C40C6 E845FFFFFF ) CALL 004C4010 FNEGATE
    ( 004C40CB C3 ) RET/NEXT
    ( 28 bytes, 7 instructions )

    The latter were basically what was existed in the implementation. As they don't handle -ve zero (or NANs) I swapped them out for the former ones you mention.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Paul Rubin@no.email@nospam.invalid to comp.lang.forth on Thu Jul 10 12:33:52 2025
    From Newsgroup: comp.lang.forth

    anton@mips.complang.tuwien.ac.at (Anton Ertl) writes:
    I believes IEEE specifies both 80 bit and 128 bit formats in addition
    to 64 bit.
    Not 80-bit format. binary128 and binary256 are specified.

    I see, 80 bits is considered double-extended. "The x87 and Motorola
    68881 80-bit formats meet the requirements of the IEEE 754-1985 double
    extended format,[12] as does the IEEE 754 128-bit binary format." (https://en.wikipedia.org/wiki/Extended_precision)

    Interestingly, Kahan's 1997 report on IEEE 754's status does say 80 bit
    is specified. But it sounds like that omits some nuance.

    https://people.eecs.berkeley.edu/~wkahan/ieee754status/IEEE754.PDF
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net to comp.lang.forth on Thu Jul 10 23:16:27 2025
    From Newsgroup: comp.lang.forth

    Am 10.07.2025 um 21:33 schrieb Paul Rubin:
    anton@mips.complang.tuwien.ac.at (Anton Ertl) writes:
    I believes IEEE specifies both 80 bit and 128 bit formats in addition
    to 64 bit.
    Not 80-bit format. binary128 and binary256 are specified.

    I see, 80 bits is considered double-extended. "The x87 and Motorola
    68881 80-bit formats meet the requirements of the IEEE 754-1985 double extended format,[12] as does the IEEE 754 128-bit binary format." (https://en.wikipedia.org/wiki/Extended_precision)

    Interestingly, Kahan's 1997 report on IEEE 754's status does say 80 bit
    is specified. But it sounds like that omits some nuance.

    https://people.eecs.berkeley.edu/~wkahan/ieee754status/IEEE754.PDF

    Kahan was also overly critical of dynamic Unum/Posit formats.

    Time has shown that he was partially wrong: https://spectrum.ieee.org/floating-point-numbers-posits-processor
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Paul Rubin@no.email@nospam.invalid to comp.lang.forth on Thu Jul 10 18:40:32 2025
    From Newsgroup: comp.lang.forth

    minforth <minforth@gmx.net> writes:
    Kahan was also overly critical of dynamic Unum/Posit formats.
    Time has shown that he was partially wrong: https://spectrum.ieee.org/floating-point-numbers-posits-processor

    I don't feel qualified to draw a conclusion from this. I wonder what
    the numerics community thinks, if there is any consensus. I remember
    being dubious of posits when I first heard of them, though Kahan
    probably influenced that. I do know that IEEE 754 took a lot of trouble
    to avoid undesirable behaviours that never would have occurred to most
    of us. No idea how well posits do at that. I guess though, given the continued attention they get, they must be more interesting than I had
    thought.

    I saw one of the posit articles criticizing IEEE 754 because IEEE 754
    addition is not always associative. But that is inherent in how
    floating point arithmetic works, and I don't see how posit addition can
    avoid it. Let a = 1e100, b = -1e100, and c=1. So mathematically,
    a+b+c=1. You should get that from (a+b)+c in your favorite floating
    point format. But a+(b+c) will almost certainly be 0, without very high precision (300+ bits).
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Fri Jul 11 13:13:51 2025
    From Newsgroup: comp.lang.forth

    On 11/07/2025 7:16 am, minforth wrote:
    Am 10.07.2025 um 21:33 schrieb Paul Rubin:
    anton@mips.complang.tuwien.ac.at (Anton Ertl) writes:
    I believes IEEE specifies both 80 bit and 128 bit formats in addition
    to 64 bit.
    Not 80-bit format.  binary128 and binary256 are specified.

    I see, 80 bits is considered double-extended.  "The x87 and Motorola
    68881 80-bit formats meet the requirements of the IEEE 754-1985 double
    extended format,[12] as does the IEEE 754 128-bit binary format."
    (https://en.wikipedia.org/wiki/Extended_precision)

    Interestingly, Kahan's 1997 report on IEEE 754's status does say 80 bit
    is specified.  But it sounds like that omits some nuance.

    https://people.eecs.berkeley.edu/~wkahan/ieee754status/IEEE754.PDF

    Kahan was also overly critical of dynamic Unum/Posit formats.

    Time has shown that he was partially wrong: https://spectrum.ieee.org/floating-point-numbers-posits-processor

    When someone begins with the line it rarely ends well:

    "Twenty years ago anarchy threatened floating-point arithmetic."

    One floating-point to rule them all.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net to comp.lang.forth on Fri Jul 11 05:15:49 2025
    From Newsgroup: comp.lang.forth

    Am 11.07.2025 um 03:40 schrieb Paul Rubin:
    minforth <minforth@gmx.net> writes:
    Kahan was also overly critical of dynamic Unum/Posit formats.
    Time has shown that he was partially wrong:
    https://spectrum.ieee.org/floating-point-numbers-posits-processor

    I don't feel qualified to draw a conclusion from this. I wonder what
    the numerics community thinks, if there is any consensus. I remember
    being dubious of posits when I first heard of them, though Kahan
    probably influenced that. I do know that IEEE 754 took a lot of trouble
    to avoid undesirable behaviours that never would have occurred to most
    of us. No idea how well posits do at that. I guess though, given the continued attention they get, they must be more interesting than I had thought.

    I saw one of the posit articles criticizing IEEE 754 because IEEE 754 addition is not always associative. But that is inherent in how
    floating point arithmetic works, and I don't see how posit addition can
    avoid it. Let a = 1e100, b = -1e100, and c=1. So mathematically,
    a+b+c=1. You should get that from (a+b)+c in your favorite floating
    point format. But a+(b+c) will almost certainly be 0, without very high precision (300+ bits).

    AFAIK Cuda does not support posits (yet). BFLOAT16 etc. still win the
    game, until the AI industry pours big money into the chip foundries
    for posit math GPUs.

    Even then, it is questionable, whether or when it would seep into the general-purpose CPU market.

    For Forthers to play with, of course. ;o)
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Paul Rubin@no.email@nospam.invalid to comp.lang.forth on Thu Jul 10 20:17:55 2025
    From Newsgroup: comp.lang.forth

    dxf <dxforth@gmail.com> writes:
    When someone begins with the line it rarely ends well:
    "Twenty years ago anarchy threatened floating-point arithmetic."
    One floating-point to rule them all.

    This gives a good perspective on posits:

    https://people.eecs.berkeley.edu/~demmel/ma221_Fall20/Dinechin_etal_2019.pdf

    Floating point arithmetic in the 1960s (before my time) was really in a terrible state. Kahan has written about it. Apparently IBM 360
    floating point arithmetic had to be redesigned after the fact, because
    the original version had such weird anomalies.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Fri Jul 11 15:34:49 2025
    From Newsgroup: comp.lang.forth

    On 11/07/2025 1:17 pm, Paul Rubin wrote:
    dxf <dxforth@gmail.com> writes:
    When someone begins with the line it rarely ends well:
    "Twenty years ago anarchy threatened floating-point arithmetic."
    One floating-point to rule them all.

    This gives a good perspective on posits:

    https://people.eecs.berkeley.edu/~demmel/ma221_Fall20/Dinechin_etal_2019.pdf

    Floating point arithmetic in the 1960s (before my time) was really in a terrible state. Kahan has written about it. Apparently IBM 360
    floating point arithmetic had to be redesigned after the fact, because
    the original version had such weird anomalies.

    But was it the case by the mid/late 70's - or certain individuals saw an opportunity to influence the burgeoning microprocessor market? Notions of single and double precision already existed in software floating point -
    most notably in the Microsoft binary format. We're talking apps such as Microsoft's Fortran for CP/M. Back then MS was very serious about quashing
    any issues customers found.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net to comp.lang.forth on Fri Jul 11 09:09:00 2025
    From Newsgroup: comp.lang.forth

    Am 11.07.2025 um 05:17 schrieb Paul Rubin:
    dxf <dxforth@gmail.com> writes:
    When someone begins with the line it rarely ends well:
    "Twenty years ago anarchy threatened floating-point arithmetic."
    One floating-point to rule them all.

    This gives a good perspective on posits:

    https://people.eecs.berkeley.edu/~demmel/ma221_Fall20/Dinechin_etal_2019.pdf


    Quintessence:

    Overburdened or incompetent programmers +
    Posits are tricky beasts ==>
    Programmers _need_ AI co-workers to avoid pitfalls

    Modern times....
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Fri Jul 11 07:02:05 2025
    From Newsgroup: comp.lang.forth

    minforth <minforth@gmx.net> writes:
    Am 10.07.2025 um 21:33 schrieb Paul Rubin:
    Kahan was also overly critical of dynamic Unum/Posit formats.

    Time has shown that he was partially wrong: >https://spectrum.ieee.org/floating-point-numbers-posits-processor

    What is supposed to be partially wrong?

    FP numbers have a number of not-so-nice properties, and John L,
    Gustafson uses that somewhat successfully to sell his alternatives to
    the gullible. The way to do that is to give some examples where
    traditional FP numbers fail and his alternative under consideration
    works. I have looked at a (IIRC) slide deck by Kahan where he shows
    examples where the altenarnative by Gustafson (don't remember which
    one he looked at in that slide deck) fails and traditional FP numbers
    work.

    Where does that leave us? Kahan makes the good argument that
    numerical analysts have worked out techniques to deal with the
    shortcomings of traditional FP numbers for over 70 years. For
    Gustafson's number formats these techniques are not applicable; maybe
    one can find new ones for these number formats, but that's not clear.

    For Posits (Type III Unums), which are close to traditional FP in many respects, one can see how that would work out; while traditional FP
    has a fixed division between mantissa and exponents, in Posits the
    division depends on the size of the exponent. This means that
    reasoning about the accuracy of the computation would have to consider
    the size of the exponent, and is therefore more complex than for
    traditional FP; with a little luck you can produce a result that gives
    an error bound based on the smallest mantissa size, but that error
    bound will be worse than for tranditional FP.

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2023 proceedings: http://www.euroforth.org/ef23/papers/
    EuroForth 2024 proceedings: http://www.euroforth.org/ef24/papers/
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Paul Rubin@no.email@nospam.invalid to comp.lang.forth on Fri Jul 11 00:55:43 2025
    From Newsgroup: comp.lang.forth

    dxf <dxforth@gmail.com> writes:
    But was it the case by the mid/late 70's - or certain individuals saw an opportunity to influence the burgeoning microprocessor market? Notions of single and double precision already existed in software floating point -

    Hardware floating point also had single and double precision. The
    really awful 1960s systems were gone by the mid 70s. But there were a
    lot of competing formats, ranging from bad to mostly-ok. VAX floating
    point was mostly ok, DEC wanted IEEE to adopt it, Kahan was ok with
    that, but Intel thought "go for the best possible". Kahan's
    retrospectives on this stuff are good reading:

    http://people.eecs.berkeley.edu/~wkahan/index.htm

    I've linked a few of them. I liked the quote

    It was remarkable that so many hardware people there, knowing how
    difficult p754 would be, agreed that it should benefit the community
    at large. If it encouraged the production of floating-point software
    and eased the development of reliable software, it would help create a
    larger market for everyone's hardware. This degree of altruism was so
    astonishing that MATLAB's creator Dr. Cleve Moler used to advise
    foreign visitors not to miss the country's two most awesome
    spectacles: the Grand Canyon, and meetings of IEEE p754.

    from http://people.eecs.berkeley.edu/~wkahan/ieee754status/754story.html
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Paul Rubin@no.email@nospam.invalid to comp.lang.forth on Fri Jul 11 01:15:00 2025
    From Newsgroup: comp.lang.forth

    anton@mips.complang.tuwien.ac.at (Anton Ertl) writes:
    I have looked at a (IIRC) slide deck by Kahan where he shows examples
    where the altenarnative by Gustafson (don't remember which one he
    looked at in that slide deck) fails and traditional FP numbers work.

    Maybe this: http://people.eecs.berkeley.edu/~wkahan/UnumSORN.pdf
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Fri Jul 11 07:27:19 2025
    From Newsgroup: comp.lang.forth

    Paul Rubin <no.email@nospam.invalid> writes:
    I guess though, given the
    continued attention they get, they must be more interesting than I had >thought.

    IMO it's the usual case of a somewhat complex topic where existing
    solutions have undesirable properties, and someone promises a solution
    that supposedly solves these problems. The attention comes from the
    problems, not from the merits of the promised solution.

    There has been attention given to research into the philosopher's
    stone for many centuries; I don't think that makes it interesting
    other than as an example of how people fall for promises.

    I saw one of the posit articles criticizing IEEE 754 because IEEE 754 >addition is not always associative. But that is inherent in how
    floating point arithmetic works, and I don't see how posit addition can
    avoid it.

    If you only added posits of a given width, you couldn't. Therefore
    the posit specification also defines quire<n> types, which are
    fixed-point numbers that can represent all the values of the posit<n>
    types plus additional bits such that a sequence of a lot of additions
    does not overflow. If you add the posits using a quire as
    accumulator, and only then convert back to a posit, the whole thing is associative.

    Of course you could also introduce a fixed-point accumulator for
    traditional FP numbers and get the same benefit without using posits
    for the rest.

    A problem is how these accumulator types are represented in
    programming languages. If somebody writes

    0e n 0 ?do a i th f@ f+ loop x f!

    should the 0e be stored in the accumulator, and F+ be translated to an
    addition to the accumulator, and should the F! then convert the
    accumulator to FP? What about

    0e x f! n 0 ?do x f@ a i th f@ f+ x f! loop

    In Forth I would make the accumulator explicit, with separate
    FP-to-accumulator addition operations and explicit accumulator-to-fp conversion, but I expect that many people (across programming
    languages) would prefer an automatic approach that works with existing
    source code. We see that with auto-vectorization.

    How big would the accumulator be? Looking at <https://en.wikipedia.org/wiki/Unum_(number_format)#Quire>, for
    posit32 (the largest format given on the page) the quire32 type would
    have 512 bits, and would allow adding up of 2^151 posit32 numbers.

    Let's see how big an accumulator for binary32 would have to be: There
    are exponents for finite numbers from -126..127, i.e., 254 finite
    exponent values, and 23 mantissa bits, plus the sign bit, so every
    binary32 number can be represented as a 278-bit fixed-point number
    (with scale factor 2^-149). If you want to also allow intermediate
    results of, say, 2^64 additions (good for 97 years of additions at 6G
    additions per second), that increases the accumulator to 342 bits; but
    note that the bigger numbers can only be represented as infinity in
    binary32.

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2023 proceedings: http://www.euroforth.org/ef23/papers/
    EuroForth 2024 proceedings: http://www.euroforth.org/ef24/papers/
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From mhx@mhx@iae.nl (mhx) to comp.lang.forth on Fri Jul 11 08:57:09 2025
    From Newsgroup: comp.lang.forth

    On Fri, 11 Jul 2025 7:55:43 +0000, Paul Rubin wrote:

    dxf <dxforth@gmail.com> writes:
    But was it the case by the mid/late 70's - or certain individuals saw an
    opportunity to influence the burgeoning microprocessor market? Notions
    of
    single and double precision already existed in software floating point -

    Hardware floating point also had single and double precision. The
    really awful 1960s systems were gone by the mid 70s. But there were a
    lot of competing formats, ranging from bad to mostly-ok. VAX floating
    point was mostly ok, DEC wanted IEEE to adopt it, Kahan was ok with
    that, but Intel thought "go for the best possible". Kahan's
    retrospectives on this stuff are good reading:

    What is there not to like with the FPU? It provides 80 bits, which
    is in itself a useful additional format, and should never have problems
    with single and double-precision edge cases. Plus it does all the
    trigonometric and transcendental stuff with a reasonable precision
    out-of-box. The instruction set is very regular and quite Forth-like.
    The only problem is that some languages and companies find it necessary
    to boycott FPU use.

    -marcel

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Fri Jul 11 08:33:12 2025
    From Newsgroup: comp.lang.forth

    dxf <dxforth@gmail.com> writes:
    On 11/07/2025 1:17 pm, Paul Rubin wrote:
    This gives a good perspective on posits:

    https://people.eecs.berkeley.edu/~demmel/ma221_Fall20/Dinechin_etal_2019.pdf

    Yes, that looks ok. One thing I noticed is that they suggest
    implementing the smaller posit formats by intelligent table lookup.
    If we have small bit widths and table lookup, I wonder if we should go
    for any variant of FP (including posits) at all, or if an
    exponent-only (i.e., logarithmic) representation would not be better.
    E.g., for 8 bits, out of the 256 values, 2 would represent infinities,
    one would represent NaN, and one would represent 0, leaving 252
    remaining values. If we use 2^-11 (~1.065) as base B, this would give
    a number range of B^-126=0.000356 to B^125=2635. You can vary B to
    either give a more fine-grained resolution at the expense of a smaller
    number range or a larger number range at the expense of a finer
    resolution. <https://developer.nvidia.com/blog/floating-point-8-an-introduction-to-efficient-lower-precision-ai-training/>
    presents E4M3 with +-448 range, and E5M2 with +-57344 range. But note
    that the next number after 1 is 1.125 for E4M3 and 1.25 for E5M2, both
    more coarse-grained than the 1.065 that an exponent-only format with
    B=2^-11 gives you.

    Addition and subtraction would be performed by table lookup (and would
    almost always be approximate), for multiplication and division an
    integer adder can be used.

    Floating point arithmetic in the 1960s (before my time) was really in a
    terrible state. Kahan has written about it. Apparently IBM 360
    floating point arithmetic had to be redesigned after the fact, because
    the original version had such weird anomalies.

    But was it the case by the mid/late 70's - or certain individuals saw an >opportunity to influence the burgeoning microprocessor market?

    Yes, that's the thing with FP. Some people just do their computations
    and who cares if the results might be an artifact of numerical
    instability. For wheather forecasts, there is no telling if a bad
    prediction is due to a numerical error, due to imperfect measurement
    data, or because of the butterfly effect (which is a convenient
    excuse).

    Other people care more about the results, and perform numerical
    analysis. There are only a few specialists for that, and they have
    asked for and gotten features in IEEE 754 and the hardware that the
    vast majority of programmers never consciously uses, e.g., rounding
    modes or the inexact "exception" (actually a flag, not a Forth
    exception), which allows them to tell if there was a rounding error in
    a computation. But when you use a library designed with the help of
    numerical analysis, you might benefit from the existence of these
    features.

    They have also asked for and gotten things like denormal numbers,
    infinities and NaNs that result in fewer numerical pitfalls for
    programmers who are not numerical analysts. These features may be
    irrelevant for those who do weather prediction, but I expect that
    those who found that binary64 provided by VFX's SSE2-based package was
    not good enough may benefit from such features.

    In any case, FP numbers are used in very diverse ways. Not everybody
    needs all the features, and even fewer features are consciously
    needed, but that's the usual case with things that are not
    custom-taylored for your application.

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2023 proceedings: http://www.euroforth.org/ef23/papers/
    EuroForth 2024 proceedings: http://www.euroforth.org/ef24/papers/
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Fri Jul 11 10:14:49 2025
    From Newsgroup: comp.lang.forth

    Paul Rubin <no.email@nospam.invalid> writes:
    anton@mips.complang.tuwien.ac.at (Anton Ertl) writes:
    I have looked at a (IIRC) slide deck by Kahan where he shows examples
    where the altenarnative by Gustafson (don't remember which one he
    looked at in that slide deck) fails and traditional FP numbers work.

    Maybe this: http://people.eecs.berkeley.edu/~wkahan/UnumSORN.pdf

    Yes.

    Here's a quote:

    | These claims pander to Ignorance and Wishful Thinking.

    That's my impression, too, and not just for Type I unums.

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2023 proceedings: http://www.euroforth.org/ef23/papers/
    EuroForth 2024 proceedings: http://www.euroforth.org/ef24/papers/
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Fri Jul 11 10:22:54 2025
    From Newsgroup: comp.lang.forth

    mhx@iae.nl (mhx) writes:
    What is there not to like with the FPU? It provides 80 bits, which
    is in itself a useful additional format, and should never have problems
    with single and double-precision edge cases.

    If you want to do double precision, using the 387 stack has the
    double-rounding problem <https://en.wikipedia.org/wiki/Rounding#Double_rounding>. Even if you
    limit the mantissa to 53 bits, you still get double rounding when you
    deal with numbers that are denormal numbers in binary64
    representation. Java wanted to give the same results, bit for bit, on
    all hardware, and ran afoul of this until they could switch to SSE2.

    The only problem is that some languages and companies find it necessary
    to boycott FPU use.

    The rest of the industry has standardized on binary64 and binary32,
    and they prefer bit-equivalent results for ease of testing. So as
    soon as SSE2 gave that to them, they flocked to SSE2.

    Another nudge towards binary64 (and binary32) is autovectorization.
    You don't want to get different results depending on whether the
    compiler manages to auto-vectorize a program (and use SSE2 parallel
    (rather than scalar) instructions, AVX, or AVX-512) or not. So you
    also use SSE2 when it fails to auto-vectorize.

    OTOH, e.g., on gcc you can ask for -mfpmath=386, for -mfpmath=sse or
    for -mfpmath=both; or if you define a variable as "long double", it
    will store an 80-bit FP value, and computations involving this
    variable will be done on the 387.

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2023 proceedings: http://www.euroforth.org/ef23/papers/
    EuroForth 2024 proceedings: http://www.euroforth.org/ef24/papers/
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Fri Jul 11 22:35:30 2025
    From Newsgroup: comp.lang.forth

    On 11/07/2025 8:22 pm, Anton Ertl wrote:
    mhx@iae.nl (mhx) writes:
    What is there not to like with the FPU? It provides 80 bits, which
    is in itself a useful additional format, and should never have problems
    with single and double-precision edge cases.

    If you want to do double precision, using the 387 stack has the double-rounding problem <https://en.wikipedia.org/wiki/Rounding#Double_rounding>. Even if you
    limit the mantissa to 53 bits, you still get double rounding when you
    deal with numbers that are denormal numbers in binary64
    representation. Java wanted to give the same results, bit for bit, on
    all hardware, and ran afoul of this until they could switch to SSE2.

    The only problem is that some languages and companies find it necessary
    to boycott FPU use.

    The rest of the industry has standardized on binary64 and binary32,
    and they prefer bit-equivalent results for ease of testing. So as
    soon as SSE2 gave that to them, they flocked to SSE2.
    ...

    I wonder how much of this is academic or trend inspired? AFAICS Forth
    clients haven't flocked to it else vendors would have SSE2 offerings at
    the same level as their x387 packs.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net to comp.lang.forth on Sat Jul 12 06:53:22 2025
    From Newsgroup: comp.lang.forth

    Am 11.07.2025 um 10:33 schrieb Anton Ertl:
    In any case, FP numbers are used in very diverse ways. Not everybody
    needs all the features, and even fewer features are consciously
    needed, but that's the usual case with things that are not
    custom-taylored for your application.


    The strongest application niche for Forth is embedded devices, e.g.
    MCUs. The ADCs often used there have typical bit widths of 12 to 24 bit
    (e.g. 24 bit for audio). So there are definitely areas of application
    for Forth and small floats (after de-/normalization).

    In some PLC/DCS, float24 is the usable width of a 32-bit word, whereby
    the 8 free bits are used as binary companions, e.g. for measured value
    over limit.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Sun Jul 13 09:01:41 2025
    From Newsgroup: comp.lang.forth

    dxf <dxforth@gmail.com> writes:
    On 11/07/2025 8:22 pm, Anton Ertl wrote:
    The rest of the industry has standardized on binary64 and binary32,
    and they prefer bit-equivalent results for ease of testing. So as
    soon as SSE2 gave that to them, they flocked to SSE2.
    ...

    I wonder how much of this is academic or trend inspired?

    Is ease of testing an academic concern or a trend?

    AFAICS Forth
    clients haven't flocked to it else vendors would have SSE2 offerings at
    the same level as their x387 packs.

    For Forth, Inc. and MPE AFAIK their respective IA-32 Forth system was
    the only one with hardware FP for many years, so there probably was
    little pressure from users for bit-identical results with, say, SPARC,
    because they did not have a Forth system that ran on SPARC.

    And when they did their IA-32 systems, SSE2 did not exist, so of
    course they used the 387. Plus, 387 was guaranteed to be available
    with Intel's Pentium and AMD's K5, while SSE2 was only available on
    the Pentium 4 and the Athlon 64; so for many years there was a good
    reason to prefer 387 over SSE2 if you compiled for IA-32. And gcc
    generated 387 code to this day if you ask it to produce code for
    IA-32. Only with AMD64 SSE2 was guaranteed, and only there gcc
    defaults to it if you use float or double. Now SwiftForth and VFX are
    only being ported to AMD64 since a relatively short time.

    And as long as customers did not ask for bit-identical results to
    those on, say, a Raspi, there was little reason to reimplement FP with
    SSE2. I wonder if the development of the SSE2 package for VFX was
    influenced by the availability of VFX for the Raspi.

    These Forth systems also don't do global register allocation or auto-vectorization, so two other reasons why, e.g., C compilers chose
    to use SSE2 on AMD64 (where SSE2 was guaranteed to be available) don't
    exist for them.

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2023 proceedings: http://www.euroforth.org/ef23/papers/
    EuroForth 2024 proceedings: http://www.euroforth.org/ef24/papers/
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Sun Jul 13 21:28:43 2025
    From Newsgroup: comp.lang.forth

    On 13/07/2025 7:01 pm, Anton Ertl wrote:
    ...
    For Forth, Inc. and MPE AFAIK their respective IA-32 Forth system was
    the only one with hardware FP for many years, so there probably was
    little pressure from users for bit-identical results with, say, SPARC, because they did not have a Forth system that ran on SPARC.

    What do you mean by "bit-identical results"? Since SSE2 comes without transcendentals (or basics such as FABS and FNEGATE) and implementers
    are expected to supply their own, if anything, I expect results across platforms and compilers to vary.

    ...
    And as long as customers did not ask for bit-identical results to
    those on, say, a Raspi, there was little reason to reimplement FP with
    SSE2. I wonder if the development of the SSE2 package for VFX was
    influenced by the availability of VFX for the Raspi.

    According to the change log it originally began as software floating
    point for embedded systems and circa 2020 was converted to SSE and x64.
    Perhaps Stephen can advise as to the reasons.


    These Forth systems also don't do global register allocation or auto-vectorization, so two other reasons why, e.g., C compilers chose
    to use SSE2 on AMD64 (where SSE2 was guaranteed to be available) don't
    exist for them.

    - anton

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Mon Jul 14 06:04:13 2025
    From Newsgroup: comp.lang.forth

    dxf <dxforth@gmail.com> writes:
    On 13/07/2025 7:01 pm, Anton Ertl wrote:
    ...
    For Forth, Inc. and MPE AFAIK their respective IA-32 Forth system was
    the only one with hardware FP for many years, so there probably was
    little pressure from users for bit-identical results with, say, SPARC,
    because they did not have a Forth system that ran on SPARC.

    What do you mean by "bit-identical results"? Since SSE2 comes without >transcendentals (or basics such as FABS and FNEGATE) and implementers
    are expected to supply their own, if anything, I expect results across >platforms and compilers to vary.

    There are operations for which IEEE 754 specifies the result to the
    last bit (except that AFAIK the representation of NaNs is not
    specified exactly), among them F+ F- F* F/ FSQRT, probably also
    FNEGATE and FABS. It does not specify the exact result for
    transcendental functions, but if your implementation performs the same bit-exact operations for computing a transcendental function on two
    IEEE 754 compliant platforms, the result will be bit-identical (if it
    is a number). So just use the same implementations of transcentental functions, and your results will be bit-identical; concerning the
    NaNs, if you find a difference, check if the involved values are NaNs.

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2023 proceedings: http://www.euroforth.org/ef23/papers/
    EuroForth 2024 proceedings: http://www.euroforth.org/ef24/papers/
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From peter@peter.noreply@tin.it to comp.lang.forth on Mon Jul 14 09:09:00 2025
    From Newsgroup: comp.lang.forth

    On Mon, 14 Jul 2025 06:04:13 GMT
    anton@mips.complang.tuwien.ac.at (Anton Ertl) wrote:

    dxf <dxforth@gmail.com> writes:
    On 13/07/2025 7:01 pm, Anton Ertl wrote:
    ...
    For Forth, Inc. and MPE AFAIK their respective IA-32 Forth system
    was the only one with hardware FP for many years, so there
    probably was little pressure from users for bit-identical results
    with, say, SPARC, because they did not have a Forth system that
    ran on SPARC.

    What do you mean by "bit-identical results"? Since SSE2 comes
    without transcendentals (or basics such as FABS and FNEGATE) and >implementers are expected to supply their own, if anything, I expect >results across platforms and compilers to vary.

    There are operations for which IEEE 754 specifies the result to the
    last bit (except that AFAIK the representation of NaNs is not
    specified exactly), among them F+ F- F* F/ FSQRT, probably also
    FNEGATE and FABS. It does not specify the exact result for
    transcendental functions, but if your implementation performs the same bit-exact operations for computing a transcendental function on two
    IEEE 754 compliant platforms, the result will be bit-identical (if it
    is a number). So just use the same implementations of transcentental functions, and your results will be bit-identical; concerning the
    NaNs, if you find a difference, check if the involved values are NaNs.

    - anton

    This of course excludes the use of libm or other math libraries provided
    by the distribution. They will change between releases.
    I have with success used fdlibm, that is the base for many others. I
    gives max 1 ulp rounding error. I have now also tested the core-math
    project https://gitlab.inria.fr/core-math/core-math This gives
    correctly rounded functions at the cost of being 10 times the compiled
    size! A complete library with trig, log, pow etc comes in at 500k.

    Peter

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From mhx@mhx@iae.nl (mhx) to comp.lang.forth on Mon Jul 14 07:21:45 2025
    From Newsgroup: comp.lang.forth

    On Mon, 14 Jul 2025 6:04:13 +0000, Anton Ertl wrote:

    [..] if your implementation performs the same
    bit-exact operations for computing a transcendental function on two
    IEEE 754 compliant platforms, the result will be bit-identical (if it
    is a number). So just use the same implementations of transcentental functions, and your results will be bit-identical; concerning the
    NaNs, if you find a difference, check if the involved values are NaNs.

    When e.g. summing the elements of a DP vector, it is hard to see why
    that couldn't be done on the FPU stack (with 80 bits) before (possibly)
    storing the result to a DP variable in memory. I am not sure that Forth
    users would be able to resist that approach.

    -marcel

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Paul Rubin@no.email@nospam.invalid to comp.lang.forth on Mon Jul 14 01:24:03 2025
    From Newsgroup: comp.lang.forth

    anton@mips.complang.tuwien.ac.at (Anton Ertl) writes:
    So just use the same implementations of transcentental functions, and
    your results will be bit-identical

    Same implementations = same FP operations in the exact same order? That
    seems hard to ensure, if the functions are implemented in a language
    that leaves anything up to a compiler.

    Also, in the early implementations x87, 68881, NS320something(?), transcententals were included in the coprocessor and the workings
    weren't visible. There is a proposal to add this to RISC-V (https://libre-soc.org/ztrans_proposal/). It looks like there was an
    AVX-512 ER subset that also does transcententals, but it only appeared
    on some Xeon Phi processors now discontinued (per Wikipedia article on
    AVX). No idea about other processors.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Mon Jul 14 07:50:04 2025
    From Newsgroup: comp.lang.forth

    mhx@iae.nl (mhx) writes:
    On Mon, 14 Jul 2025 6:04:13 +0000, Anton Ertl wrote:

    [..] if your implementation performs the same
    bit-exact operations for computing a transcendental function on two
    IEEE 754 compliant platforms, the result will be bit-identical (if it
    is a number). So just use the same implementations of transcentental
    functions, and your results will be bit-identical; concerning the
    NaNs, if you find a difference, check if the involved values are NaNs.

    When e.g. summing the elements of a DP vector, it is hard to see why
    that couldn't be done on the FPU stack (with 80 bits) before (possibly) >storing the result to a DP variable in memory. I am not sure that Forth
    users would be able to resist that approach.

    The question is: What properties do you want your computation to have?

    1) Bit-identical result to a naively-coded IEEE 754 DP computation?

    2) A more accurate result? How much more accuracy?

    3) More performance?

    If you want 1), there is little alternative to actually performing the operations sequentially, using scalar SSE2 operations.

    If you can live without 1), there's a wide range of options:

    A) Perform the naive summation, but using 80-bit addition. This will
    produce higher accuracy, but limit performance to typically 4
    cycles or so per addition (as does the naive SSE2 approach),
    because the latency of the floating-point addition is 4 cycles or
    so (depending on the actual processor).

    B) Perform vectorized summation using SIMD instructions (e.g.,
    AVX-512), with enough parallel additions (beyond the vector size)
    that either the load unit throughput, the FPU throughput, or the
    instruction issue rate will limit the performance. Reduce the n
    intermediate results to one intermediate result in the end. If I
    give the naive loop to gcc -O3 and allow it to pretend that
    floating-point addition is associative, it produces such a
    computation automatically. The result will typically be a little
    more accurate than the result of 1), because the length of the
    addition chains is lenth(vector)/lanes+ld(lanes) rather than
    length(vector).

    C) Perform tree addition

    a) Using 80-bit addition. This will be faster than sequential
    addition because in many cases several additions can run in
    parallel. It will also be quite accurate because it uses 80-bit
    addition, and because the addition chains are reduced to
    ld(length(vector)).

    b) Using DP addition. This allows to use SIMD instructions for
    increased performance (except near the root of the tree), but the
    accuracy is not as good as with 80-bit addition. It is still
    good because the length of the addition chains is only
    ld(length(vector)).

    D) Use Kahan summation (you must not allow the compiler to pretend
    that FP addition is associative, or this will not work) or one of
    its enhancements. This provides a very high accuracy, but (in case
    of the original Kahan summation) requires four FP operations for
    each summand, and each operation depends on the previous one. So
    you get the latency of 4 FP additions per iteration for a version
    that goes across the array sequentially. You can apply
    vectorization to eliminate the effect of these latencies, but you
    will still see the increased resource consumption. If the vector
    resides in a distant cache or in main memory, the memory limit may
    limit performance more than lack of FPU resources, however.

    E) Sort the vector, then start with the element closest to 0. At
    every step, add the element of the sign other than the current
    intermediate sum that is closest to 0. If there is no such element
    left, add the remaining elements in order, starting with the one
    closest to 0. This is pretty accurate and slower than naive
    addition. At the current relative costs of sorting and FP
    operations, Kahan summation probably dominates over this approach.


    So, as you can see, depending on your objectives there may be more
    attractive ways to add a vector than what you suggested. Your
    suggestion actually looks pretty unattractive, except if your
    objectives are "ease of implementation" and "more accuracy than the
    naive approach".

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2023 proceedings: http://www.euroforth.org/ef23/papers/
    EuroForth 2024 proceedings: http://www.euroforth.org/ef24/papers/
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Mon Jul 14 10:11:57 2025
    From Newsgroup: comp.lang.forth

    Paul Rubin <no.email@nospam.invalid> writes:
    anton@mips.complang.tuwien.ac.at (Anton Ertl) writes:
    So just use the same implementations of transcentental functions, and
    your results will be bit-identical

    Same implementations = same FP operations in the exact same order?

    Same operations with the same data flow. Independent operations can
    be reordered.

    That
    seems hard to ensure, if the functions are implemented in a language
    that leaves anything up to a compiler.

    Even gcc heeds data flow of FP operations unless you tell it with
    -fastmath that anything goes.

    Also, in the early implementations x87, 68881, NS320something(?), >transcententals were included in the coprocessor and the workings
    weren't visible.

    The bigger problem with at least x87 is that math you don't always get bit-identical results even for basic operations such as addition,
    thanks to double rounding. So even if you implement transcendentals
    yourself based basic operations, you can see results that are not bit-identical.

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2023 proceedings: http://www.euroforth.org/ef23/papers/
    EuroForth 2024 proceedings: http://www.euroforth.org/ef24/papers/
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From mhx@mhx@iae.nl (mhx) to comp.lang.forth on Mon Jul 14 18:13:34 2025
    From Newsgroup: comp.lang.forth

    On Mon, 14 Jul 2025 7:50:04 +0000, Anton Ertl wrote:

    mhx@iae.nl (mhx) writes:
    On Mon, 14 Jul 2025 6:04:13 +0000, Anton Ertl wrote:
    [..]
    The question is: What properties do you want your computation to have?
    [..]
    2) A more accurate result? How much more accuracy?

    3) More performance?

    3) + 2). If the result is more accurate, the condition number of
    matrices should be better, resulting in less LU decomposition
    iterations. However, solving the system matrix normally takes
    less than 20% of the total runtime.

    I've never seen *anybody* worry about the numerical accuracy of
    final simulation results.

    [..]
    C) Perform tree addition

    a) Using 80-bit addition. This will be faster than sequential
    addition because in many cases several additions can run in
    parallel. It will also be quite accurate because it uses 80-bit
    addition, and because the addition chains are reduced to
    ld(length(vector)).

    This looks very interesting. I can find Kahan and Neumaier, but
    "tree addition" didn't turn up (There is a suspicious looking
    reliability paper about the approach which surely is not what
    you meant). Or is it pairwise addition what I should look for?

    So, as you can see, depending on your objectives there may be more
    attractive ways to add a vector than what you suggested. Your
    suggestion actually looks pretty unattractive, except if your
    objectives are "ease of implementation" and "more accuracy than the
    naive approach".

    Sure, "ease of implementation" is high on my list too. Life is too
    short.

    Thank you for your wonderful and very useful suggestions.

    -marcel

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Paul Rubin@no.email@nospam.invalid to comp.lang.forth on Mon Jul 14 11:31:24 2025
    From Newsgroup: comp.lang.forth

    mhx@iae.nl (mhx) writes:
    This looks very interesting. I can find Kahan and Neumaier, but
    "tree addition" didn't turn up (There is a suspicious looking
    reliability paper about the approach which surely is not what
    you meant). Or is it pairwise addition what I should look for?

    I think the idea is to treat (say) a 1024 element sum into two
    512-element sums that you compute separately, then add the results
    together. You do the 512-element sums the same way, recursively.
    Sometimes you can parallelize the computations, and depending on the CPU
    you might be able to use vector or SIMD instructions once the chunks are
    small enough.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Tue Jul 15 15:25:51 2025
    From Newsgroup: comp.lang.forth

    Now riscv is the future.

    I don't know. From what I learned, RISC-V
    is strongly compiler-oriented. They wrote,
    for example, that it lacks any condition codes.
    Only conditional branches are predicated on
    examining the contents of registers at the time
    of the branch. No "add with carry" nor "subtract
    with carry". From an assembly point of view, the
    lack of a carry flag is a PITA if you desire to
    do multi-word mathematical manipulation of numbers.

    So it seems, that the RISC-V architecture is intended
    to be used by compilers generating code from high level
    languages. Therefore I rather still prefer that "closed"
    ARM arch. Besides: it's more ubiquitous and cheaper.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net to comp.lang.forth on Wed Jul 16 04:09:09 2025
    From Newsgroup: comp.lang.forth

    Am 15.07.2025 um 17:25 schrieb LIT:
    Now riscv is the future.

    I don't know. From what I learned, RISC-V
    is strongly compiler-oriented. They wrote,
    for example, that it lacks any condition codes.
    Only conditional branches are predicated on
    examining the contents of registers at the time
    of the branch. No "add with carry" nor "subtract
    with carry". From an assembly point of view, the
    lack of a carry flag is a PITA if you desire to
    do multi-word mathematical manipulation of numbers.

    So it seems, that the RISC-V architecture is intended
    to be used by compilers generating code from high level
    languages.

    I read somewhere:
    The standard is now managed by RISC-V International, which
    has more than 3,000 members and which reported that more
    than 10 billion chips containing RISC-V cores had shipped
    by the end of 2022. Many implementations of RISC-V are
    available, both as open-source cores and as commercial
    IP products.

    You call that compiler-oriented???


    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Wed Jul 16 15:21:32 2025
    From Newsgroup: comp.lang.forth

    On 16/07/2025 12:09 pm, minforth wrote:
    Am 15.07.2025 um 17:25 schrieb LIT:
    Now riscv is the future.

    I don't know. From what I learned, RISC-V
    is strongly compiler-oriented. They wrote,
    for example, that it lacks any condition codes.
    Only conditional branches are predicated on
    examining the contents of registers at the time
    of the branch. No "add with carry" nor "subtract
    with carry". From an assembly point of view, the
    lack of a carry flag is a PITA if you desire to
    do multi-word mathematical manipulation of numbers.

    So it seems, that the RISC-V architecture is intended
    to be used by compilers generating code from high level
    languages.

    I read somewhere:
    The standard is now managed by RISC-V International, which
    has more than 3,000 members and which reported that more
    than 10 billion chips containing RISC-V cores had shipped
    by the end of 2022. Many implementations of RISC-V are
    available, both as open-source cores and as commercial
    IP products.

    You call that compiler-oriented???

    It depends on how many are being programmed by the likes of GCC.
    When ATMEL hit the market the manufacturer claimed their chips
    were designed with compilers in mind. Do Arduino users program
    in hand-coded assembler? Do you? It's no longer just the chip's
    features and theoretical performance one has to worry about but
    the compilers too.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net to comp.lang.forth on Wed Jul 16 07:41:26 2025
    From Newsgroup: comp.lang.forth

    Am 16.07.2025 um 07:21 schrieb dxf:
    On 16/07/2025 12:09 pm, minforth wrote:
    Am 15.07.2025 um 17:25 schrieb LIT:
    Now riscv is the future.

    I don't know. From what I learned, RISC-V
    is strongly compiler-oriented. They wrote,
    for example, that it lacks any condition codes.
    Only conditional branches are predicated on
    examining the contents of registers at the time
    of the branch. No "add with carry" nor "subtract
    with carry". From an assembly point of view, the
    lack of a carry flag is a PITA if you desire to
    do multi-word mathematical manipulation of numbers.

    So it seems, that the RISC-V architecture is intended
    to be used by compilers generating code from high level
    languages.

    I read somewhere:
    The standard is now managed by RISC-V International, which
    has more than 3,000 members and which reported that more
    than 10 billion chips containing RISC-V cores had shipped
    by the end of 2022. Many implementations of RISC-V are
    available, both as open-source cores and as commercial
    IP products.

    You call that compiler-oriented???

    It depends on how many are being programmed by the likes of GCC.
    When ATMEL hit the market the manufacturer claimed their chips
    were designed with compilers in mind. Do Arduino users program
    in hand-coded assembler? Do you? It's no longer just the chip's
    features and theoretical performance one has to worry about but
    the compilers too.


    Don't worry, be happy, visit https://riscv.org/

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Wed Jul 16 08:20:04 2025
    From Newsgroup: comp.lang.forth

    Now riscv is the future.

    I don't know. From what I learned, RISC-V
    is strongly compiler-oriented. They wrote,
    for example, that it lacks any condition codes.
    Only conditional branches are predicated on
    examining the contents of registers at the time
    of the branch. No "add with carry" nor "subtract
    with carry". From an assembly point of view, the
    lack of a carry flag is a PITA if you desire to
    do multi-word mathematical manipulation of numbers.

    So it seems, that the RISC-V architecture is intended
    to be used by compilers generating code from high level
    languages.

    I read somewhere:
    The standard is now managed by RISC-V International, which
    has more than 3,000 members and which reported that more
    than 10 billion chips containing RISC-V cores had shipped
    by the end of 2022. Many implementations of RISC-V are
    available, both as open-source cores and as commercial
    IP products.

    You call that compiler-oriented???

    I think it doesn't depend on RISCV members count,
    but on technical specs/abilities of CPU rather.
    Like on the ones I listed, for instance.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Wed Jul 16 08:25:06 2025
    From Newsgroup: comp.lang.forth

    It depends on how many are being programmed by the likes of GCC.
    When ATMEL hit the market the manufacturer claimed their chips
    were designed with compilers in mind. Do Arduino users program
    in hand-coded assembler? Do you? It's no longer just the chip's
    features and theoretical performance one has to worry about but
    the compilers too.

    Regarding features it's worth to mention
    that ATMELs actually are quite nice to
    program them in ML. Even, if they were
    designed "with compilers in mind".

    But when CPU is stripped off SBC/ADC and
    similar... I don't know.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Wed Jul 16 11:25:04 2025
    From Newsgroup: comp.lang.forth

    mhx@iae.nl (mhx) writes:
    On Mon, 14 Jul 2025 7:50:04 +0000, Anton Ertl wrote:
    C) Perform tree addition

    a) Using 80-bit addition. This will be faster than sequential
    addition because in many cases several additions can run in
    parallel. It will also be quite accurate because it uses 80-bit
    addition, and because the addition chains are reduced to
    ld(length(vector)).

    This looks very interesting. I can find Kahan and Neumaier, but
    "tree addition" didn't turn up (There is a suspicious looking
    reliability paper about the approach which surely is not what
    you meant). Or is it pairwise addition what I should look for?

    Yes, "tree addition" is not a common term, and Wikipedia calls it
    pairwise addition. Except that unlike suggeseted in <https://en.wikipedia.org/wiki/Pairwise_summation> I would not switch to
    a sequential approach for small n, for both accuracy and performance.
    In any case the idea is to turn the evaluation tree from a degenerate
    tree into a balanced tree. E.g., if you add up a, b, c, and d, then
    the naive evaluation

    a b f+ c f+ d f+

    has the evaluation tree

    a b
    \ /
    f+ c
    \ /
    f+ d
    \ /
    f+

    with the three F+ each depending on the previous one, and also
    increasing the rounding errors. If you balance the tree

    a b c d
    \ / \ /
    f+ f+
    \ /
    f+

    corresponding to

    a b f+ c d f+ f+

    the first two f+ can run in parallel (increasing performance), and the
    rounding errors tend to be less.

    So how to implement this for an arbitrary N? We had an extensive
    discussion of a similar problem in the thread on the subject "balanced
    REDUCE: a challenge for the brave", and you can find that discussion
    at <https://comp.lang.forth.narkive.com/GIg9V9HK/balanced-reduce-a-challenge-for-the-brave>

    But I decided to use a recursive approach (recursive-sum, REC) that
    uses the largest 2^k<n as the left child and the rest as the right
    child, and as base cases for the recursion use a straight-line
    balanced-tree evaluation for 2^k with k<=7 (and combine these for n
    that are not 2^k). For systems with tiny FP stacks, I added the
    option to save intermediate results on a software stack in the
    recursive word. Concerning the straight-line code, it turned out that
    the highest k I could use on sf64 and vfx64 is 5 (corresponding to 6
    FP stack items); it's not clear to me why; on lxf I can use k=7 (and
    it uses the 387 stack, too).

    I also coded the shift-reduce-sum algorithm (shift-reduce-sum, SR)
    described in <https://en.wikipedia.org/wiki/Pairwise_summation> in
    Forth, because it can make use of Forth's features (such as the FP
    stack) where the C code has to hand-code it. It uses the FP stack
    beyond 8 elements if there are more than 128 elements in the array, so
    it does not work for the benchmark (with 100_000 elements in the
    array) on lxf, sf64, and vfx64. As you will see, this is no loss.

    I also coded the naive, sequential approach (naive-sum, NAI).

    One might argue that the straight-line stuff in REC puts REC at an
    advantage, so i also produced an unrolled version of the naive code (unrolled-sum, UNR) that uses straight-line sequences for adding up to
    2^7 elements to the intermediate result.

    You can find a file containing all these versions, compatibility
    configurations for various Forth systems, and testing and benchmarking
    code and data, on

    https://www.complang.tuwien.ac.at/forth/programs/pairwise-sum.4th

    I did not do any accuracy measurements, but I did performance
    measurements on a Ryzen 5800X:

    cycles:u
    gforth-fast iforth lxf SwiftForth VFX
    3_057_979_501 6_482_017_334 6_087_130_593 6_021_777_424 6_034_560_441 NAI
    6_601_284_920 6_452_716_125 7_001_806_497 6_606_674_147 6_713_703_069 UNR
    3_787_327_724 2_949_273_264 1_641_710_689 7_437_654_901 1_298_257_315 REC
    9_150_679_812 14_634_786_781 SR

    cycles:u
    gforth-fast iforth lxf SwiftForth VFX 13_113_842_702 6_264_132_870 9_011_308_923 11_011_828_048 8_072_637_768 NAI
    6_802_702_884 2_553_418_501 4_238_099_417 11_277_658_203 3_244_590_981 UNR
    9_370_432_755 4_489_562_792 4_955_679_285 12_283_918_226 3_915_367_813 REC 51_113_853_111 29_264_267_850 SR

    The versions used are:
    Gforth 0.7.9_20250625
    iForth 5.1-mini
    lxf 1.7-172-983
    SwiftForth x64-Linux 4.0.0-RC89
    VFX Forth 64 5.43 [build 0199] 2023-11-09

    The ":u" means that I measured what happened at the user-level, not at
    the kernel-level.

    Each benchmark run performs 1G f@ and f+ operations, and the naive
    approach performs 1G iterations of the loop.

    The NAIve and UNRolled results show that performance in both is
    limited by the latency of the F+: 3 cycles for the DP SSE2 operation
    in Gforth-fast, 6 cycles for the 80-bit 387 fadd on the other systems.
    It's unclear to me why UNR is much slower on gforth-fast compared to
    NAI.

    The RECursive balanced-tree sum is faster on iForth, lxf and VFX than
    the NAIve and UNRolled versions. It is slower on Gforth: My guess is
    that, despite all hardware advances, the lack of multi-state stack
    caching in Gforth means that the hardware of the Ryzen 5800X does not
    just see the real data flow, but a lot of additional dependences; or
    it may be related to whatever causes the slowdown for UNRolled.

    The SR (shift-reduce) sum looks cute, but performs so many additional instructions, even on iForth, that it is uncompetetive. It's unclear
    to me what slows it down so much on iForth, however.

    I expect that vectorized implementations using AVX will be several
    times faster than the fastest scalar stuff we see here.

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2025 CFP: http://www.euroforth.org/ef25/cfp.html
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Wed Jul 16 15:39:26 2025
    From Newsgroup: comp.lang.forth

    anton@mips.complang.tuwien.ac.at (Anton Ertl) writes:
    I did not do any accuracy measurements, but I did performance
    measurements on a Ryzen 5800X:

    cycles:u
    gforth-fast iforth lxf SwiftForth VFX 3_057_979_501 6_482_017_334 6_087_130_593 6_021_777_424 6_034_560_441 NAI 6_601_284_920 6_452_716_125 7_001_806_497 6_606_674_147 6_713_703_069 UNR 3_787_327_724 2_949_273_264 1_641_710_689 7_437_654_901 1_298_257_315 REC 9_150_679_812 14_634_786_781 SR

    cycles:u

    This second table is about instructions:u

    gforth-fast iforth lxf SwiftForth VFX
    13_113_842_702 6_264_132_870 9_011_308_923 11_011_828_048 8_072_637_768 NAI
    6_802_702_884 2_553_418_501 4_238_099_417 11_277_658_203 3_244_590_981 UNR 9_370_432_755 4_489_562_792 4_955_679_285 12_283_918_226 3_915_367_813 REC
    51_113_853_111 29_264_267_850 SR

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2025 CFP: http://www.euroforth.org/ef25/cfp.html
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net to comp.lang.forth on Wed Jul 16 18:15:08 2025
    From Newsgroup: comp.lang.forth

    Am 16.07.2025 um 13:25 schrieb Anton Ertl:
    I did not do any accuracy measurements, but I did performance
    measurements
    YMMV but "fast but wrong" would not be my goal. ;-)

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Wed Jul 16 16:02:41 2025
    From Newsgroup: comp.lang.forth

    anton@mips.complang.tuwien.ac.at (Anton Ertl) writes:
    But I decided to use a recursive approach (recursive-sum, REC) that
    uses the largest 2^k<n as the left child and the rest as the right
    child, and as base cases for the recursion use a straight-line
    balanced-tree evaluation for 2^k with k<=7 (and combine these for n
    that are not 2^k). For systems with tiny FP stacks, I added the
    option to save intermediate results on a software stack in the
    recursive word. Concerning the straight-line code, it turned out that
    the highest k I could use on sf64 and vfx64 is 5 (corresponding to 6
    FP stack items); it's not clear to me why; on lxf I can use k=7 (and
    it uses the 387 stack, too).

    Actually, after writing that, I found out the reasons for the FP stack overflows, and in the published versions and the results I use k=7 on
    all systems. It's really easy to leave an FP stack item on the FP
    stack while calling another word, and that's not so good if you do it
    while calling sum128:-).

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2025 CFP: http://www.euroforth.org/ef25/cfp.html
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Wed Jul 16 16:23:03 2025
    From Newsgroup: comp.lang.forth

    minforth <minforth@gmx.net> writes:
    Am 16.07.2025 um 13:25 schrieb Anton Ertl:
    I did not do any accuracy measurements, but I did performance
    measurements
    YMMV but "fast but wrong" would not be my goal. ;-)

    I did test correctness with cases where roundoff errors do not play a
    role.

    As mentioned, the RECursive balanced-tree sum (which is also the
    fastest on several systems and absolutely) is expected to be more
    accurate in those cases where roundoff errors do play a role. But if
    you care about that, better design a test and test it yourself. It
    will be interesting to see how you find out which result is more
    accurate when they differ.

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2025 CFP: http://www.euroforth.org/ef25/cfp.html
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net to comp.lang.forth on Wed Jul 16 19:17:16 2025
    From Newsgroup: comp.lang.forth

    Am 16.07.2025 um 18:23 schrieb Anton Ertl:
    minforth <minforth@gmx.net> writes:
    Am 16.07.2025 um 13:25 schrieb Anton Ertl:
    I did not do any accuracy measurements, but I did performance
    measurements
    YMMV but "fast but wrong" would not be my goal. ;-)

    I did test correctness with cases where roundoff errors do not play a
    role.

    As mentioned, the RECursive balanced-tree sum (which is also the
    fastest on several systems and absolutely) is expected to be more
    accurate in those cases where roundoff errors do play a role. But if
    you care about that, better design a test and test it yourself. It
    will be interesting to see how you find out which result is more
    accurate when they differ.

    Meanwhile many years ago, comparative tests were carried out with a
    couple of representative archived serial data (~50k samples) by
    using a Java 128-bit quadruple fp-math class to perform summations
    and calculate dot-product results.

    The results were compared with those of naive linear summation and multiplication and pairwise divide&conquer summation at different
    rounding modes, for float32 and float64. Ultimately, Kahan summation
    was the winner. It is slow, but there were no in-the-loop
    requirements, so for a background task, Kahan was fast enough.



    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From mhx@mhx@iae.nl (mhx) to comp.lang.forth on Wed Jul 16 21:12:13 2025
    From Newsgroup: comp.lang.forth

    Well, that is strange ...

    Results with the current iForth are quite different:

    FORTH> bench ( see file quoted above + usual iForth timing words )
    \ 7963 times
    \ naive-sum : 0.999 seconds elapsed. ( 4968257259 )
    \ unrolled-sum : 1.004 seconds elapsed. ( 4968257259 )
    \ recursive-sum : 0.443 seconds elapsed. ( 4968257259 )
    \ shift-reduce-sum : 2.324 seconds elapsed. ( 4968257259 ) ok

    So here recursive-sum is by far the fastest, and shift-reduce-sum
    is not horribly slow. The slowdown in srs is because the 2nd loop
    is using the external stack.

    -marcel

    PS: Because of recent user requests a development snapshot was
    made available at the usual place.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Thu Jul 17 15:55:41 2025
    From Newsgroup: comp.lang.forth

    On 16/07/2025 6:25 pm, LIT wrote:
    It depends on how many are being programmed by the likes of GCC.
    When ATMEL hit the market the manufacturer claimed their chips
    were designed with compilers in mind.  Do Arduino users program
    in hand-coded assembler?  Do you?  It's no longer just the chip's
    features and theoretical performance one has to worry about but
    the compilers too.

    Regarding features it's worth to mention
    that ATMELs actually are quite nice to
    program them in ML. Even, if they were
    designed "with compilers in mind".
    ...

    Reminds me of the 6502 for some reason. But it's the 'skip next
    instruction on bit in register' that throws me. Not to mention
    companies that release chips that don't do what the spec says.
    Their solution? Amend the documentation to exclude that feature!

    Didn't get that in the good old days as products were expected to
    have a reasonable lifetime. Today CPU designs are as 'throw away'
    as everything else. No reason to believe RISC-V will be different.
    Only thing distinguishing it are the years of hype and promise.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From peter@peter.noreply@tin.it to comp.lang.forth on Thu Jul 17 10:14:00 2025
    From Newsgroup: comp.lang.forth

    On Wed, 16 Jul 2025 15:39:26 GMT
    anton@mips.complang.tuwien.ac.at (Anton Ertl) wrote:
    anton@mips.complang.tuwien.ac.at (Anton Ertl) writes:
    I did not do any accuracy measurements, but I did performance
    measurements on a Ryzen 5800X:

    cycles:u
    gforth-fast iforth lxf SwiftForth VFX 3_057_979_501 6_482_017_334 6_087_130_593 6_021_777_424 6_034_560_441 NAI
    6_601_284_920 6_452_716_125 7_001_806_497 6_606_674_147 6_713_703_069 UNR
    3_787_327_724 2_949_273_264 1_641_710_689 7_437_654_901 1_298_257_315 REC
    9_150_679_812 14_634_786_781 SR

    cycles:u

    This second table is about instructions:u

    gforth-fast iforth lxf SwiftForth VFX
    13_113_842_702 6_264_132_870 9_011_308_923 11_011_828_048 8_072_637_768 NAI
    6_802_702_884 2_553_418_501 4_238_099_417 11_277_658_203 3_244_590_981 UNR
    9_370_432_755 4_489_562_792 4_955_679_285 12_283_918_226 3_915_367_813 REC
    51_113_853_111 29_264_267_850 SR

    - anton
    I have run this test now on my Ryzen 9950X for lxf, lxf64 ans a snapshot of gforth
    Here are the results
    Ryzen 9950X
    lxf64
    5,010,566,495 NAI cycles:u
    2,011,359,782 UNR cycles:u
    646,926,001 REC cycles:u
    3,589,863,082 SR cycles:u
    lxf64
    7,019,247,519 NAI instructions:u
    4,128,689,843 UNR instructions:u
    4,643,499,656 REC instructions:u
    25,019,182,759 SR instructions:u
    gforth-fast 20250219
    2,048,316,578 NAI cycles:u
    7,157,520,448 UNR cycles:u
    3,589,638,677 REC cycles:u
    17,199,889,916 SR cycles:u
    gforth-fast 20250219
    13,107,999,739 NAI instructions:u
    6,789,041,049 UNR instructions:u
    9,348,969,966 REC instructions:u
    50,108,032,223 SR instructions:u
    lxf
    6,005,617,374 NAI cycles:u
    6,004,157,635 UNR cycles:u
    1,303,627,835 REC cycles:u
    9,187,422,499 SR cycles:u
    lxf
    9,010,888,196 NAI instructions:u
    4,237,679,129 UNR instructions:u
    4,955,258,040 REC instructions:u
    26,018,680,499 SR instructions:u
    Doing the milliseconds timing gives
    lxf64 native code
    timer-reset ' naive-sum bench .elapsed 889 ms elapsed ok
    timer-reset ' unrolled-sum bench .elapsed 360 ms elapsed ok
    timer-reset ' recursive-sum bench .elapsed 114 ms elapsed ok
    timer-reset ' shift-reduce-sum bench .elapsed 647 ms elapsed ok
    lxf64 token code
    timer-reset ' naive-sum bench .elapsed 2284 ms elapsed ok
    timer-reset ' unrolled-sum bench .elapsed 2723 ms elapsed ok
    timer-reset ' recursive-sum bench .elapsed 3474 ms elapsed ok
    timer-reset ' shift-reduce-sum bench .elapsed 6842 ms elapsed ok
    lxf
    timer-reset ' naive-sum bench .elapsed 1073 milli-seconds ok timer-reset ' unrolled-sum bench .elapsed 1103 milli-seconds ok timer-reset ' recursive-sum bench .elapsed 234 milli-seconds ok timer-reset ' shift-reduce-sum bench .elapsed 1632 milli-seconds ok
    It is interesting to note how the Best algorithm" change depending
    on the underlying system implementation.
    lxf uses the x87 builtin fp stack, lxf64 uses sse4 and a large fp stack
    Thanks for these tests, they uncovered a problem with the lxf64 code
    generator. It could only handle 114 immediate values in a basic block!
    Both sum128 and nsum128 compiles gigantic functions of over 2k compile code. Best Regards
    Peter
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From zbigniew2011@zbigniew2011@gmail.com (LIT) to comp.lang.forth on Thu Jul 17 09:35:25 2025
    From Newsgroup: comp.lang.forth

    Reminds me of the 6502 for some reason. But it's the 'skip next
    instruction on bit in register' that throws me.

    Nothing too unusual. It's actually just an abbreviation
    for something like, for example:

    CMP AX, BX
    JZ SHORT skip
    CALL something
    skip: ...

    So instead of separate CMP and JZ we've got
    "CMP?JZ" as single instruction. If not the
    variable size of instruction in x86, one could
    devise a macro. On a second thought: probably
    in A86 it'll be possible to devise such a macro,
    because its macro facility treats macro
    parameters character-wise. So probably a macro
    like 'CMP?JZ reg1,reg2 next_instruction" should
    be possible (I'll try that later).

    PIC features similar instructions (INCFSZ/DECFSZ).
    PIC is actually more 6502-like, with its spartan
    instruction set (when compared to ATMEL).

    Didn't get that in the good old days as products were expected to
    have a reasonable lifetime. Today CPU designs are as 'throw away'
    as everything else. No reason to believe RISC-V will be different.
    Only thing distinguishing it are the years of hype and promise.

    Well, at least x86 and ARM seem to be more 'persistent'.
    Actually they already proved to be.

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Thu Jul 17 12:41:45 2025
    From Newsgroup: comp.lang.forth

    mhx@iae.nl (mhx) writes:
    Well, that is strange ...

    Results with the current iForth are quite different:

    FORTH> bench ( see file quoted above + usual iForth timing words )
    \ 7963 times
    \ naive-sum : 0.999 seconds elapsed. ( 4968257259 )
    \ unrolled-sum : 1.004 seconds elapsed. ( 4968257259 )
    \ recursive-sum : 0.443 seconds elapsed. ( 4968257259 )
    \ shift-reduce-sum : 2.324 seconds elapsed. ( 4968257259 ) ok

    Assuming that you were also using a Ryzen 5800X (or other Zen3-based
    CPU), running at 4.8GHz, accounting for the different number of
    iteratons, and that basically all the elapsed time is due to user
    cycles of our benchmark, I defined:

    : scale s>f 4.8e9 f/ 10000e f/ 7963e f* ;

    The output should be the approximate number of seconds. Here's what I
    get from the cycle:u numbers for iForth 5.1-mini given in the earlier
    postings:

    \ ------------ input ---------- | output
    6_482_017_334 scale 7 5 3 f.rdp 1.07534 ok
    6_452_716_125 scale 7 5 3 f.rdp 1.07048 ok
    2_949_273_264 scale 7 5 3 f.rdp 0.48927 ok
    14_634_786_781 scale 7 5 3 f.rdp 2.42785 ok

    The resulting numbers are not very different from those you show. My measurements include iForth's startup overhead, which may be one
    explanation why they are a little higher.

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2025 CFP: http://www.euroforth.org/ef25/cfp.html
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Thu Jul 17 12:54:29 2025
    From Newsgroup: comp.lang.forth

    peter <peter.noreply@tin.it> writes:
    Ryzen 9950X

    lxf64
    5,010,566,495 NAI cycles:u
    2,011,359,782 UNR cycles:u
    646,926,001 REC cycles:u
    3,589,863,082 SR cycles:u

    lxf64 =20
    7,019,247,519 NAI instructions:u =20
    4,128,689,843 UNR instructions:u =20
    4,643,499,656 REC instructions:u=20
    25,019,182,759 SR instructions:u=20


    gforth-fast 20250219
    2,048,316,578 NAI cycles:u
    7,157,520,448 UNR cycles:u
    3,589,638,677 REC cycles:u
    17,199,889,916 SR cycles:u

    gforth-fast 20250219
    13,107,999,739 NAI instructions:u=20
    6,789,041,049 UNR instructions:u
    9,348,969,966 REC instructions:u=20
    50,108,032,223 SR instructions:u=20

    lxf
    6,005,617,374 NAI cycles:u
    6,004,157,635 UNR cycles:u
    1,303,627,835 REC cycles:u
    9,187,422,499 SR cycles:u

    lxf
    9,010,888,196 NAI instructions:u
    4,237,679,129 UNR instructions:u=20
    4,955,258,040 REC instructions:u=20
    26,018,680,499 SR instructions:u

    lxf uses the x87 builtin fp stack, lxf64 uses sse4 and a large fp stack=20

    Apparently the latency of ADDSD (SSE2) is down to 2 cycles on Zen5
    (visible in lxf64 UNR and gforth-fast NAI) while the latency of FADD
    (387) is still 6 cycles (lxf NAI and UNR). I have no explanation why
    on lxf64 NAI performs so much worse than UNR, and in gforth-fast UNR
    so much worse than NAI.

    For REC the latency should not play a role. There lxf64 performs at
    7.2IPC and 1.55 F+/cycle, whereas lxf performs only at 3.8IPC and 0.77 F+/cycle. My guess is that FADD can only be performed by one FPU, and
    that's connected to one dispatch port, and other instructions also
    need or are at least assigned to this dispatch port.

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2025 CFP: http://www.euroforth.org/ef25/cfp.html
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Thu Jul 17 13:56:36 2025
    From Newsgroup: comp.lang.forth

    minforth <minforth@gmx.net> writes:
    Meanwhile many years ago, comparative tests were carried out with a
    couple of representative archived serial data (~50k samples)

    Representative of what? Serial: what series?

    Anyway, since I don't have these data, I won't repeat this experiment
    with the routines I have written.

    Ultimately, Kahan summation
    was the winner. It is slow, but there were no in-the-loop
    requirements, so for a background task, Kahan was fast enough.

    I wanted to see how slow, so I added KAHAN-SUM to

    https://www.complang.tuwien.ac.at/forth/programs/pairwise-sum.4th

    and on the Ryzen 5800X I got (data for the other routines from the
    earlier posting):

    cycles:u
    gforth-fast iforth lxf SwiftForth VFX
    3_057_979_501 6_482_017_334 6_087_130_593 6_021_777_424 6_034_560_441 NAI
    6_601_284_920 6_452_716_125 7_001_806_497 6_606_674_147 6_713_703_069 UNR
    3_787_327_724 2_949_273_264 1_641_710_689 7_437_654_901 1_298_257_315 REC
    9_150_679_812 14_634_786_781 SR 57_819_112_550 28_621_991_440 28_431_247_791 28_409_857_650 28_462_276_524 KAH

    instructions:u
    gforth-fast iforth lxf SwiftForth VFX 13_113_842_702 6_264_132_870 9_011_308_923 11_011_828_048 8_072_637_768 NAI
    6_802_702_884 2_553_418_501 4_238_099_417 11_277_658_203 3_244_590_981 UNR
    9_370_432_755 4_489_562_792 4_955_679_285 12_283_918_226 3_915_367_813 REC 51_113_853_111 29_264_267_850 SR 54_114_197_272 18_264_494_804 21_011_621_955 27_012_178_800 20_072_845_336 KAH

    The versions used are still:
    Gforth 0.7.9_20250625
    iForth 5.1-mini
    lxf 1.7-172-983
    SwiftForth x64-Linux 4.0.0-RC89
    VFX Forth 64 5.43 [build 0199] 2023-11-09

    KAHan-sum is More than 20 times slower than REC on VFX64. The
    particular slowness of gforth-fast is probably due to the weaknesses
    of FP stack caching in Gforth.

    One can do something like Kahan summation also for pairwise addition.
    The base step (half of the additions) becomes simpler (no compensation
    in any input), but more complicated in the inner additions (one
    compensation each). The main benefit would be that several additions
    can be done in parallel, and the expected error is even smaller.

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2025 CFP: http://www.euroforth.org/ef25/cfp.html
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net to comp.lang.forth on Thu Jul 17 18:02:56 2025
    From Newsgroup: comp.lang.forth

    Am 17.07.2025 um 15:56 schrieb Anton Ertl:
    minforth <minforth@gmx.net> writes:
    Meanwhile many years ago, comparative tests were carried out with a
    couple of representative archived serial data (~50k samples)

    Representative of what? Serial: what series?

    Measured process signals and machine vibrations.
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From peter@peter.noreply@tin.it to comp.lang.forth on Thu Jul 17 22:48:25 2025
    From Newsgroup: comp.lang.forth

    On Thu, 17 Jul 2025 12:54:29 GMT
    anton@mips.complang.tuwien.ac.at (Anton Ertl) wrote:

    peter <peter.noreply@tin.it> writes:
    Ryzen 9950X

    lxf64
    5,010,566,495 NAI cycles:u
    2,011,359,782 UNR cycles:u
    646,926,001 REC cycles:u
    3,589,863,082 SR cycles:u

    lxf64 =20
    7,019,247,519 NAI instructions:u =20
    4,128,689,843 UNR instructions:u =20
    4,643,499,656 REC instructions:u=20
    25,019,182,759 SR instructions:u=20


    gforth-fast 20250219
    2,048,316,578 NAI cycles:u
    7,157,520,448 UNR cycles:u
    3,589,638,677 REC cycles:u
    17,199,889,916 SR cycles:u

    gforth-fast 20250219
    13,107,999,739 NAI instructions:u=20
    6,789,041,049 UNR instructions:u
    9,348,969,966 REC instructions:u=20
    50,108,032,223 SR instructions:u=20

    lxf
    6,005,617,374 NAI cycles:u
    6,004,157,635 UNR cycles:u
    1,303,627,835 REC cycles:u
    9,187,422,499 SR cycles:u

    lxf
    9,010,888,196 NAI instructions:u
    4,237,679,129 UNR instructions:u=20
    4,955,258,040 REC instructions:u=20
    26,018,680,499 SR instructions:u

    lxf uses the x87 builtin fp stack, lxf64 uses sse4 and a large fp stack=20

    Apparently the latency of ADDSD (SSE2) is down to 2 cycles on Zen5
    (visible in lxf64 UNR and gforth-fast NAI) while the latency of FADD
    (387) is still 6 cycles (lxf NAI and UNR). I have no explanation why
    on lxf64 NAI performs so much worse than UNR, and in gforth-fast UNR
    so much worse than NAI.

    For REC the latency should not play a role. There lxf64 performs at
    7.2IPC and 1.55 F+/cycle, whereas lxf performs only at 3.8IPC and 0.77 F+/cycle. My guess is that FADD can only be performed by one FPU, and
    that's connected to one dispatch port, and other instructions also
    need or are at least assigned to this dispatch port.

    - anton

    I did a test coding the sum128 as a code word with avx-512 instructions
    and got the following results

    285,584,376 cycles:u
    941,856,077 instructions:u

    timing was
    timer-reset ' recursive-sum bench .elapsed 51 ms elapsed

    so half the time of the original recursive.
    with 32 zmm registers I could have done a sum256 also

    the code is below for reference
    r13 is the fp stack pointer
    rbx top of stack
    xmm0 top of fp stack

    code asum128

    movsd [r13-0x8], xmm0
    lea r13, [r13-0x8]

    vmovapd zmm0, [rbx]
    vmovapd zmm1, [rbx+64]
    vmovapd zmm2, [rbx+128]
    vmovapd zmm3, [rbx+192]
    vmovapd zmm4, [rbx+256]
    vmovapd zmm5, [rbx+320]
    vmovapd zmm6, [rbx+384]
    vmovapd zmm7, [rbx+448]
    vmovapd zmm8, [rbx+512]
    vmovapd zmm9, [rbx+576]
    vmovapd zmm10, [rbx+640]
    vmovapd zmm11, [rbx+704]
    vmovapd zmm12, [rbx+768]
    vmovapd zmm13, [rbx+832]
    vmovapd zmm14, [rbx+896]
    vmovapd zmm15, [rbx+960]

    vaddpd zmm0, zmm0, zmm1
    vaddpd zmm2, zmm2, zmm3
    vaddpd zmm4, zmm4, zmm5
    vaddpd zmm6, zmm6, zmm7
    vaddpd zmm8, zmm8, zmm9
    vaddpd zmm10, zmm10, zmm11
    vaddpd zmm12, zmm12, zmm13
    vaddpd zmm14, zmm14, zmm15

    vaddpd zmm0, zmm0, zmm2
    vaddpd zmm4, zmm4, zmm6
    vaddpd zmm8, zmm8, zmm10
    vaddpd zmm12, zmm12, zmm14

    vaddpd zmm0, zmm0, zmm4
    vaddpd zmm8, zmm8, zmm12

    vaddpd zmm0, zmm0, zmm8

    ; Horizontal sum of zmm0

    vextractf64x4 ymm1, zmm0, 1
    vaddpd ymm2, ymm1, ymm0

    vextractf64x2 xmm3, ymm2, 1
    vaddpd ymm4, ymm3, ymm2

    vhaddpd xmm0, xmm4, xmm4

    ret
    end-code

    lxf64 uses a modified fasm as the backend assembler
    so full support for all instructions

    BR
    Peter


    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From mhx@mhx@iae.nl (mhx) to comp.lang.forth on Fri Jul 18 05:25:21 2025
    From Newsgroup: comp.lang.forth

    On Thu, 17 Jul 2025 12:41:45 +0000, Anton Ertl wrote:

    mhx@iae.nl (mhx) writes:
    Well, that is strange ...
    [..]
    The output should be the approximate number of seconds. Here's what I
    get from the cycle:u numbers for iForth 5.1-mini given in the earlier postings:

    \ ------------ input ---------- | output
    6_482_017_334 scale 7 5 3 f.rdp 1.07534 ok
    6_452_716_125 scale 7 5 3 f.rdp 1.07048 ok
    2_949_273_264 scale 7 5 3 f.rdp 0.48927 ok
    14_634_786_781 scale 7 5 3 f.rdp 2.42785 ok

    The resulting numbers are not very different from those you show. My measurements include iForth's startup overhead, which may be one
    explanation why they are a little higher.

    You are right, of course. I was confused by the original posting's
    second table (which showed #instructions but was labeled #cycles).

    ( For the record, I used #7963 iterations of the code to get
    approximately 1 second runtime for the naive implementation. )

    -marcel

    --
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Fri Jul 18 17:44:28 2025
    From Newsgroup: comp.lang.forth

    On 14/07/2025 4:04 pm, Anton Ertl wrote:
    dxf <dxforth@gmail.com> writes:
    On 13/07/2025 7:01 pm, Anton Ertl wrote:
    ...
    For Forth, Inc. and MPE AFAIK their respective IA-32 Forth system was
    the only one with hardware FP for many years, so there probably was
    little pressure from users for bit-identical results with, say, SPARC,
    because they did not have a Forth system that ran on SPARC.

    What do you mean by "bit-identical results"? Since SSE2 comes without
    transcendentals (or basics such as FABS and FNEGATE) and implementers
    are expected to supply their own, if anything, I expect results across
    platforms and compilers to vary.

    There are operations for which IEEE 754 specifies the result to the
    last bit (except that AFAIK the representation of NaNs is not
    specified exactly), among them F+ F- F* F/ FSQRT, probably also
    FNEGATE and FABS. It does not specify the exact result for
    transcendental functions, but if your implementation performs the same bit-exact operations for computing a transcendental function on two
    IEEE 754 compliant platforms, the result will be bit-identical (if it
    is a number). So just use the same implementations of transcentental functions, and your results will be bit-identical; concerning the
    NaNs, if you find a difference, check if the involved values are NaNs.

    So in mandating bit-identical results, not only in calculations but also input/output, IEEE 754 is all about giving the illusion of truth in floating-point when, if anything, they should be warning users don't be
    fooled.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Fri Jul 18 15:34:05 2025
    From Newsgroup: comp.lang.forth

    dxf <dxforth@gmail.com> writes:
    So in mandating bit-identical results, not only in calculations but also >input/output

    I don't think that IEEE 754 specifies I/O, but I could be wrong.

    IEEE 754 is all about giving the illusion of truth in
    floating-point when, if anything, they should be warning users don't be >fooled.

    I don't think that IEEE 754 mentions truth. It does, however, specify
    the inexact "exception" (actually a flag), which allows you to find
    out if the results of the computations are exact or if some rounding
    was involved.

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2025 CFP: http://www.euroforth.org/ef25/cfp.html
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Sat Jul 19 10:18:15 2025
    From Newsgroup: comp.lang.forth

    peter <peter.noreply@tin.it> writes:
    I did a test coding the sum128 as a code word with avx-512 instructions
    and got the following results

    285,584,376 cycles:u
    941,856,077 instructions:u

    timing was
    timer-reset ' recursive-sum bench .elapsed 51 ms elapsed

    so half the time of the original recursive.
    with 32 zmm registers I could have done a sum256 also

    One could do sum128 with just 8 registers by performing the adds ASAP,
    i.e., for sum32

    vmovapd zmm0, [rbx]
    vmovapd zmm1, [rbx+64]
    vaddpd zmm0, zmm0, zmm1
    vmovapd zmm1, [rbx+128]
    vmovapd zmm2, [rbx+192]
    vaddpd zmm1, zmm1, zmm2
    vaddpd zmm0, zmm0, zmm1
    ; and then the Horizontal sum

    And you can code this as:

    vmovapd zmm0, [rbx]
    vaddpd zmm0, zmm0, [rbx+64]
    vmovapd zmm1, [rbx+128]
    vaddpd zmm1, zmm1, [rbx+192]
    vaddpd zmm0, zmm0, zmm1
    ; and then the Horizontal sum

    ; Horizontal sum of zmm0

    vextractf64x4 ymm1, zmm0, 1
    vaddpd ymm2, ymm1, ymm0

    vextractf64x2 xmm3, ymm2, 1
    vaddpd ymm4, ymm3, ymm2

    vhaddpd xmm0, xmm4, xmm4

    Instead of doing the horizontal sum once for every sum128, it might be
    more efficient (assuming the whole thing is not
    cache-bandwidth-limited) to have the result of sum128 be a full SIMD
    width, and then add them up with vaddpd instead of addsd, and do the
    horizontal sum once in the end.

    But if the recursive part is to be programmed in Forth, we would need
    a way to represent a SIMD width of data in Forth, maybe with a SIMD
    stack. I see a few problems there:

    * What to do about the mask registers of AVX-512? In the RISC-V
    vector extension masks are stored in regular SIMD registers.

    * There is a trend visible in ARM SVE and the RISC-V Vector extension
    to have support for dealing with loops across longer vectors. Do we
    also need to support something like that.

    For the RISC-V vector extension, see <https://riscv.org/wp-content/uploads/2024/12/15.20-15.55-18.05.06.VEXT-bcn-v1.pdf>

    One way to deal with all that would be to have a long-vector stack and
    have something like my vector wordset
    <https://github.com/AntonErtl/vectors>, where the sum of a vector
    would be a word that is implemented in some lower-level way (e.g.,
    assembly language); the sum of a vector is actually a planned, but not
    yet existing feature of this wordset.

    An advantage of having a (short) SIMD stack would be that one could
    use SIMD operations for other uses where the long-vector wordset looks
    too heavy-weight (or would need optimizations to get rid of the
    long-vector overhead). The question is if enough such uses exist to
    justify adding such a stack.

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2025 CFP: http://www.euroforth.org/ef25/cfp.html
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net to comp.lang.forth on Sat Jul 19 13:53:20 2025
    From Newsgroup: comp.lang.forth

    Am 19.07.2025 um 12:18 schrieb Anton Ertl:

    One way to deal with all that would be to have a long-vector stack and
    have something like my vector wordset
    <https://github.com/AntonErtl/vectors>, where the sum of a vector
    would be a word that is implemented in some lower-level way (e.g.,
    assembly language); the sum of a vector is actually a planned, but not
    yet existing feature of this wordset.


    Not wanting to sound negative, but who in practice adds up long
    vectors, apart from testing compilers and fp-arithmetic?

    Dot products, on the other hand, are fundamental for many linear
    algebra algorithms, eg. matrix multiplication and AI.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From peter@peter.noreply@tin.it to comp.lang.forth on Sat Jul 19 15:24:48 2025
    From Newsgroup: comp.lang.forth

    On Sat, 19 Jul 2025 10:18:15 GMT
    anton@mips.complang.tuwien.ac.at (Anton Ertl) wrote:

    peter <peter.noreply@tin.it> writes:
    I did a test coding the sum128 as a code word with avx-512 instructions
    and got the following results

    285,584,376 cycles:u
    941,856,077 instructions:u

    timing was
    timer-reset ' recursive-sum bench .elapsed 51 ms elapsed

    so half the time of the original recursive.
    with 32 zmm registers I could have done a sum256 also

    One could do sum128 with just 8 registers by performing the adds ASAP,
    i.e., for sum32

    vmovapd zmm0, [rbx]
    vmovapd zmm1, [rbx+64]
    vaddpd zmm0, zmm0, zmm1
    vmovapd zmm1, [rbx+128]
    vmovapd zmm2, [rbx+192]
    vaddpd zmm1, zmm1, zmm2
    vaddpd zmm0, zmm0, zmm1
    ; and then the Horizontal sum

    And you can code this as:

    vmovapd zmm0, [rbx]
    vaddpd zmm0, zmm0, [rbx+64]
    vmovapd zmm1, [rbx+128]
    vaddpd zmm1, zmm1, [rbx+192]
    vaddpd zmm0, zmm0, zmm1
    ; and then the Horizontal sum

    ; Horizontal sum of zmm0

    vextractf64x4 ymm1, zmm0, 1
    vaddpd ymm2, ymm1, ymm0

    vextractf64x2 xmm3, ymm2, 1
    vaddpd ymm4, ymm3, ymm2

    vhaddpd xmm0, xmm4, xmm4

    the simd instructions does also take a memory operand
    I can du sum128 as

    code asum128b

    movsd [r13-0x8], xmm0
    lea r13, [r13-0x8]

    vmovapd zmm0, [rbx]
    vaddpd zmm0, zmm0, [rbx+64]
    vaddpd zmm0, zmm0, [rbx+128]
    vaddpd zmm0, zmm0, [rbx+192]
    vaddpd zmm0, zmm0, [rbx+256]
    vaddpd zmm0, zmm0, [rbx+320]
    vaddpd zmm0, zmm0, [rbx+384]
    vaddpd zmm0, zmm0, [rbx+448]
    vaddpd zmm0, zmm0, [rbx+512]
    vaddpd zmm0, zmm0, [rbx+576]
    vaddpd zmm0, zmm0, [rbx+640]
    vaddpd zmm0, zmm0, [rbx+704]
    vaddpd zmm0, zmm0, [rbx+768]
    vaddpd zmm0, zmm0, [rbx+832]
    vaddpd zmm0, zmm0, [rbx+896]
    vaddpd zmm0, zmm0, [rbx+960]


    ; Horizontal sum of zmm0

    vextractf64x4 ymm1, zmm0, 1
    vaddpd ymm2, ymm1, ymm0

    vextractf64x2 xmm3, ymm2, 1
    vaddpd ymm4, ymm3, ymm2

    vpermilpd xmm5, xmm4, 1
    vaddsd xmm0, xmm4, xmm5


    ret
    end-code

    this compiles to 154 bytes and 25 instructions
    The original sum128 is 2157 bytes and 513 instructions!

    Yes the horizontal sum should just be done once.
    I have only replaced sum128 with simd as a test.
    Later I will do a complete example

    This asum128b does not change the timing but reduces
    the number of instructions

    277,333,790 cycles:u
    834,846,183 instructions:u # 3.01 insn per cycle



    Instead of doing the horizontal sum once for every sum128, it might be
    more efficient (assuming the whole thing is not
    cache-bandwidth-limited) to have the result of sum128 be a full SIMD
    width, and then add them up with vaddpd instead of addsd, and do the horizontal sum once in the end.

    But if the recursive part is to be programmed in Forth, we would need
    a way to represent a SIMD width of data in Forth, maybe with a SIMD
    stack. I see a few problems there:

    * What to do about the mask registers of AVX-512? In the RISC-V
    vector extension masks are stored in regular SIMD registers.

    * There is a trend visible in ARM SVE and the RISC-V Vector extension
    to have support for dealing with loops across longer vectors. Do we
    also need to support something like that.

    For the RISC-V vector extension, see <https://riscv.org/wp-content/uploads/2024/12/15.20-15.55-18.05.06.VEXT-bcn-v1.pdf>

    One way to deal with all that would be to have a long-vector stack and
    have something like my vector wordset
    <https://github.com/AntonErtl/vectors>, where the sum of a vector
    would be a word that is implemented in some lower-level way (e.g.,
    assembly language); the sum of a vector is actually a planned, but not
    yet existing feature of this wordset.

    An advantage of having a (short) SIMD stack would be that one could
    use SIMD operations for other uses where the long-vector wordset looks
    too heavy-weight (or would need optimizations to get rid of the
    long-vector overhead). The question is if enough such uses exist to
    justify adding such a stack.

    - anton

    I will take a look at your vector implementation and see if it can be used
    in lxf64

    BR
    Peter

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Sat Jul 19 14:39:42 2025
    From Newsgroup: comp.lang.forth

    peter <peter.noreply@tin.it> writes:
    On Sat, 19 Jul 2025 10:18:15 GMT
    anton@mips.complang.tuwien.ac.at (Anton Ertl) wrote:
    [sum32][
    vmovapd zmm0, [rbx]
    vaddpd zmm0, zmm0, [rbx+64]
    vmovapd zmm1, [rbx+128]
    vaddpd zmm1, zmm1, [rbx+192]
    vaddpd zmm0, zmm0, zmm1
    ; and then the Horizontal sum

    ; Horizontal sum of zmm0

    vextractf64x4 ymm1, zmm0, 1
    vaddpd ymm2, ymm1, ymm0

    vextractf64x2 xmm3, ymm2, 1
    vaddpd ymm4, ymm3, ymm2

    vhaddpd xmm0, xmm4, xmm4

    the simd instructions does also take a memory operand
    I can du sum128 as

    code asum128b

    movsd [r13-0x8], xmm0
    lea r13, [r13-0x8]

    vmovapd zmm0, [rbx]
    vaddpd zmm0, zmm0, [rbx+64]
    vaddpd zmm0, zmm0, [rbx+128]
    vaddpd zmm0, zmm0, [rbx+192]
    vaddpd zmm0, zmm0, [rbx+256]
    vaddpd zmm0, zmm0, [rbx+320]
    vaddpd zmm0, zmm0, [rbx+384]
    vaddpd zmm0, zmm0, [rbx+448]
    vaddpd zmm0, zmm0, [rbx+512]
    vaddpd zmm0, zmm0, [rbx+576]
    vaddpd zmm0, zmm0, [rbx+640]
    vaddpd zmm0, zmm0, [rbx+704]
    vaddpd zmm0, zmm0, [rbx+768]
    vaddpd zmm0, zmm0, [rbx+832]
    vaddpd zmm0, zmm0, [rbx+896]
    vaddpd zmm0, zmm0, [rbx+960]

    Yes, but that's not pairwise addition, so for these 16 adds you get
    worse avarage accuracy; if the CPU has limited OoO bufferering (maybe
    one of the Xeon Phis, but not anything modern that has AVX or
    AVX-512), you may also see some of the addition latency. You still
    get pairwise addition and its accuracy benefit for the horizontal sum
    and the recursive parts.

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2025 CFP: http://www.euroforth.org/ef25/cfp.html
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From anton@anton@mips.complang.tuwien.ac.at (Anton Ertl) to comp.lang.forth on Sat Jul 19 14:51:00 2025
    From Newsgroup: comp.lang.forth

    minforth <minforth@gmx.net> writes:
    Am 19.07.2025 um 12:18 schrieb Anton Ertl:

    One way to deal with all that would be to have a long-vector stack and
    have something like my vector wordset
    <https://github.com/AntonErtl/vectors>, where the sum of a vector
    would be a word that is implemented in some lower-level way (e.g.,
    assembly language); the sum of a vector is actually a planned, but not
    yet existing feature of this wordset.


    Not wanting to sound negative, but who in practice adds up long
    vectors, apart from testing compilers and fp-arithmetic?

    Everyone who does dot-products.

    Dot products, on the other hand, are fundamental for many linear
    algebra algorithms, eg. matrix multiplication and AI.

    If I add a vector-sum word

    df+red ( dfv -- r )
    \ r is the sum of the elements of dfv

    to the vector wordset, then the dot-product is:

    : dot-product ( dfv1 dfv2 -- r )
    df*v df+red ;

    Concerning matrix multiplication, while you can use the dot-product
    for it, there are many other ways to do it, and some are more
    efficient (although, admittedly, I have not used pairwise addition for
    these ways).

    - anton
    --
    M. Anton Ertl http://www.complang.tuwien.ac.at/anton/home.html
    comp.lang.forth FAQs: http://www.complang.tuwien.ac.at/forth/faq/toc.html
    New standard: https://forth-standard.org/
    EuroForth 2025 CFP: http://www.euroforth.org/ef25/cfp.html
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Sun Jul 20 13:16:17 2025
    From Newsgroup: comp.lang.forth

    On 19/07/2025 1:34 am, Anton Ertl wrote:
    dxf <dxforth@gmail.com> writes:
    So in mandating bit-identical results, not only in calculations but also
    input/output

    I don't think that IEEE 754 specifies I/O, but I could be wrong.

    They specify converting to/from external representation (aka ASCII).
    If the hardware does it for me - fine - but as an fp implementer no
    way am I going to jump hoops for IEEE.

    IEEE 754 is all about giving the illusion of truth in
    floating-point when, if anything, they should be warning users don't be
    fooled.

    I don't think that IEEE 754 mentions truth. It does, however, specify
    the inexact "exception" (actually a flag), which allows you to find
    out if the results of the computations are exact or if some rounding
    was involved.

    AFAICS IEEE 754 offers nothing particularly useful for the end-user.
    Either one's fp application works - or it doesn't. IEEE hasn't changed
    that. IEEE's relevance is that it spurred Intel into making an FPU
    which in turn made implementing fp easy. Had Intel not integrated their
    FPU into the CPU effectively reducing the cost to the end-user to zero,
    IEEE would have remained a novelty.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From minforth@minforth@gmx.net to comp.lang.forth on Sun Jul 20 06:27:53 2025
    From Newsgroup: comp.lang.forth

    Am 19.07.2025 um 16:51 schrieb Anton Ertl:
    minforth <minforth@gmx.net> writes:
    Am 19.07.2025 um 12:18 schrieb Anton Ertl:

    One way to deal with all that would be to have a long-vector stack and
    have something like my vector wordset
    <https://github.com/AntonErtl/vectors>, where the sum of a vector
    would be a word that is implemented in some lower-level way (e.g.,
    assembly language); the sum of a vector is actually a planned, but not
    yet existing feature of this wordset.


    Not wanting to sound negative, but who in practice adds up long
    vectors, apart from testing compilers and fp-arithmetic?

    Everyone who does dot-products.

    Dot products, on the other hand, are fundamental for many linear
    algebra algorithms, eg. matrix multiplication and AI.

    If I add a vector-sum word

    df+red ( dfv -- r )
    \ r is the sum of the elements of dfv

    to the vector wordset, then the dot-product is:

    : dot-product ( dfv1 dfv2 -- r )
    df*v df+red ;

    Sure, slow hand is not just for guitar players.
    With FMA, one could traverse the vectors in one go.

    https://docs.nvidia.com/cuda/floating-point/index.html

    Concerning matrix multiplication, while you can use the dot-product
    for it, there are many other ways to do it, and some are more
    efficient (although, admittedly, I have not used pairwise addition for
    these ways).

    There are tons of algorithms depending on various matrix properties.

    Then, given a desktop and a fat CPU, LAPACK et al. are your friends.
    Embedded or special CPU .. is a different story.






    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From Paul Rubin@no.email@nospam.invalid to comp.lang.forth on Mon Jul 21 13:28:11 2025
    From Newsgroup: comp.lang.forth

    dxf <dxforth@gmail.com> writes:
    AFAICS IEEE 754 offers nothing particularly useful for the end-user.
    Either one's fp application works - or it doesn't. IEEE hasn't
    changed that.

    The purpose of IEEE FP was to improve the numerical accuracy of
    applications that used it as opposed to other formats.

    IEEE's relevance is that it spurred Intel into making an FPU which in
    turn made implementing fp easy.

    Exactly the opposite, Intel decided that it wanted to make an FPU and it
    wanted the FPU to have the best FP arithmetic possible. So it
    commissioned Kahan (a renowned FP expert) to design the FP format.
    Kahan said "Why not use the VAX format? It is pretty good". Intel said
    it didn't want pretty good, it wanted the best, so Kahan said "ok" and
    designed the 8087 format.

    The IEEE standardization process happened AFTER the 8087 was already in progress. Other manufacturers signed onto it, some of them overcoming
    initial resistance, after becoming convinced that it was the right
    thing.

    http://people.eecs.berkeley.edu/~wkahan/ieee754status/754story.html
    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Tue Jul 22 11:52:04 2025
    From Newsgroup: comp.lang.forth

    On 22/07/2025 6:28 am, Paul Rubin wrote:
    dxf <dxforth@gmail.com> writes:
    AFAICS IEEE 754 offers nothing particularly useful for the end-user.
    Either one's fp application works - or it doesn't. IEEE hasn't
    changed that.

    The purpose of IEEE FP was to improve the numerical accuracy of
    applications that used it as opposed to other formats.

    IEEE's relevance is that it spurred Intel into making an FPU which in
    turn made implementing fp easy.

    Exactly the opposite, Intel decided that it wanted to make an FPU and it wanted the FPU to have the best FP arithmetic possible. So it
    commissioned Kahan (a renowned FP expert) to design the FP format.
    Kahan said "Why not use the VAX format? It is pretty good". Intel said
    it didn't want pretty good, it wanted the best, so Kahan said "ok" and designed the 8087 format.

    The IEEE standardization process happened AFTER the 8087 was already in progress. Other manufacturers signed onto it, some of them overcoming initial resistance, after becoming convinced that it was the right
    thing.

    http://people.eecs.berkeley.edu/~wkahan/ieee754status/754story.html

    There's nothing intrinsically "best" in IEEE's format. Best product
    on the market is what Intel wanted. It had been selling AMD's 9511 single-precision FPU under licence. As Kahan says, wind of what Intel
    was doing got out and industry's response was to create a standard
    that even Intel couldn't ignore.

    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From B. Pym@Nobody447095@here-nor-there.org to comp.lang.forth on Tue Jul 29 15:07:23 2025
    From Newsgroup: comp.lang.forth

    B. Pym wrote:

    mhx wrote:

    On Sun, 6 Oct 2024 7:51:31 +0000, dxf wrote:

    Is there an easier way of doing this? End goal is a double number representing centi-secs.


    empty decimal

    : SPLIT ( a u c -- a2 u2 a3 u3 ) >r 2dup r> scan 2swap 2 pick - ;
    : >INT ( adr len -- u ) 0 0 2swap >number 2drop drop ;

    : /T ( a u -- $hour $min $sec )
    2 0 do [char] : split 2swap dup if 1 /string then loop
    2 0 do dup 0= if 2rot 2rot then loop ;

    : .T 2swap 2rot cr >int . ." hr " >int . ." min " >int . ." sec " ;

    s" 1:2:3" /t .t
    s" 02:03" /t .t
    s" 03" /t .t
    s" 23:59:59" /t .t
    s" 0:00:03" /t .t

    Why don't you use the fact that >NUMBER returns the given
    string starting with the first unconverted character?
    SPLIT should be redundant.

    -marcel

    : CHAR-NUMERIC? 48 58 WITHIN ;
    : SKIP-NON-NUMERIC ( adr u -- adr2 u2)
    BEGIN
    DUP IF OVER C@ CHAR-NUMERIC? NOT ELSE 0 THEN
    WHILE
    1 /STRING
    REPEAT ;

    : SCAN-NEXT-NUMBER ( n adr len -- n2 adr2 len2)
    2>R 60 * 0. 2R> >NUMBER
    2>R D>S + 2R> ;

    : PARSE-TIME ( adr len -- seconds)
    0 -ROT
    BEGIN
    SKIP-NON-NUMERIC
    DUP
    WHILE
    SCAN-NEXT-NUMBER
    REPEAT
    2DROP ;

    S" hello 1::36 world" PARSE-TIME CR .
    96 ok


    : get-number ( accum adr len -- accum' adr' len' )
    { adr len }
    0. adr len >number { adr' len' }
    len len' =
    if
    2drop adr len 1 /string
    else
    d>s swap 60 * +
    adr' len'
    then ;

    : parse-time ( adr len -- seconds)
    0 -rot
    begin
    dup
    while
    get-number
    repeat
    2drop ;

    s" foo-bar" parse-time . 0
    s" foo55bar" parse-time . 55
    s" foo 1 bar 55 zoo" parse-time . 155
    s" and9foo 1 bar 55 zoo" parse-time . 32515


    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From B. Pym@Nobody447095@here-nor-there.org to comp.lang.forth on Tue Jul 29 15:22:17 2025
    From Newsgroup: comp.lang.forth

    B. Pym wrote:


    : get-number ( accum adr len -- accum' adr' len' )
    { adr len }
    0. adr len >number { adr' len' }
    len len' =
    if
    2drop adr len 1 /string
    else
    d>s swap 60 * +
    adr' len'
    then ;

    : parse-time ( adr len -- seconds)
    0 -rot
    begin
    dup
    while
    get-number
    repeat
    2drop ;

    s" foo-bar" parse-time . 0
    s" foo55bar" parse-time . 55
    s" foo 1 bar 55 zoo" parse-time . 155

    Actually prints 115.


    --- Synchronet 3.21a-Linux NewsLink 1.2
  • From dxf@dxforth@gmail.com to comp.lang.forth on Wed Jul 30 03:35:09 2025
    From Newsgroup: comp.lang.forth

    On 30/07/2025 1:07 am, B. Pym wrote:
    ...
    : get-number ( accum adr len -- accum' adr' len' )
    { adr len }
    0. adr len >number { adr' len' }
    len len' =
    if
    2drop adr len 1 /string
    else
    d>s swap 60 * +
    adr' len'
    then ;

    : parse-time ( adr len -- seconds)
    0 -rot
    begin
    dup
    while
    get-number
    repeat
    2drop ;

    s" foo-bar" parse-time . 0
    s" foo55bar" parse-time . 55
    s" foo 1 bar 55 zoo" parse-time . 155
    s" and9foo 1 bar 55 zoo" parse-time . 32515

    : digit? ( c -- f ) 48 58 within ;

    : scan-digit ( a u -- a' u' )
    begin dup while
    over c@ digit? 0= while 1 /string
    repeat then ;

    : /number ( a u -- a' u' u2 )
    0. 2swap >number 2swap drop ;

    : parse-time ( adr len -- seconds)
    0 begin >r scan-digit dup while
    /number r> 60 * +
    repeat 2drop r> ;

    s" foo-bar" parse-time . 0 ok
    s" foo55bar" parse-time . 55 ok
    s" foo 1 bar 55 zoo" parse-time . 115 ok
    s" and9foo 1 bar 55 zoo" parse-time . 32515 ok

    --- Synchronet 3.21a-Linux NewsLink 1.2