6502.org Forum  Projects  Code  Documents  Tools  Forum
It is currently Thu May 09, 2024 1:49 pm

All times are UTC




Post new topic Reply to topic  [ 12 posts ] 
Author Message
 Post subject: M/ vs U/
PostPosted: Tue Feb 15, 2022 4:38 am 
Offline

Joined: Sun Apr 26, 2020 3:08 am
Posts: 357
I understand the difference to be U/ is unsigned division whereas M/ is signed division.

I have seen some very compact code for U/ programmed for the 65816. And have been trying to convert the Forth definition of M/ to a primitive.

The forth definition for M/ being:
Code:
: M/ ( d n1 -- rem quot ) OVER >R >R DABS R ABS U/ R> R XOR +- SWAP R> +- SWAP ;

I basically converted straight from Forth to Assembly. It wasn't worth putting "ABS, DABS or +-" into routines as they add quite a bit of code elsewhere, so I put the ensuing code inline. But this adds quite a bit to the length of M/ (70 assembled vs 32 Forth).

Just wondering if someone is savvy enough to make M/ into a compact primitive using 16-bit 65816 instructions and willing to share?


Top
 Profile  
Reply with quote  
 Post subject: Re: M/ vs U/
PostPosted: Tue Feb 15, 2022 5:12 am 
Offline
User avatar

Joined: Fri Aug 30, 2002 1:09 am
Posts: 8432
Location: Southern California
It should just be
Code:
: M/  M/MOD  NIP  ;

The "M" of course means "mixed-precision," and yes, it's signed. The unsigned would be UM/MOD which I show at http://6502.org/source/integers/ummodfix/ummodfix.htm with the common bug fixed. M/MOD is not in Starting Forth; but the definition I have for it is:
Code:
: M/MOD         ( d n -- rem quot )     \                              not in SF
   ?DUP
   IF
      DUP >R 2DUP XOR >R >R DABS R@ ABS UM/MOD
      R> 0<
      IF SWAP NEGATE SWAP THEN
      R> 0<
      IF NEGATE OVER
         IF 1- R@ ROT - SWAP THEN
      THEN  R> DROP EXIT
   THEN TRUE ABORT" /0 in UM/MOD"       ;

I figured it out at some point, but it'll take time to wrap my head around it again.

Related ones I have are:
Code:
: /MOD          ( n1 n2 -- rem quot )   \       SF39-40  F83  ANS
   >R  S>D  R> M/MOD    ;


: U/MOD         ( u1 u2 -- rem quot )   \ My own.  Faster than /MOD if you don't
   0  SWAP  UM/MOD      ;               \ need to deal with negative numbers.


: /             ( n1 n2 -- quot )       \       SF32  F83  ANS
   /MOD  NIP            ;


: U/            ( u1 u2 -- quot )       \ My own.  Faster than / if you don't
   U/MOD NIP            ;               \ need to deal with negative numbers.


: MOD           ( n1 n2 -- rem )        \       SF39-40  F83  ANS
   /MOD  DROP           ;


: UMOD          ( u1 u2 -- rem )        \ My own.  Faster than MOD if you don't
   U/MOD DROP           ;               \ need to deal with negative numbers.

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


Top
 Profile  
Reply with quote  
 Post subject: Re: M/ vs U/
PostPosted: Tue Feb 15, 2022 8:43 am 
Offline

Joined: Sun Apr 26, 2020 3:08 am
Posts: 357
Thanks for that. Basically my M/ is the same as your M/MOD as they are supposed to do the same thing and I can see mine has a bug in it. I thought I was getting some erroneous results on my negative divisions.

Then it is your M/MOD that I was hoping someone had it converted to a primitive definition as it is quite long. It basically does a lot of NEGATE'ing of both the Dividend and Divisor both before and after the unsigned division.

Was just wondering if there was a simpler, shorter way to cut to the chase?


Top
 Profile  
Reply with quote  
 Post subject: Re: M/ vs U/
PostPosted: Tue Feb 15, 2022 9:37 am 
Offline
User avatar

Joined: Fri Aug 30, 2002 1:09 am
Posts: 8432
Location: Southern California
It's probably because of the floored division. It would be a matter of taking the time to twist my brain around it again; but somehow the difference between floored and symmetrical division hasn't come into play in my particular uses.

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


Top
 Profile  
Reply with quote  
 Post subject: Re: M/ vs U/
PostPosted: Wed Feb 16, 2022 12:12 am 
Offline

Joined: Sun Apr 26, 2020 3:08 am
Posts: 357
Garth: since my Forth word definitions are from an older out-dated Forth and are not made public anywhere, I think I will instead convert the definitions you posted to use with 65816 version I am working on. Most of the definitions are the same, just different wording being used.

Since I am winding down and getting close to being done, I should also confirm your numeric output and digit formatting word definitions. It will make what I am doing more compatible with what is mostly already out on the net. Thanks.

HOLD
<#
#
#>
SIGN
#S
D.R
D.
.R
and .


Top
 Profile  
Reply with quote  
 Post subject: Re: M/ vs U/
PostPosted: Wed Feb 16, 2022 3:56 am 
Offline
User avatar

Joined: Fri Aug 30, 2002 1:09 am
Posts: 8432
Location: Southern California
IamRob wrote:
Garth: since my Forth word definitions are from an older out-dated Forth and are not made public anywhere,

I have not gotten into the newer Forth standards (ANS, 2012, and maybe others), partly because they seem unnecessarily complex for what I do, and I don't think I would live long enough to make my Forth ANS-compliant. I have posted some of the following before, but it's relevant to your quote to repeat it. Skip down to the part after your next quote if you like.

There are also some parts of ANS Forth that present extra overhead in order to make it more portable across a wide range of processors. My personal opinion is that hey may have taken this a little too far. At some point, we need to acknowledge that no language that lets you get so close to the heart of the computer will be 100% portable. We must consider the programmer(s) and platform(s) involved, and decide on a good balance between portability and optimization. I personally prefer a little more optimization at the expense of some portability. Greater optimization means a particular processor can be used for a wider range of jobs anyway, which would in itself reduce the need for portability.

Jack Woehr, a senior project manager for Vesta Technologies, who was on the X3J14 committee, says in his book "Forth: The New Model", "When Forth, which some hold to be inextricably wedded to hardware, takes responsibility for cross-platform portability, a certain light-footedness and grace will be surrendered." He admits that optimum portability and optimum efficiency don't come at the same point.

What I use is mostly Forth-83, but when I add things, I try to make them conform, as much as possible, to things in later standards or at least in common usage (which is kind of a standard in itself, even if it hasn't made it into later official specifications). Some aspects of my Forth meet different "standards", without conflicting with each other. For example, we have the old word SHIFT which uses both positive and negative shift distances, but we also have RSHIFT and LSHIFT which are in ANS Forth. There's no reason they can't both be in the same system. The same is true for the older COMPILE and [COMPILE], and ANS's POSTPONE.

Where I added useful words that are not part of Forth 83, I tried to move toward the new standard in order to become more like the standard, instead of less. For example, my word RANGE was useful in test equipment, when you want to see if a test result falls within the allowable limits. ANS has a word WITHIN which was almost the same, so I included that. I found that my word RANGE is actually in common use, but it's usually called BETWEEN, and it almost made it into the standard under that name. I changed the name of my word from RANGE to BETWEEN.

Quote:
I think I will instead convert the definitions you posted to use with 65816 version I am working on. Most of the definitions are the same, just different wording being used.

Since I am winding down and getting close to being done, I should also confirm your numeric output and digit formatting word definitions. It will make what I am doing more compatible with what is mostly already out on the net. Thanks.

HOLD
<#
#
#>
SIGN
#S
D.R
D.
.R
and .

What I have in the .FTH file which is sort of like a shadow-screen file in that it just describes to humans what's in the .ASM file is:
Code:
: HOLD          ( ASCII -- )            \               SF151-156  FIG  ANS_CORE
   HLD  DECR
   HLD  @  C!                   ;

: >DIGIT                ( n -- ASCII_char ) ( b -- ASCII_char ) \ used in #
   DUP 9 >              \ Greater than 9?
   IF 7 + THEN          \ If so, add 7;  then
   30 +         ;       \ add 30.


: #             ( d1 -- d2 )            \               SF152-154  FIG  ANS_CORE
   BASE @  UD/MOD
   ROT >DIGIT HOLD              ;

: ##  #  #      ( d1 -- d2 )    ;       \ No header. Used internally to save mem

: #>            ( d -- addr len )       \               SF151-156  FIG  ANS_CORE
   2DROP
   PAD 1- HLD @ -               ;

: SIGN          ( n -- )                \               SF154-155  FIG  ANS_CORE
   0<           IF
   ASCII - HOLD ELSE
   DROP         THEN            ;

: #S            ( d1 -- d0 )            \             SF151-154,  FIG,  ANS_CORE
   BEGIN   # 2DUP D0=   UNTIL   ;

: D.R           ( d width -- )          \               SF157,  FIG,  ANS_DOUBLE
   >R DUP >R DABS <# #S R> SIGN #>
   R> OVER - SPACES TYPE        ;

: D.            ( d -- )                \                 SF150,155,  ANS_DOUBLE
   0  D.R  SPACE                ;

: .             ( n -- )                \            SF20,21,26,  FIG,  ANS_CORE
   S>D  D.                      ;

: ?             ( addr -- )             \                              ANS_TOOLS
   @ .                          ;

: U.            ( u -- )                \                       SF147,  ANS_CORE
   0  D.                        ;

: U.R           ( u width -- )          \                   SF148,  ANS_CORE_EXT
   0  SWAP  D.R                 ;

: .R            ( n width -- )          \         SF123,131,  FIG,  ANS_CORE_EXT
   >R  S>D  R>  D.R             ;

What I have in the .ASM actual assembly source code is the following. "DWL" in C32 is "Define Word(s), Low byte first."
Code:
        HEADER "HOLD", NOT_IMMEDIATE    ; ( ASCII -- )
HOLD:   PRIMITIVE                       ; 10x as fast as the secondary version!
        DEC     HLDdata                 ; First, decrement HLD .
        LDA     HLDdata                 ; Put the addr held by HLD in ZP so we
        STA     N                       ; can STA indirect below.
        ACCUM_8                         ; Temporarily make accum only 8-bit.
        LDA     0,X                     ; Get just the 8-bit character off the
        STA     (N)                     ; stack, and store it where HLD said.
        ACCUM_16                        ; Return the accum to 16-bit, and
 hp1:   POP1                            ; pop the character off the stack.
 ;-------------------
          HEADER ">DIGIT", NOT_IMMEDIATE ; ( n -- ASCII_CHR ) ( b -- ASCII_CHR )
TO_DIGIT: PRIMITIVE             ; Turn number (0-15) into ASCII character.
        LDA     0,X             ; We'll do it in 16-bit to avoid changing from
        CMP     #$A             ; 16 to 8 and back.  It's only meaningful for
        BCC     ja30            ; bytes though.
        ADC     #6              ; Add only 6, not 7, because C flag was set.
 ja30:  ADC     #$30            ; Carry flag is always clear when getting here.
        PUT_TOS
 ;-------------------
        HEADER "#", NOT_IMMEDIATE               ; ( d1 -- d2 )
SHARP:  DWL     nest, BASE_FETCH, UDsMOD
        DWL     ROT, TO_DIGIT, HOLD, unnest
 ;-------------------
 NO_HEADERS
        HEADER "##", NOT_IMMEDIATE              ; ( d1 -- d2 )
SHARP_SHARP:    DWL     nest, SHARP, SHARP, unnest
 HEADERS
 ;-------------------
              HEADER "#>", NOT_IMMEDIATE        ; ( d -- addr len )
sharpGREATER: PRIMITIVE         ; Primitive version 7 bytes longer & 7x as fast.
        LDA     HLDdata         ; First put addr of number string in the second-
        STA     2,X             ; from-top stack position.  ( #> as a secondary
                                ; begins with 2DROP anyway.)
        LDA     DPdata          ; Re-derive the addr of first byte past end of
        CLC                     ; our string, which was the last byte before
        ADC     #_tib_len + $21 ; PAD .
        SEC                     ; Then subtract the addr shown by HLD , and that
        SBC     HLDdata         ; will give us the length of our string.
        JMP     PUT             ; Put that at the top of the stack.
 ;-------------------
        HEADER "SIGN", NOT_IMMEDIATE            ; ( n -- )
SIGN:   PRIMITIVE
        LDA     0,X
        BPL     hp1             ; Branch to pop 1 off stack and finish.
        LDA     #"-"
        STA     0,X
        BRA     HOLD + 2
 ;-------------------
        HEADER "#S", NOT_IMMEDIATE              ; ( d1 -- d0 )
sharpS: DWL     nest                            ; Just does # enough times to
 shs1:  DWL     SHARP, _2DUP, D0EQU             ; reduce the input double
        DWL     Zbranch, shs1, unnest           ; number to 0.
 ;-------------------
        HEADER "D.R", NOT_IMMEDIATE      ; ( d width -- )
D.R:    DWL     nest, TO_R, DUP2R, DABS, LESSsharp, sharpS, R_FR, SIGN,
        DWL     sharpGREATER, R_FR, OVER, MINUS, SPACES, TYPE, unnest
 ;-------------------
        HEADER "D.", NOT_IMMEDIATE       ; ( d -- )
D.:     DWL     nest, ZERO, D.R, SPACE, unnest
 ;-------------------
        HEADER ".", NOT_IMMEDIATE        ; ( n -- )
.:      DWL     nest, StoD, D., unnest
 ;-------------------
        HEADER "?", NOT_IMMEDIATE        ; ( addr -- )
?:      DWL     nest, FETCH, ., unnest
 ;-------------------
        HEADER "U.", NOT_IMMEDIATE       ; ( u -- )
U.:     DWL     nest, ZERO, D., unnest
 ;-------------------
        HEADER "U.R", NOT_IMMEDIATE      ; ( u width -- )
U.R:    DWL     nest, ZERO, SWAP, D.R, unnest
 ;-------------------
        HEADER ".R", NOT_IMMEDIATE       ; ( n width -- )
.R:     DWL     nest, TO_R, StoD, R_FR, D.R, unnest
 ;-------------------

so only four of them are primitives.

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


Top
 Profile  
Reply with quote  
 Post subject: Re: M/ vs U/
PostPosted: Fri Feb 18, 2022 4:52 am 
Offline

Joined: Sun Apr 26, 2020 3:08 am
Posts: 357
Garth, I think I am missing one.

There seems to be a UD/MOD in # that is not listed.


Top
 Profile  
Reply with quote  
 Post subject: Re: M/ vs U/
PostPosted: Fri Feb 18, 2022 5:38 am 
Offline
User avatar

Joined: Fri Aug 30, 2002 1:09 am
Posts: 8432
Location: Southern California
IamRob wrote:
Garth, I think I am missing one.

There seems to be a UD/MOD in # that is not listed.

Here's what I have:
Code:
: UD/MOD        ( d n -- rem dquot )    \ Used in #                       FNM287
   >R  0  R@       \ ^ input_lo_cell  input_hi_cell  0  n  \ Put base on R stack
   UM/MOD          \ ( ud base -- rem quot )  ^ in_lo_cell  rem  quot
   R>  SWAP  >R    \ ^ in_lo_cell  rem  base           \ Put 1st quot on R stack
   UM/MOD          \ ( ud base -- rem quot )
   R>           ;  \ ^ rem quot2 quot1


Code:
 COMMENT
    UD/MOD below is like UM/MOD above except that it gives a double-number
    quotient.  M/MOD gave a double-number quotient too in FIG Forth, but
    the M/MOD below gives the single-number quotient like ANS.  # uses
    this UD/MOD .  If you don't need it for anything else, you might just
    assemble it without a header.
 END_COMMENT

 ;   NO_HEADERS
        HEADER "UD/MOD", NOT_IMMEDIATE  ; (Used in #  ( ud u -- rem dquot )
UDsMOD: DWL     nest, TO_R, ZERO, Rfetch,
        DWL     UMsMOD
        DWL     R_FR, SWAP, TO_R
        DWL     UMsMOD, R_FR
        DWL     unnest
 ;   HEADERS
 ;-------------------

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


Top
 Profile  
Reply with quote  
 Post subject: Re: M/ vs U/
PostPosted: Fri Feb 18, 2022 7:56 am 
Offline
User avatar

Joined: Sun Jun 30, 2013 10:26 pm
Posts: 1928
Location: Sacramento, CA, USA
Charlie started a nice thread back in 2010 that spanned several years and may be of interest in this one:

viewtopic.php?f=9&t=1652

_________________
Got a kilobyte lying fallow in your 65xx's memory map? Sprinkle some VTL02C on it and see how it grows on you!

Mike B. (about me) (learning how to github)


Top
 Profile  
Reply with quote  
 Post subject: Re: M/ vs U/
PostPosted: Fri Feb 18, 2022 8:16 pm 
Offline

Joined: Sun Apr 26, 2020 3:08 am
Posts: 357
GARTHWILSON wrote:
IamRob wrote:
Garth, I think I am missing one.

There seems to be a UD/MOD in # that is not listed.

[color=#000000]Here's what I have:[size=120]
Code:
: UD/MOD        ( d n -- rem dquot )    \ Used in #                       FNM287
   >R  0  R@       \ ^ input_lo_cell  input_hi_cell  0  n  \ Put base on R stack
   UM/MOD          \ ( ud base -- rem quot )  ^ in_lo_cell  rem  quot
   R>  SWAP  >R    \ ^ in_lo_cell  rem  base           \ Put 1st quot on R stack
   UM/MOD          \ ( ud base -- rem quot )
   R>           ;  \ ^ rem quot2 quot1

Yep, thought so. It's the same as my M/MOD

Since pretty much all of the definitions are the same, just under different words for '83 Forth. What I might do then is use the names that '83 Forth uses, and include a vocabulary that just basically renames the words for use with Fig Forth. Or vice-versa.


Top
 Profile  
Reply with quote  
 Post subject: Re: M/ vs U/
PostPosted: Fri Feb 18, 2022 8:18 pm 
Offline

Joined: Sun Apr 26, 2020 3:08 am
Posts: 357
barrym95838 wrote:
Charlie started a nice thread back in 2010 that spanned several years and may be of interest in this one:

viewtopic.php?f=9&t=1652

Thanks for that link Mike. Good read. I went back to the beginning of threads in this Forum and read anything that looked interesting. Don't know how I missed this one.


Top
 Profile  
Reply with quote  
 Post subject: Re: M/ vs U/
PostPosted: Sat Feb 19, 2022 3:43 am 
Offline

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

In Fleet Forth, an ITC Forth, I took an idea from Blazin' Forth and combined some of the benefits of STC Forth for the multiplication and division routines.
Code:
// ABS NEGATE
CODE ABS  ( N1 -- N2 )
   1 ,X LDA
   0< IF
      LABEL NEGATE.BODY
      HERE 6 + JSR
   THEN
   NEXT JMP
   SEC
   LABEL <DNEGATE>
   TYA  0 ,X SBC  0 ,X STA
   TYA  1 ,X SBC  1 ,X STA
   RTS  END-CODE
CODE NEGATE  ( N1 -- N2 )
   -2 ALLOT NEGATE.BODY ,
   END-CODE

// DABS DNEGATE
CODE DABS  ( D1 -- D2 )
   1 ,X LDA
   0< IF
      LABEL DNEGATE.BODY
      HERE 6 + JSR
   THEN
   NEXT JMP
   SEC
   TYA  2 ,X SBC  2 ,X STA
   TYA  3 ,X SBC  3 ,X STA
   <DNEGATE> JMP  END-CODE
CODE DNEGATE  ( D1 -- D2 )
   -2 ALLOT  DNEGATE.BODY ,
   END-CODE

// UM/MOD
HEX
CODE UM/MOD  ( UD U1 -- U2 U3 )
   HERE 6 + JSR  NEXT JMP
   INX  INX
   0 ,X LDA  0FE ,X CMP
   1 ,X LDA  0FF ,X SBC
   CS NOT IF
      N 1+ STY
      2 ,X LDA  0 ,X LDY
      2 ,X STY  .A ASL  0 ,X STA
      3 ,X LDA  1 ,X LDY
      3 ,X STY  .A ROL  1 ,X STA
      10 # LDA  N STA
      BEGIN
         2 ,X ROL  3 ,X ROL
         N 1+ ROL  SEC
         2 ,X LDA  $FE ,X SBC  N 1- STA
         3 ,X LDA  $FF ,X SBC  TAY
         N 1+ LDA  0 # SBC
         CS IF
            N 1+ STA  3 ,X STY
            N 1- LDA  2 ,X STA
         THEN
         0 ,X ROL  1 ,X ROL
         N DEC
      0= UNTIL
      0 # LDY
      RTS
   THEN
   $FF # LDA
   3 ,X STA  2 ,X STA
   1 ,X STA  0 ,X STA
   RTS
END-CODE

So here is Fleet Forth's UD/MOD :
Code:
// UD/MOD
HEX
CODE UD/MOD  ( UD1 U1 -- U2 UD2 )
   DEX  DEX
   2 ,X LDA  N 2+ STA  0 ,X STA
   3 ,X LDA  N 3 + STA  1 ,X STA
   2 ,X STY  3 ,X STY
   ' UM/MOD @ 6 + JSR
   0 ,X LDA  PHA
   1 ,X LDA  PHA
   N 2+ LDA  0 ,X STA
   N 3 + LDA  1 ,X STA
   ' UM/MOD @ 6 + JSR
   PLA
   PUSH JMP  END-CODE

And Fleet Forth's */MOD and /MOD , as well as M/MOD , the signed counterpart to UM/MOD :
Code:
// */MOD
HEX
CODE */MOD  ( N1 N2 N3 -- N4 N5 )
   HERE 6 + JSR  NEXT JMP
   INX  INX
   ' M* @ 6 + JSR
   DEX  DEX
   LABEL (M/MOD)
   0 ,X LDA  N 2+ STA
   1 ,X LDA  N 3 + STA
   3 ,X EOR  PHA
   N 3 + LDA
   0< IF
      ' NEGATE @ 6 + JSR
   THEN
   3 ,X LDA
   0< IF
      INX  INX
      ' DNEGATE @ 6 + JSR
      DEX  DEX
   THEN
   ' UM/MOD @ 6 + JSR
   N 3 + LDA
   0< IF
      INX  INX
      ' NEGATE @ 6 + JSR
      DEX  DEX
   THEN
   PLA
   0< IF
      ' NEGATE @ 6 + JSR
      2 ,X LDA  3 ,X ORA
      0= NOT IF
         0 ,X LDA
         0= IF  1 ,X DEC  THEN
         0 ,X DEC
         SEC  N 2+ LDA
         2 ,X SBC  2 ,X STA
         N 3 + LDA
         3 ,X SBC  3 ,X STA
      THEN
   THEN
   RTS  END-CODE

// /MOD M/MOD
HEX
CODE /MOD  ( N1 N2 -- N3 N4 )
   HERE 6 + JSR  NEXT JMP
   DEX  DEX
   2 ,X LDA  0 ,X STA
   3 ,X LDA  1 ,X STA
   5 ,X LDA
   0< IF  DEY  THEN
   2 ,X STY  3 ,X STY
   0 # LDY
   (M/MOD) JMP  END-CODE
CODE M/MOD  ( D N1 -- N2 N3 )
   (M/MOD) JSR  NEXT JMP
   END-CODE



Top
 Profile  
Reply with quote  
Display posts from previous:  Sort by  
Post new topic Reply to topic  [ 12 posts ] 

All times are UTC


Who is online

Users browsing this forum: No registered users and 3 guests


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

Search for:
Jump to: