Post Reply 
(71B) FORTH questions
10-19-2023, 05:01 PM (This post was last modified: 06-18-2024 02:22 PM by floppy.)
Post: #81
RE: (71B) FORTH questions
(06-22-2023 06:51 PM)rprosperi Wrote:  FTHUTILA is a TEXT file, with source code for the assembler portion
FTHUTILF is a TEXT file with source code for the FORTH portion

After uploading the files, LIST show following words which are not documented in the Forth utilities manual. Where is the doc? Any advice where to search is welcome.
Code:

"
(
?
:
]
;
*
#
.
[
/
,
3
2
1
0
@
!
>
<
=
-
+
J
I
'
L
T
Z
Y
X
S<
S=
S!
C,
U.
<>
M*
D<
<#
#>
#S
CR
*/
D.
M/
S0
.(
."
DO
IF
C!
C@
BL
D+
D-
U<
0>
0<
1-
2-
1+
2+
5-
5+
2/
2*
+!
0=
OR
R@
>R
R>
OF
F/
F*
F-
F+
N!
N@
F.
LN
H.
.S
IP
FP
ASC
VAL
POS
EOF
MAX
MIN
D.R
MOD
PAD
KEY
BYE
>IN
BLK
USE
TIB
RP0
SP0
ABS
NOT
XOR
AND
ROT
DUP
RP!
RP@
SP!
C@+
SP@
RDN
RUP
E^X
Y^X
1/X
X^2
TAN
COS
SIN
ENG
SCI
FIX
STD
RCL
STO
[']
UM*
CHS
LGT
HEX
4N@
S>&
S<&
END$
CHR$
STR$
SUB$
+BUF
TYPE
CASE
SIGN
?DUP
HOLD
/MOD
HERE
EMIT
WORD
QUIT
FIND
ROLL
LOOP
ELSE
THEN
BASE
PREV
WARN
S->D
DABS
FILL
2DUP
OVER
PICK
SWAP
DROP
GROW
10^X
X<>Y
ATAN
ACOS
ASIN
EXIT
SPAN
#TIB
FTOI
ITOF
SQRT
X#Y?
X=Y?
X>Y?
X=0?
X<Y?
CRLF
FABS
LEFT$
SMOVE
NULL$
OPENF
LOADF
BLOCK
ENDOF
M/MOD
*/MOD
DEPTH
SPACE
ABORT
?COMP
ALLOT
QUERY
CMOVE
+LOOP
WHILE
UNTIL
BEGIN
DOES>
LEAVE
LINE#
LIMIT
FIRST
STATE
ONERR
OKFLG
FENCE
WIDTH
COUNT
2SWAP
DIGIT
2DROP
NMOVE
2OVER
ENTER
LASTX
>BODY
FLUSH
EXPBF
CONBF
X>=Y?
X<=Y?
FINDF
FDROP
VARID
FSTR$
NFILL
RIGHT$
MAXLEN
STRING
CLOSEF
SMUDGE
SPACES
ABORT"
NUMBER
TOGGLE
LATEST
?STACK
FORGET
REPEAT
CREATE
SCRFIB
NMOVE>
CMOVE>
NEGATE
SHRINK
OUTPUT
BASICX
FENTER
UM/MOD
KILLBF
FINDBF
MAKEBF
BASIC$
BASICF
BASICI
NALLOT
ADJUSTF
SYNTAXF
CREATEF
ENDCASE
COMPILE
LITERAL
'STREAM
ENCLOSE
CONVERT
DECIMAL
CURRENT
CONTEXT
DNEGATE
DEGREES
RADIANS
EXECUTE
PRIMARY
LISTING
CLOSEALL
DLITERAL
TRAVERSE
EXPECT96
VARIABLE
CONSTANT
FLITERAL
PAGESIZE
ASSEMBLE
IMMEDIATE
-TRAILING
INTERPRET
[COMPILE]
SECONDARY
FVARIABLE
FCONSTANT
?TERMINAL
VOCABULARY
DEFINITIONS
STRING-ARRAY

HP71B 4TH/ASM/Multimod, HP41CV/X/Y & Nov64d, PILBOX, HP-IL 821.62A & 64A & 66A, Deb11 64b-PC & PI2 3 4 w/ ILPER, VIDEO80, V41 & EMU71, DM41X
Find all posts by this user
Quote this message in a reply
10-20-2023, 02:11 AM
Post: #82
RE: (71B) FORTH questions
These words are simply components of the larger words which are documented in the manual, e.g. UN:C is a component of UN:, DOSST a component of SST, etc.

Limited docs for each word are included in the FTHUTILF source file, including the stack in/out lists and a brief summary of what the word does, for example for UN:C

( UN:C Decompile a word, omitting header [ cfa -> ] )
: UN:C ." CFA: " DUP 'END DUP DUP @ - -5 = IF H. 5SP ." Primitive" PAUSE CR
ELSE WORD@ BEGIN 5SP WORD@ DUP ENDA @ = UNTIL DROP THEN ; ( )

--Bob Prosperi
Find all posts by this user
Quote this message in a reply
10-20-2023, 07:45 AM (This post was last modified: 10-20-2023 07:46 AM by floppy.)
Post: #83
RE: (71B) FORTH questions
(10-20-2023 02:11 AM)rprosperi Wrote:  These words are simply components of the larger words which are documented in the manual, e.g. UN:C is a component of UN:, DOSST a component of SST, etc.

Limited docs for each word are included in the FTHUTILF source file, including the stack in/out lists and a brief summary of what the word does, for example for UN:C

( UN:C Decompile a word, omitting header [ cfa -> ] )
: UN:C ." CFA: " DUP 'END DUP DUP @ - -5 = IF H. 5SP ." Primitive" PAUSE CR
ELSE WORD@ BEGIN 5SP WORD@ DUP ENDA @ = UNTIL DROP THEN ; ( )

Thanks. Good to see few comments in the TXT file.

Try in EMU71.

first try.. (WEIRD)
PLIST FTHUTILF:HDRIVE1
ERR:Invalid Filespec

second try..
COPY FTHUTILF:HDRIVE1 TO :MAIN
PLIST FTHUTILF (DISPLAY IS PRINTER defined for ILPER)

Code:
(                       FTHUTILF                                         )   
( FORTH Utilities:  Secondaries.  FTHUTILA file should assembled prior to )
(     loading this file.                                                  )
BASE @

( PAUSELEN: Variable to hold pause length )
VARIABLE PAUSELEN 0 PAUSELEN !

( PAUSE : Pause for PAUSELEN/1000 seconds )
: PAUSE PAUSELEN @ 1+ 0 DO LOOP ;

( N-A: convert a nibble to its hex ascii equivalent.  n -> )
DECIMAL
: N-A 10 - DUP 0< IF 58 + ELSE 65 + THEN EMIT ;

: DUMP OVER + SWAP ( addr n -> print n nibs starting at addr)
    DO I N@ N-A LOOP ;

: DUMP+ 2DUP + ROT ROT DUMP ; ( Do DUMP; leave next addr on stack )

( SHOW: disp contents of n consecutive memory cells.  { addr n -> } )
: SHOW 1+ 1 DO DUP H. DUP @ 5 SPACES H. PAUSE CR 5+ LOOP ;

: BASE? BASE @ DUP DECIMAL . BASE ! ; ( put current base in X and display)

( DELAY00: Set DELAY0,0)
: DELAY00 " DELAY0,0" BASICX ;

( D- {D P R *}: Do DISPLAY IS {DISPLAY  PRINTER RS232 *} )
: D-P " DISPLAY IS PRINTER" BASICX ;
: D-* " DISPLAYIS*" BASICX ;
: D-D " DISPLAYISDISPLAY" BASICX ;
: D-R " DISPLAYISRS232"BASICX ;

( ROOM?:  Display number of nibbles available in dictionary )
: ROOM? SP0 @ HERE - 458 - . ;

( S.: Print stack contents bottom first )
: S. ." [ " DEPTH 0> IF DEPTH 1 SWAP DO I PICK U. -1 +LOOP THEN ." ] " ;

HEX
( ADDR-    get the addr of the namefield of the previous word.)
(          NFAddr1 -> NFAddr2 )
: ADDR- 5- @ ;

( NFA:  GIVEN CFA, GET NFA.  [ CFA -> NFA ] )
: NFA 2- -1 TRAVERSE ;

( NAME: From NFA, type name  [ nfa -> ] )
: NAME DUP C@ 1F AND 2DUP 1- SWAP 2+ SWAP TYPE
       2* + C@ 7F AND EMIT ;

( NFASTR: Convert NFA to name string.  [NFA -> str] )
: NFASTR DUP 2+ SWAP C@ 1F AND ;

( SPECIAL: Array containing list of words with remote CFA's. )
( 1st value is # of entries. )
CREATE SPECIAL 
   D ,
   E701A , ( COLON )
   E71E8 , ( SEMI )
   E1C54 , ( number )
   E22ED , ( F-number )
   E1C67 , ( DO )
   E3FF1 , ( LOOP )
   E3F81 , ( +LOOP )
   E5D86 , ( IF / UNTIL / WHILE )
   E5D99 , ( ELSE / REPEAT )
   E0640 , ( " )
   E0EFA , ( ." )
   E580E , ( ABORT")
   E0168 , ( J )

( SPEC?: Find CFA in SPECIAL. Return # of entry, or 0 if not present. )
( [ cfa -> cfa # ] )

: SPEC? 0 SPECIAL @ 1+ 1 DO  ( CFA 0 )
   OVER SPECIAL I 5 * + @ =  ( CFA 0 CFA SPECi )
      IF DROP I LEAVE THEN LOOP ; ( CFA # )

( 'NAME: Given CFA, type name.  { CFA -> } )
: 'NAME DUP NFA SWAP OVER - 2/ 1- SWAP NFASTR DUP 4 ROLL = 
      IF 1- 2DUP TYPE 2* + C@ 7F AND EMIT 
      ELSE 2DROP ." Unknown" THEN ;

( HEREN: Find the start of the n+1th link field.  { n -> addr } )
: HEREN DUP C = IF DROP E6FAB ELSE 1+ 5 * E0000 + @  ( NFA )
   BEGIN 5- DUP @ DUP 0 <> WHILE SWAP DROP REPEAT DROP THEN ;

VARIABLE ENDA VARIABLE HERE0

( END: given a CFA, find the addr of the start of the next word   )
( and store in ENDA.   CFA -> )
: 'END DUP E0000 U< IF LATEST HERE
   ELSE DUP NFA C@ 1F AND  ( CFA n )
      DUP 5 * E0000 + @ SWAP HEREN THEN
   DUP HERE0 ! ENDA ! BEGIN 2DUP < WHILE DUP ENDA ! ADDR- REPEAT 
   2DROP ENDA @ HERE0 @ <> IF -5 ENDA +! THEN ;

: 5SP 5 SPACES ;

( +ADDR: Type addr following control word; incr addr. { I -> I+5 } )
: +ADDR 5+ DUP DUP @ + ."  to " H. ;

( "STR: Type the compiled string following a " word [ I 4-or-2 ] )
: "STR SWAP 5+ DUP C@ 2DUP SWAP 5 ROLL + SWAP 22 EMIT SPACE TYPE 22 EMIT
           2* + 1- ;

( FTEMP: FVariable to hold X during decompilation of a FP word )
FVARIABLE FTEMP

( WORDNAME: Given I and its WA, type the word identified; advance I)
( [ I WA -> I' ]  I' = next I -5 )
: WORDNAME DUP ABS 10000 > ( Is this a legitimate word addr? )
        IF SPEC? CASE 0 OF 'NAME ENDOF SWAP DROP
        1 OF ." :" ENDOF
        2 OF ." ;" ENDOF 
        3 OF 5+ DUP @ . ENDOF 
        4 OF 5+ DUP FTEMP STO RDN RCL F. RDN FTEMP RCL B + ENDOF
        5 OF ." DO" ENDOF
        6 OF ." LOOP" +ADDR ENDOF
        7 OF ." +LOOP" +ADDR ENDOF
        8 OF DUP 5+ @ 0> 
      IF OVER 5+ DUP @ + 5- DUP @ 0< SWAP 5- @ E5D99 = AND 
         IF ." WHILE" ELSE ." IF" THEN
      ELSE ." UNTIL" THEN +ADDR ENDOF
        9 OF DUP 5+ @ 0> IF ." ELSE" ELSE ." REPEAT" THEN +ADDR ENDOF
        A OF 4 "STR ENDOF
        B OF ." ." 2 "STR 2- ENDOF
        C OF ." ABORT" 2 "STR 2- ENDOF
        D OF ." J" ENDOF
      ENDCASE     ( addr')
     ELSE DROP ( addr'=addr )
     THEN ;

( WORD@: Given an addr, type it, it's content, and the word identified. )
(    { addr -> addr'}  where addr' = addr of next I )
: WORD@ DUP H. 5SP DUP @ DUP H. ( addr cfa )
   WORDNAME 5+ PAUSE CR ;

( UN:C  Decompile a word, omitting header [ cfa -> ] )
: UN:C ." CFA: " DUP 'END DUP DUP @ - -5 = IF H. 5SP ." Primitive" PAUSE CR
   ELSE WORD@ BEGIN 5SP WORD@ DUP ENDA @ = UNTIL DROP THEN ;  ( )

( UN: Decompile the word named next, including the header )
: UN: ' DUP ." Word: " DUP 'NAME PAUSE CR NFA ( CFA NFA )
     DUP 5- ." LFA: " DUP H. 5SP @ ." Link: " H. PAUSE CR ( CFA NFA )
   DUP ." NFA: " H. 5SP NFASTR 1+ 2* SWAP 2- SWAP DUMP PAUSE CR ( CFA )
   UN:C ;

( RS.  Decompile the return stack, omitting the bottom two levels )
: RS. RP@ RP0 @ 5-
     DO I @ WORD@ DROP -5 +LOOP ;

( RTNSAVE: Variable to hold SST environment. )
( Contents of addr: )
( RTNSAVE = I )
(      +5 = Orig. I --in word that calls DOSST )
(      +A = CFA of SST word )
(      +F = END of SST word )
(     +14 = >RTN )
(     +19 = >RBOT )
( RTNSAVE+E6 points to end of RTNSAVE--temp RP0@)
CREATE RTNSAVE E6 NALLOT
( " CREATE TEXT RTNSAVE:PORT[1],500" BASICX )
( : RTNSAVE " ADDR$['RTNSAVE']" BASIC$ DROP 2- NUMBER DROP 25 + ; )

( NEWRTN: Copy the RTN stack & >RTN to RTNSAVE )
: NEWRTN RP@ RP0 @ ( >RTN >RBOT)
   OVER - SWAP OVER RTNSAVE E6 + 
   SWAP - DUP RTNSAVE 14 + ! ( Save >RTN* ) ROT ( [ >RTN >RTN* # ] )
   NMOVE   ( COPY RTN stack to RTNSAVE)
   RTNSAVE 2FB7F ! ; ( Put RTNSAVE addr in 2FB7F )

( SSTERROR: Onerror routine for single step )
: SSTERROR 0 ONERR ! RTNSAVE 19 + @ RP0 ! ( Restore >RBOT )
     2F7E4 4N@ DUP 2DUP ( 4 copies of errn )
     2EFF > ( >2EFF ? )
    SWAP 2F41 < ( <2F41 ? )
     AND SWAP 0= OR  ( =0? )
     IF R>  ( Go back to ABORT )
    ELSE " BEEP" BASICX " 'ERR:'&MSG$(ERRN)"BASIC$ TYPE SP! RP! QUIT
    THEN ;

( SSTOUT: Variable to hold CFA of word to be executed after DOSST )
VARIABLE SSTOUT

( SST: Single step the word identified by the instruction pointer I* stored )
( at RTNSAVE, unless it is a semi.  Then display the stack. )
: SST RTNSAVE @ DUP @ DUP E71E8 <> ( I WA flag )
      IF WORDNAME DROP 5 SPACES
      [ ' SSTERROR  ] ( Put SSTERROR cfa on stack for onerror )
      LITERAL ONERR !
      DOSST 0 ONERR ! SSTOUT @ EXECUTE
         ELSE ." ;" 2DROP THEN ;

' S. SSTOUT ! ( Initialize SSTOUT to hold S.'s CFA )

( READYSTEP: Set up environment for STEP or BREAK )

( Save I*, END, CFA in RTNSAVE, do NEWRTN )
: READYSTEP ' DUP RTNSAVE A + !  ( Store CFA )
   DUP 'END ENDA @ RTNSAVE F + !   ( Store word END )
   5+ RTNSAVE ! ( Save new I )
   NEWRTN ; 

( STEP: Single step next word.)
: STEP READYSTEP SST ;

( BP: Set a breakpoint.  [ Ib -> ] )
: BP 2FB84 ! ;

( CONT: Continue execution of a BREAKed or SSTed word to next breakpoint )
: CONT [ ' SSTERROR ] LITERAL ONERR ! 
      BRRUN 0 ONERR ! SSTOUT @ EXECUTE  ;

( FINISH: Complete execution of an interrupted word )
: FINISH 0 BP CONT ;

( BREAK: Execute next word, stopping at Ib specified on stack or at the )
(        final ;  [ I -> ] )
: BREAK READYSTEP BP CONT ;

( LIST: List current RAM dictionary.  Same as RAMLIST )
: LIST LATEST BEGIN 
   DUP NAME DUP C@ 40 AND IF ."  Immediate" THEN PAUSE CR 5- @ 
    DUP 0= UNTIL DROP ;

( FSCRATCH : Floating point scratch variable )
FVARIABLE FSCRATCH

( FINDW: Get a word from input stream and return its cfa [ -> cfa ] )
: FINDW BL WORD FIND 0= IF ABORT" Word not found" THEN ;

( PRINT:  Direct the display output of the next word to the printer )
: PRINT 2F78D 2FC79 7 NMOVE ( Save old Display device )
     D-P ( Make printer the display )
     FINDW EXECUTE CR ( Do it and print output)
     2FC79 2F78D 7 NMOVE ( Restore old display )
     7 2F7B1 N! ( Reset display type )
     2FC79 7 0 NFILL ( Zero the assembler variables )
     ;

( SKIP : Set printer to skip over perf mode )
: SKIP " PRINT CHR$(27);'&l1L';"BASICX ;

( TIMED: Execute the next word and display its execution time )
(    The time is left in X.  T is lost on input, and Z & T are lost)
(    on output. )
: TIMED FINDW FSCRATCH
     TIME STO FDROP EXECUTE TIME
     FSCRATCH DUP DUP RCL F-
     TIME STO FDROP         TIME
     F- RCL F+ F. ;

BASE !

HP71B 4TH/ASM/Multimod, HP41CV/X/Y & Nov64d, PILBOX, HP-IL 821.62A & 64A & 66A, Deb11 64b-PC & PI2 3 4 w/ ILPER, VIDEO80, V41 & EMU71, DM41X
Find all posts by this user
Quote this message in a reply
10-20-2023, 11:56 AM
Post: #84
RE: (71B) FORTH questions
(10-20-2023 07:45 AM)floppy Wrote:  first try.. (WEIRD)
PLIST FTHUTILF:HDRIVE1
ERR:Invalid Filespec
For some unknown reasons the HP-IL module do not extend the LIST and PLIST keywords to work with files on mass media.
Like you did, you have to copy the file into the HP-71B memory and then LIST/PLIST the file.

Sylvain Côté
Find all posts by this user
Quote this message in a reply
10-20-2023, 12:32 PM
Post: #85
RE: (71B) FORTH questions
(10-20-2023 11:56 AM)Sylvain Cote Wrote:  
(10-20-2023 07:45 AM)floppy Wrote:  first try.. (WEIRD)
PLIST FTHUTILF:HDRIVE1
ERR:Invalid Filespec
For some unknown reasons the HP-IL module do not extend the LIST and PLIST keywords to work with files on mass media.
Like you did, you have to copy the file into the HP-71B memory and then LIST/PLIST the file.

I've wondered why this limitation exists, and concluded that since the LIST & PLIST output is often directed to an output device (monitor, printer, virtual printer), traffic on the IL loop for simultaneously reading portions of the file INTO the 71B while also sending OUT of the 71B would be quite slow, if indeed not confused.

Also, AFAIK, all loop-based file transfers are for the complete file at once, possibly for the same reason(s), but I'm just speculating.

--Bob Prosperi
Find all posts by this user
Quote this message in a reply
10-20-2023, 03:46 PM (This post was last modified: 10-20-2023 03:52 PM by Sylvain Cote.)
Post: #86
RE: (71B) FORTH questions
(10-20-2023 12:32 PM)rprosperi Wrote:  
(10-20-2023 11:56 AM)Sylvain Cote Wrote:  For some unknown reasons the HP-IL module do not extend the LIST and PLIST keywords to work with files on mass media.
Like you did, you have to copy the file into the HP-71B memory and then LIST/PLIST the file.
I've wondered why this limitation exists, and concluded that since the LIST & PLIST output is often directed to an output device (monitor, printer, virtual printer), traffic on the IL loop for simultaneously reading portions of the file INTO the 71B while also sending OUT of the 71B would be quite slow, if indeed not confused.
Also, AFAIK, all loop-based file transfers are for the complete file at once, possibly for the same reason(s), but I'm just speculating.
In theory it should be easy to do for a text file, the limitation is probably how list/plist is implemented.
For sure, the way file transfer is currently implemented, it is a lot more efficient to transfer the file into the 71B memory and then list/plist it.
When you factor in the other files types, which in some cases include decoding logic, they probably took a step back and decided to leave it as it was.

Sylvain Côté
Find all posts by this user
Quote this message in a reply
06-03-2024, 08:49 PM
Post: #87
RE: (71B) FORTH questions
(06-22-2023 06:51 PM)rprosperi Wrote:  FTHUTILA is a TEXT file, with source code for the assembler portion
How this file can be printed or extracted?
I just wanted to create a new version of it with the latest updated TIMEASM

HP71B 4TH/ASM/Multimod, HP41CV/X/Y & Nov64d, PILBOX, HP-IL 821.62A & 64A & 66A, Deb11 64b-PC & PI2 3 4 w/ ILPER, VIDEO80, V41 & EMU71, DM41X
Find all posts by this user
Quote this message in a reply
06-04-2024, 02:06 AM
Post: #88
RE: (71B) FORTH questions
(06-03-2024 08:49 PM)floppy Wrote:  
(06-22-2023 06:51 PM)rprosperi Wrote:  FTHUTILA is a TEXT file, with source code for the assembler portion
How this file can be printed or extracted?
I just wanted to create a new version of it with the latest updated TIMEASM

Code:
lifget -r HP-00071-90097_SOFT-DEV-HANDBOOK_MEDIA.LIF FTHUTILA | liftext >FTHUTILA.txt

Code:
       FORTH
*                                FTHUTILA
*                      FORTH Utilities: Primitives
SAVEFP EQU #E717A           FORTH entry points:  Save FORTH pointers
GETFP  EQU #E71A5                                Recover FORTH pointers
STKLFT EQU #E7320                                Lift floating-point stack
NEXT   EQU #E71CA                                Inner loop
NEXT00 EQU #E71DD                                Call inner loop
DOATN  EQU #E7204                                ATTN/poll check
CMPT   EQU #125B2          System entry points:  Read time
IDIV   EQU #0EC7B                                Full word integer divide
HXDCW  EQU #0ECB4                                Hex to decimal
FLOAT  EQU #1B322                                Integer to floating point
CLRFRC EQU #0C6F4                                Clear fractional part
DV2-12 EQU #0C4A8                                12-digit divide

* TIME : Read system clock in seconds; return result to X
       WORD 'TIME'
       GOSBVL SAVEFP
       GOSBVL STKLFT
       GOSBVL CMPT           C(W) = Time in hex 512ths of a second
*
ACLC24 A=C W                 Unsupported entry point. 12B79
       C=0 W
       P= 4
       LCHEX 2A3             C = 2A30000
       D=C W                 D = 2A30000 ( 24 hours in 512th's of a second )
*
       GOSBVL IDIV
       GOSBVL HXDCW
       A=C W
       GOSBVL FLOAT
       C=0 W
       P= 12
       LCHEX 512             C = 5.12
       GOSBVL DV2-12         A,B = Time*100
       GOSBVL CLRFRC         A,B = IP(Time*100)
       GOSUB TRUNCC
       C=C-1 X
       C=C-1 X               C= TIME
       SETHEX
       D0=(5) #2FBD0           X-Register
       DAT0=C W              X = TIME
       GOSBVL GETFP
       RTNCC
*
*
TRUNCC P= 0                  unsupported system utility at 12B4A
       LCHEX 00499           rounds 15-digit A,B to 12-digit C
       ?A<=C A
       GOYES TRUN20
       C=-C A
       ?A>=C A
       GOYES TRUN20
       C=0 W
       A=A+A A
       GOC TRUN10
       LCHEX F00
       C=A S
TRUN10 RTNCC
TRUN20 C=A W
       C=B M
       RTNCC
*
       WORD 'DOSST'
* Single-step primitive
       GOSUB NEWENV         Switch to temp. environment
*
*
* 4. Run inner loop once
MORE   D0=A                 D0 = I*
NEXT10 GOSBVL NEXT1         Do 1 inner loop
*
* 5. Are we back to original (I) word?
NEXT11 AD0EX                A = I*'
       D0=(5) #2FB7F
       C=DAT0 A             C = RTNSAVE
       CD0EX                D0 = RTNSAVE
       D0=D0+ #A            D0= RTNSAVE+A
       C=DAT0 A             C = CFA
       ?A<C A               I*' < CFA?
       GOYES MORE           Do another cycle
       D0=D0+ 5             D0 = RTNSAVE+F
       C=DAT0 A             C = END
       ?A>C A               Is I*' past END?
       GOYES MORE           Do another cycle
*
* 6. Return to normal execution.  Save I*, restore I
DONE1  D0=D0- #F             D0 = RTNSAVE
DONE2  DAT0=A A             RTNSAVE = I*
       D0=D0+ 5             D0 = RTNSAVE+5
       A=DAT0 A             A = Orig I
*
* 7. Switch >RTN
       D0=D0+ #F            D0 = RTNSAVE+14
       C=DAT0 A             C = >RTN
       CBEX A               B(A) = >RTN; C = >RTN*
       DAT0=C A             RTNSAVE+14 = >RTN*
*
* 8. Restore >RBOT
       D0=D0+ 5             D0 = RTNSAVE+19
       C=DAT0 A             C = Orig >RBOT
       D0=(5) #2FB16        D0 = RP0
       DAT0=C A             RP0 = >RBOT
       AD0EX                D0 = I
       GOVLNG NEXT00        Exit back to word that called DOSST
*
*  Switch to new environment.  1.  Switch I
NEWENV AD0EX                A = I
       D0=(5) #2FB7F        
       C=DAT0 A             C = RTNSAVE
       CD0EX                D0 = RTNSAVE
       C=DAT0 A             C = I*
       D0=D0+ 5             D0 = RTNSAVE+5
       DAT0=A A             RTNSAVE+5 = I
*
* 2. Switch >RTN
       D0=D0+ #F            D0 = RTNSAVE+14
       A=DAT0 A             A = >RTN*
       ABEX A               A = >RTN, B = >RTN*
       DAT0=A A             RTNSAVE+14 = >RTN
*
* 3. Switch >RBOT
       R0=C A               R0 = I*
       CD0EX                C = RTNSAVE+14
       D0=(5) #2FB16        D0 = RP0
       A=DAT0 A             A = >RBOT
       CD0EX                C = RP0, D0 = RTNSAVE+A
       D0=D0+ 5             D0 = RTNSAVE+19
       DAT0=A A             RTNSAVE+19 = >RBOT
       P= 0
       AD0EX                A = RTNSAVE+14
       CD0EX                D0 = RP0
       LC(5) #E6-#19        C = (RTNSAVE+E6)-(RTNSAVE+19)
       C=C+A A              C = RTNSAVE+E6
       DAT0=C A             RP0 = RTNSAVE+E6
       A=R0 A               A = I*
       RTN
*
* Inner Loop
NEXT1  A=DAT0 A               C = WA
       D0=D0+ 5               Increment I*
       R0=A A                 R0 = WA
       AD0EX                  D0 = WA; A = I*
       C=DAT0 A               C = @WA
       D0=(5) #E71ED          D0 = SEMI
       AD0EX                  A = SEMI; D0 = I*
       ?A=C A                 Is the next word SEMI?
       GOYES MYSEMI           Go to local SEMI 
       A=R0 A                 A = WA
       RSTK=C                 Push @WA onto RTNSTK
       RTN                    Go execute @WA, rtn to NEXT 11
*
* Local SEMI
MYSEMI GOSBVL DOATN
       C=B A                  C = >RTN*
       CD0EX                  D0 = >RTN*; C = I*
       A=DAT0 A               A = I*'
       D0=D0+ 5               Pop RSTK
       AD0EX                  D0 = I*'; A = >RTN*
       B=A A                  B = >RTN*
       RTNCC
*
*
*  BRRUN:  Execute a word up to breakpoint stored in 2FB7F or to final ;
       WORD 'BRRUN'
       GOSUB NEWENV         A = I*
       GOTO NEXT22
* Run inner loop once
MORE2  D0=A                 D0 = I*
NEXT20 GOSUB NEXT1          Do one inner loop
NEXT21 AD0EX                A = I*
       D0=(5) #2FB84  
       C=DAT0 A             C = Ib
       ?C=A A               I* = Ib ?
       GOYES DONE3          Then exit
NEXT22 D0=(5) #2FB7F         
       C=DAT0 A             C(A)-> RTNSAVE
       CD0EX                D0-> RTNSAVE
       D0=D0+ #F            D0-> RTNSAVE+F
       C=DAT0 A             C(A)-> END
       CD0EX                D0-> END
       D0=D0- 5             D0-> final ;
       CD0EX                C(A)-> final ;
       ?A#C A               Is I* # final ; ?
       GOYES MORE2          Do another cycle
DONE3  D0=(5) #2FB7F     
       C=DAT0 A             C = RTNSAVE
       CD0EX                D0 = RTNSAVE
       GOTO DONE2           Go back to orig. environment
       END

Sylvain Côté
Find all posts by this user
Quote this message in a reply
06-04-2024, 02:10 AM
Post: #89
RE: (71B) FORTH questions
(06-03-2024 08:49 PM)floppy Wrote:  
(06-22-2023 06:51 PM)rprosperi Wrote:  FTHUTILA is a TEXT file, with source code for the assembler portion
How this file can be printed or extracted?
I just wanted to create a new version of it with the latest updated TIMEASM

Connect ILPer, then

Code:
RESTORE IO
COPY FTHUTILA:TAPE(1) TO FTHUTILA:MAIN                  (use whichever drive the file is loaded on)
DISPLAY IS PRINTER                                      (to redirect display screen outlet to ILPer)
LIST FTHUTILA                                           (lists the entire file to the virtual printer window of ILPer)
Select portions of the listed file from the ILPer window
Control-C to copy selected text
Paste into a text editor
DISPLAY IS *                                            (Restore default DISPLAY device
OFF IO

Makes changes from revised TIMEASM

--Bob Prosperi
Find all posts by this user
Quote this message in a reply
06-17-2024, 02:23 PM (This post was last modified: 06-17-2024 02:40 PM by floppy.)
Post: #90
RE: (71B) FORTH questions
From a previous post with TIMEASM..

FORTH
* TIMEASM
* FORTH TIME: Primitive

SAVEFP EQU #E717A FORTH entry points: Save FORTH pointers
GETFP EQU #E71A5 Recover FORTH pointers
STKLFT EQU #E7320 Lift floating-point stack

CMPT EQU #125B2 System entry points: Read time
IDIV EQU #0EC7B Full word integer divide
HXDCW EQU #0ECB4 Hex to decimal
FLOAT EQU #1B322 Integer to floating point
CLRFRC EQU #0C6F4 Clear fractional part
DV2-12 EQU #0C4A8 12-digit divide

Where can I find all the Forth Primitive?

I can find the System primitives there https://github.com/bug400/asm71/blob/mas...71ENTR.TXT and in the HP71 SW IDS Volume 3.

Background: trying to make Forth words like X<>Z or RCL/Z or X_2/ or X_2* purely in assembler (no Forth stack movement)

HP71B 4TH/ASM/Multimod, HP41CV/X/Y & Nov64d, PILBOX, HP-IL 821.62A & 64A & 66A, Deb11 64b-PC & PI2 3 4 w/ ILPER, VIDEO80, V41 & EMU71, DM41X
Find all posts by this user
Quote this message in a reply
06-18-2024, 02:57 AM
Post: #91
RE: (71B) FORTH questions
(06-17-2024 02:23 PM)floppy Wrote:  Where can I find all the Forth Primitive?

There is no canonical list (at least none I've ever found), however to easily explore them, you can use VCAT (in the manual) to list all the words in the ROM, and then use uncolon ("UN:") from the Developers handbook to decompile the Forth words (written in Forth), but these are not true primitives if you mean written in assembler.

While disassemblers do exist for the 71B, AFAIK, they all are aimed at disassembling LEX files, which are structurally very different from Forth primitives, so it's highly doubtful if these would work.

--Bob Prosperi
Find all posts by this user
Quote this message in a reply
06-18-2024, 04:29 AM
Post: #92
RE: (71B) FORTH questions
(06-18-2024 02:57 AM)rprosperi Wrote:  to easily explore them, you can use VCAT (in the manual) to list all the words in the ROM

It's VLIST, on p.32 of the 82441A manual from April 1984.

http://WilsonMinesCo.com  (Lots of HP-41 links at the bottom of the links page, at http://wilsonminesco.com/links.html#hp41 )
Visit this user's website Find all posts by this user
Quote this message in a reply
06-18-2024, 09:42 AM (This post was last modified: 06-18-2024 06:36 PM by floppy.)
Post: #93
RE: (71B) FORTH questions
(06-18-2024 04:29 AM)Garth Wilson Wrote:  It's VLIST, on p.32 of the 82441A manual from April 1984.
Thanks. Output of it is below (if need of anybody in a text form).
However, the entry points E717A and E71A5 and E7320 are not seen: in a readable assembler code like in the IDS V3.. My new path: I will have a look now how to dump the module then to print the assembler in a readable form.
VLIST
Code:
"
(
?
:
]
;
*
#
.
[
/
,
3
2
1
0
@
!
>
<
=
-
+
J
I
'
L
T
Z
Y
X
S<
S=
S!
C,
U.
<>
M*
D<
<#
#>
#S
CR
*/
D.
M/
S0
.(
."
DO
IF
C!
C@
BL
D+
D-
U<
0>
0<
1-
2-
1+
2+
5-
5+
2/
2*
+!
0=
OR
R@
>R
R>
OF
F/
F*
F-
F+
N!
N@
F.
LN
H.
.S
IP
FP
ASC
VAL
POS
EOF
MAX
MIN
D.R
MOD
PAD
KEY
BYE
>IN
BLK
USE
TIB
RP0
SP0
ABS
NOT
XOR
AND
ROT
DUP
RP!
RP@
SP!
C@+
SP@
RDN
RUP
E^X
Y^X
1/X
X^2
TAN
COS
SIN
ENG
SCI
FIX
STD
RCL
STO
[']
UM*
CHS
LGT
HEX
4N@
S>&
S<&
END$
CHR$
STR$
SUB$
+BUF
TYPE
CASE
SIGN
?DUP
HOLD
/MOD
HERE
EMIT
WORD
QUIT
FIND
ROLL
LOOP
ELSE
THEN
BASE
PREV
WARN
S->D
DABS
FILL
2DUP
OVER
PICK
SWAP
DROP
GROW
10^X
X<>Y
ATAN
ACOS
ASIN
EXIT
SPAN
#TIB
FTOI
ITOF
SQRT
X#Y?
X=Y?
X>Y?
X=0?
X<Y?
CRLF
FABS
LEFT$
SMOVE
NULL$
OPENF
LOADF
BLOCK
ENDOF
M/MOD
*/MOD
DEPTH
SPACE
ABORT
?COMP
ALLOT
QUERY
CMOVE
+LOOP
WHILE
UNTIL
BEGIN
DOES>
LEAVE
LINE#
LIMIT
FIRST
STATE
ONERR
OKFLG
FENCE
WIDTH
COUNT
2SWAP
DIGIT
2DROP
NMOVE
2OVER
ENTER
LASTX
>BODY
FLUSH
EXPBF
CONBF
X>=Y?
X<=Y?
FINDF
FDROP
VARID
FSTR$
NFILL
RIGHT$
MAXLEN
STRING
CLOSEF
SMUDGE
SPACES
ABORT"
NUMBER
TOGGLE
LATEST
?STACK
FORGET
REPEAT
CREATE
SCRFIB
NMOVE>
CMOVE>
NEGATE
SHRINK
OUTPUT
BASICX
FENTER
UM/MOD
KILLBF
FINDBF
MAKEBF
BASIC$
BASICF
BASICI
NALLOT
ADJUSTF
SYNTAXF
CREATEF
ENDCASE
COMPILE
LITERAL
'STREAM
ENCLOSE
CONVERT
DECIMAL
CURRENT
CONTEXT
DNEGATE
DEGREES
RADIANS
EXECUTE
PRIMARY
LISTING
CLOSEALL
DLITERAL
TRAVERSE
EXPECT96
VARIABLE
CONSTANT
FLITERAL
PAGESIZE
ASSEMBLE
IMMEDIATE
-TRAILING
INTERPRET
[COMPILE]
SECONDARY
FVARIABLE
FCONSTANT
?TERMINAL
VOCABULARY
DEFINITIONS
STRING-ARRAY

Are the entries listed above in the post top, the CFA address of some words?
when I see the "lift floating point stack" then I was thinking about FENTER. Then I tried to find it.. but it shows E4C0F. Then perhaps thats not the correct way.
" FENTER" S. . 2- FIND S. . HEX .
[ 35491 6 ] 6 [ E4C0F FFFFF ] -1 -1B3F1 OK { 0 }
UN: FENTER show.
Word: FENTER
LFA: E4BFC Link: E4B8A
NFA: E4C01 686454E445542D
CFA: E4C0F Primitive
OK { 0 }

Now I will scan the other Forth words till I find the searched entry points.

UPDATE/CLOSURE: the Forth entry points are found in the 71ForthASM_IMS_IDS.pdf (entry point E7320 found in page 298 of the pdf file).

HP71B 4TH/ASM/Multimod, HP41CV/X/Y & Nov64d, PILBOX, HP-IL 821.62A & 64A & 66A, Deb11 64b-PC & PI2 3 4 w/ ILPER, VIDEO80, V41 & EMU71, DM41X
Find all posts by this user
Quote this message in a reply
07-03-2024, 09:31 AM
Post: #94
RE: (71B) FORTH questions
I was searching for Forth words written in ASM using float numbers. Apart the IDS 1 2 3 and Forth ROM IDS and TIMEASM ( and JPC ROM http://www.jeffcalc.hp41.eu/emu71/files/jpclstx.pdf ) where I could find a light mix of float and integer ASM code lines, I could not find anything. Has anybody some hint where to find float functions written in ASM? (outside the HP OS/ROM SW listings)
Thanks.

HP71B 4TH/ASM/Multimod, HP41CV/X/Y & Nov64d, PILBOX, HP-IL 821.62A & 64A & 66A, Deb11 64b-PC & PI2 3 4 w/ ILPER, VIDEO80, V41 & EMU71, DM41X
Find all posts by this user
Quote this message in a reply
07-03-2024, 11:47 AM
Post: #95
RE: (71B) FORTH questions
(07-03-2024 09:31 AM)floppy Wrote:  I was searching for Forth words written in ASM using float numbers. Apart the IDS 1 2 3 and Forth ROM IDS and TIMEASM ( and JPC ROM http://www.jeffcalc.hp41.eu/emu71/files/jpclstx.pdf ) where I could find a light mix of float and integer ASM code lines, I could not find anything. Has anybody some hint where to find float functions written in ASM? (outside the HP OS/ROM SW listings)
Thanks.

I hope you find something, but I doubt it; I've looked for 30+ years and never found any, or even heard that some exist. The only 'source' of such might be to disassemble programs such as the excellent RPN program from Chris Capener (it's in all the usual 71B LEX collections, although this program was a BIN file, not a LEX).

--Bob Prosperi
Find all posts by this user
Quote this message in a reply
07-05-2024, 08:07 AM (This post was last modified: 07-07-2024 03:13 AM by brouhaha.)
Post: #96
RE: (71B) FORTH questions
(07-03-2024 09:31 AM)floppy Wrote:  Has anybody some hint where to find float functions written in ASM? (outside the HP OS/ROM SW listings)

It seems unlikely that there are any floating point routines for Saturn (or the earlier HP calculator architectures) other than the ones built into the machine. There was no advantage to rolling your own, and huge advantage to using what was provided. Even third-party ROMs for the 41 called the 41 mainframe ROMs to do floating point. The 71 was the first machine in the HP APD and CVD development line for which the floating point routines were actually officially documented and supported by HP. The detailed documentation is in the 71B Software IDS Volume II, and the source code in Volume III.

The HP-71 FORTH/Assembler ROM provides floating point words, documented on pages 19-21 of the FORTH/Assembler ROM Owner's Manual. These of course use the mainframe floating point rotuines.

All later HP calculators based on Saturn processors (or Saturn emulated on ARM) used floating point routines derived from the HP-71, but some of the IEEE support was deemed unnecessary and removed.

All HP calculators based on the Nut architecture (41C/CV/CX, 10C-12C, 15C, 16C) used floating point routines nearly identical to the prior 30 series, which themselves are not too different than the 19C/29C/67/97 routines.
Find all posts by this user
Quote this message in a reply
07-05-2024, 11:56 AM
Post: #97
RE: (71B) FORTH questions
(07-05-2024 08:07 AM)brouhaha Wrote:  
(07-03-2024 09:31 AM)floppy Wrote:  Has anybody some hint where to find float functions written in ASM? (outside the HP OS/ROM SW listings)

The HP-71 FORTH/Assembler ROM provides floating point words, documented on pages 19-21 of the FORTH/Assembler ROM Owner's Manual. These of course use the mainframe floating point rotuines.

Thanks Eric, I had not thought of these! These are also well documented in the Forth/Assembler ROM IDS, so very useful examples of using the 71B ROM FP routines. That said, this is a seriously complex set of docs which takes a lot of time to wade through. I've never made much really useful sense of it all, but my motivation when I explored it was mere general curiosity, and did not focus on the FP words, so perhaps they are more clear.

--Bob Prosperi
Find all posts by this user
Quote this message in a reply
08-21-2024, 09:23 AM
Post: #98
RE: (71B) FORTH questions
(06-19-2023 09:08 PM)mfleming Wrote:  The .BIN file for the 41 Translator is available in various places. Load it into Emu71 and examine it there. The Forth library on which it is based is also available. You could even load the Translator into your MultiMod Smile
Is there an IDS manual for this translator module? Could not find one.

HP71B 4TH/ASM/Multimod, HP41CV/X/Y & Nov64d, PILBOX, HP-IL 821.62A & 64A & 66A, Deb11 64b-PC & PI2 3 4 w/ ILPER, VIDEO80, V41 & EMU71, DM41X
Find all posts by this user
Quote this message in a reply
08-21-2024, 11:54 AM
Post: #99
RE: (71B) FORTH questions
(08-21-2024 09:23 AM)floppy Wrote:  
(06-19-2023 09:08 PM)mfleming Wrote:  The .BIN file for the 41 Translator is available in various places. Load it into Emu71 and examine it there. The Forth library on which it is based is also available. You could even load the Translator into your MultiMod Smile
Is there an IDS manual for this translator module? Could not find one.

No, but Bill Wickes (author of the Translator) also wrote the "HP 82490A HP-41 Translator Pac Programmer's Toolkit" available at the time from HP's User Library Program, which is available here:

https://literature.hpcalc.org/items/1415

It is definitely NOT as detailed as the IDS and contains no source listing, but it will be a big help if you want to get into low-level details. Note that the toolkit itself (a .zip file with the utilities) is also provided towards the bottom.

--Bob Prosperi
Find all posts by this user
Quote this message in a reply
Post Reply 




User(s) browsing this thread: 12 Guest(s)