Jump to content
IGNORED

Camel99 Forth Information goes here


TheBF

Recommended Posts

11 hours ago, GDMike said:

I don't know what Post#998 is showing.

In Turboforth, there is a word "VWTR"

That writes the value in VALUE to VDP register REGISTER.

Example, $36 7 VWTR 

Changes screen color to red and char color to green.

I'm trying my register changes based on this word.

 

As ASMUR said some of this would be best handled on the F18 topic. But since most folks are not into Forth I will give you what I have that might help.

 

Edit simplified the code for just your purpose. Removed a Camel99 word that would not work on TF.

Edit2:  The count byte is decimal value.  Oops. Didn't matter on 9918, but it might reek holy hell on F18A.


CREATE 80COL
DECIMAL 15 C,  \ byte count for this array
\ -------------------
HEX    04 C,  \ VR1
       70 C,  \ VR2
       03 C,  \ VR3
       E8 C,  \ VR4
       01 C,  \ VR5
       06 C,  \ VR6
       00 C,  \ VR7
       17 C,  \ VR8
       88 C,  \ VR9
       00 C,  \ VR10
       00 C,  \ VR11
       00 C,  \ VR12
       94 C,  \ VR13
       10 C,  \ VR14
       00 C,  \ VR15

: VREGS    ( addr n -- ) 0 DO  COUNT  I VWTR   LOOP DROP ;

DECIMAL
: 80COLS   ( -- ) 80COL COUNT VREGS   PAGE ;

This takes a "counted" array of bytes and feeds them into the the VDP registers sequentially. 

You can cross-match the Video register numbers in the array to the docs and put difference values in there, reload the code and invoke 80COLS. 

There are many more registers of which I know no nothing. 

  • Like 1
  • Thanks 1
Link to comment
Share on other sites

RAID!  Raid - 17.5 Fluid Ounce Ant and CockRoach Killer - 48601355 - MSC  Industrial Supply

 

I found a bug in my implementation of ?DO that has implications for some code. Specifically any ?DO LOOP where there is any code after the word LOOP.

 

It didn't show up until I changed my TYPE code to a new faster "clever" version.

Originally TYPE looked like this:   (Note: PAUSE is to make it work properly when multi-tasking) 

: TYPE   ( addr cnt -- ) PAUSE  BOUNDS ?DO  I C@ (EMIT)  LOOP ;

Simple. BOUNDS computes the start and end address of the string, if they are the same ?DO jumps to the semi-colon, other wise it fetches each char and passes it to (EMIT).

It work well.

 

I found this idea on the web to use COUNT to both fetch the character and increment the address.  This version prints text 8% faster!

: TYPE     ( addr cnt -- ) PAUSE 0 ?DO COUNT (EMIT) LOOP DROP ; \ 8% faster

Remember how ?DO  tests the limit and index values of the DO LOOP and if they are the same jumps to EXIT?  Can you see the problem?

The DROP word is skipped over if this happens. This leaves the 'addr'  parameter sitting on the DATA stack... oops.

 

I fixed it this way since I cannot think of an efficient way to make ?DO know how to jump to LOOP instead of to ';'  .

: (TYPE) ( addr cnt -- ) 0 ?DO COUNT (EMIT) LOOP ;
: TYPE     ( addr cnt -- ) PAUSE (TYPE) DROP ;

In this version, (TYPE) jumps to its own semi-colon if cnt=0.  Then in the TYPE word there is DROP waiting to clean up.  Simple fix and very tiny performance hit.

 

TYPE has been corrected in the latest release.

 

So for the millions of users out there... you have been warned.

 

 

 

  • Like 1
  • Haha 1
Link to comment
Share on other sites

In the course of using VCHAR for the sorting demonstration I found the same ?DO LOOP bug.

 

Here is a new version for the multitudes to update their Camel99 DSK1.GRAFIX library file. 

Spoiler

CR .( GRAPHIX.FTH for CAMEL99 V2.X  July 4, 2021 BFox )
CR
HERE
NEEDS VC, FROM DSK1.VDPMEM  \ use by new CALLCHAR

HEX
 0380 CONSTANT CTAB      \ colour table VDP address
 0800 CONSTANT PDT       \ "pattern descriptor table" VDP address

\ access VDP tables like arrays. Usage:  9 ]CTAB returns VDP addr
 : ]CTAB  ( set# -- 'ctab[n])   CTAB + ;    \ 1 byte fields
 : ]PDT   ( char# -- 'pdt[n] )  8* PDT + ;  \ 8 byte fields

\ ABORT to Forth with a msg if input is bad
: ?MODE  ( n -- )      VMODE @ <>   ABORT" Bad mode" ;
: ?COLOR ( n -- n )    DUP 16 U>    ABORT" Bad Color" ;
: ?SCR   ( vdpadr -- ) C/SCR @ CHAR+ > ABORT" too many chars"  ;

( takes fg nibble, bg nibble, convert to TI hardware no.)
( test for legal values, and combine into 1 byte)
: >COLR ( fg bg -- byte) 1- ?COLOR SWAP 1- ?COLOR  04 LSHIFT + ;
.( .)
\ ti-basic sub-programs begin
: CLEAR  ( -- ) PAGE  0 17 AT-XY  ; ( because you love it )

: COLOR  ( character-set fg-color bg-color -- )
          1 ?MODE  >COLR SWAP ]CTAB  VC! ;

\ ascii value SET# returns the character set no.
: SET#  ( ascii -- set#) 3 RSHIFT ;

( *NEW*  change RANGE of character sets at once)
: COLORS  ( set1 set2 fg bg  -- )
          1 ?MODE
          >COLR >R
          SWAP ]CTAB SWAP ]CTAB OVER - R> VFILL ;

: SCREEN ( color -- )
         1 ?MODE             \ check for MODE 1
         1- ?COLOR ( -- n)   \ TI-BASIC color to VDP color and test
         7 VWTR  ;           \ set screen colour in Video register 7
.( .)
 : GRAPHICS  ( -- )
      1 VMODE !
      0 3C0  0 VFILL \ erase the entire 40 col. screen space
      E0 DUP 83D4 C! \ KSCAN re-writes VDP Reg1 with this byte
( -- E0) 1 VWTR      \ VDP register 1  bit3 = 0 = Graphics Mode
      0E 3 VWTR        \ color table
      01 4 VWTR        \ pattern table
      06 5 VWTR        \ sprite attribute table
      01 6 VWTR        \ set sprite pattern table to 1x$800=$800
      CTAB 10 10 VFILL \ color table: black on transparent [1,0]
      8 SCREEN         \ cyan SCREEN
      20 C/L!          \ 32 chars/line
      CLEAR ;

: >DIG  ( char -- n) DIGIT? 0= ABORT" Bad digit" ;
: CALLCHAR ( addr len char --) \ can be used for longstrings (128 bytes)
        BASE @  VP @ 2>R  \ save these variables
        ]PDT VP !         \ set vdp mem pointer to character location
        HEX               \ we are converting hex numbers in the string
        BOUNDS
        DO
           I    C@ >DIG  4 LSHIFT
           I 1+ C@ >DIG  OR VC,
        2 +LOOP
        2R> VP ! BASE !  \ restore the variables
;
.( .)
\ PATTERN: is deprecated. Use CREATE and comma
 : PATTERN: ( u u u u -- ) CREATE  >R >R >R  , R> , R> , R> , ;

: CHARDEF  ( addr char# --)  ]PDT      8 VWRITE ; \ write pattern to PDT
: CHARPAT  ( addr char# --)  ]PDT SWAP 8 VREAD ;  \ read pattern to 'addr'
: GCHAR    ( col row -- char) >VPOS VC@ ; \ does not affect VROW,VCOL

: HCHAR   ( col row char cnt -- )
          2SWAP >VPOS   ( -- char cnt vdp_addr)
          2DUP + ?SCR
         -ROT SWAP VFILL ;

\ change to Graphics mode (C/SCR = HEX300) to compile VCHAR correctly
GRAPHICS
: (VCHAR) ( char vdp_addr cnt --)
          0 ?DO               ( -- char vadr)
             2DUP VC!       \ write a character
             C/L@ +         \ bump address by char-per-line
             DUP [ C/SCR @ 1- ] LITERAL >
             IF
                 [ C/SCR @ 1- ] LITERAL -
             THEN
          LOOP ;

: VCHAR  ( col row char cnt -- ) 2SWAP >VPOS SWAP (VCHAR) 2DROP ;

CR .( GRAPHICS 1 Mode READY)
CR HERE SWAP - DECIMAL . .( bytes)
HEX

 

 

  • Like 2
Link to comment
Share on other sites

Different ways to do the same thing.

 

While looking at my VCHAR I decided to open the archives to see how it was done in TI-Forth many years ago.

Here is the original code:

: VCHAR ( X Y CNT CH ---  )
      >R >R SCRN_WIDTH @ * + SCRN_END @ SCRN_START @ - SWAP
      R> R> SWAP 0 DO SWAP OVER OVER SCRN_START @ + VSBW SCRN_WIDTH
      @ + ROT OVER OVER /MOD IF 1+ SCRN_WIDTH @ OVER OVER = IF -
      ELSE DROP ENDIF ENDIF ROT DROP ROT LOOP DROP DROP DROP ;

Ok lets  reformat that a little bit.

: VCHAR ( X Y CNT CH ---  )
      >R >R 
      SCRN_WIDTH @ * + SCRN_END @ SCRN_START @ - SWAP
      R> R> 
      SWAP 0 
      DO 
         SWAP OVER OVER SCRN_START @ + VSBW 
         SCRN_WIDTH @ + ROT OVER OVER /MOD 
         IF 1+ SCRN_WIDTH @ OVER OVER = 
           IF -
           ELSE DROP 
           ENDIF 
       ENDIF 
       ROT DROP ROT 
     LOOP 
     DROP DROP DROP ;

OMG that's a lot of code!  49  Forth tokens (ENDIF does not run code at runtime) 

VCHAR also uses a lot of slow functions;  division, multiple rotates and OVER OVER is used three times.

 

This is an opportunity look at factoring code the Forth way.

 

Right away we could factor out OVER OVER as 2DUP.  This should be a code word for full speed.
 

We can also see >R >R   two words that must be matched with R> R>

In Camel99 VCHAR, this is replaced by a general purpose word 2SWAP which is also ASM CODE.
An alternative would be to use the Forth word 2>R  and 2R>  

 

The 2nd line...

  SCRN_WIDTH @ * + SCRN_END @ SCRN_START @ -

... is handled in Camel99 by another CODE word that computes the VDP address from the x,y coordinates called >VPOS. 

>VPOS takes into account which video page we are using and is re-useable anytime you need to calculate a VDP address from x and y.

It used five times in the GRAFIC library file so it very re-useable.

 

In fairness I am sure the guys developing TI-FORTH had no time to optimize their code. They were racing to make it work.

A final product would no doubt have been quite a bit better. We can see what could have been in FbForth.

 

 

For reference here is the new version in Camel99 .  13 Forth tokens.

: (VCHAR) ( char vdp_addr cnt --)
          0 ?DO               ( -- char vadr)
             2DUP VC!       \ write a character
             C/L@ +         \ bump address by char-per-line
             DUP [ C/SCR @ 1- ] LITERAL >
             IF
                 [ C/SCR @ 1- ] LITERAL -
             THEN
          LOOP ;

: VCHAR  ( col row char cnt -- ) 2SWAP >VPOS SWAP (VCHAR) 2DROP ;

 

There is something in this code that I didn't use for years when using Forth so here is some explanation for new Forth programmers.

 

In case you have never used  [     ]  in Forth here is what's happening.

 

We want the number of "characters per screen"  held in the variable C/SCR.

We also want that value minus one.

 

So we could code:

C/SCR @  1- 

That will work just fine but it is three calls to three Forth words. Each call takes time. These three calls are in a loop so we pay for it every time the loop goes around!

 

It would be better is we have that number already calculated like a constant.

 

We could make a new CONSTANT for example to "pre-calculate" this number like this:

C/SCR @ 1- CONSTANT C/SCR2  

But that takes extra space in the dictionary and we are only using that constant twice in this code so it's a bit of a waste.

 

The alternative is:

  1. Drop out of the compiler with  [      This actually turns off the compiler. :) 
  2. Now we can do our variable fetch and subtract 1 in the interpreter. (immediately)  This leaves our magic number on the data stack
  3. Turn on the compiler back on with ]
  4. Use LITERAL to take the number we left on the data stack and compile it as  "literal" number. 
    (literal numbers are like when you just put a number in your definitions rather than making a constant)

 

 

 

 

 

 

 

 

 

 

  • Like 2
Link to comment
Share on other sites

You can't brick the F18A from the host computer directly or by writing to any VDP registers.  The only way to write to the onboard flash (that holds the FPGA's bit stream) is to use a few repurposed 9900 instructions via the GPU.  So you would have to write the correct GPU program, load it to VRAM, and tell the GPU to execute at the correct location.  In theory it is "possible" you might do that via random data and pure chance, but I'm going to say it just can't happen.  If you do manage to brick your F18A from the host system, I will gladly reprogram it for you.

  • Like 2
Link to comment
Share on other sites

49 minutes ago, matthew180 said:

You can't brick the F18A from the host computer directly or by writing to any VDP registers.  The only way to write to the onboard flash (that holds the FPGA's bit stream) is to use a few repurposed 9900 instructions via the GPU.  So you would have to write the correct GPU program, load it to VRAM, and tell the GPU to execute at the correct location.  In theory it is "possible" you might do that via random data and pure chance, but I'm going to say it just can't happen.  If you do manage to brick your F18A from the host system, I will gladly reprogram it for you.

Good to know.  I read it in the docs so I passed it along. :) 

Given that Forth lets you do anything, it can go into random loops and do stuff, if one is not careful.

 

Murphy's law of Engineering

"It's impossible to make something idiot proof because idiots are too ingenious"

  • Like 1
Link to comment
Share on other sites

SAMS Card Tests

 

Here is the source code for the SAMSTESTER program.

It needs E/A cartridge to run.

 

Edit: Updated source code July 6. Removed some duplicated words.

 

Spoiler

\ sams card test using SAMS BLOCK function July 5 2021 Fox

\ NEEDS DUMP    FROM DSK1.TOOLS
\ NEEDS SDUMP   FROM DSK1.SAMSDUMP
NEEDS SBLOCK   FROM DSK1.SAMSBLOCK
NEEDS COMPARE FROM DSK1.COMPARE
NEEDS ELAPSE  FROM DSK1.ELAPSE
NEEDS U.R     FROM DSK1.UDOTR

MARKER /SAMSTEST   \ command to remove everything when you are done.
HEX
\ *set the CRU address in 'R12 before using these words*
  CODE 0SBO  ( -- ) 1D00 ,  NEXT, ENDCODE
  CODE 0SBZ  ( -- ) 1E00 ,  NEXT, ENDCODE

CREATE FF$  20 ALLOT  FF$ 20 FF FILL
CREATE AA$  20 ALLOT  AA$ 20 AA FILL

: ?SAMSCARD  ABORT" SAMS card not present" ;

: REGTEST ( -- )
      1E00 'R12 !        \ select SAMS card CRU address
      SAMS-OFF           \ mapper off
      0SBO               \ turn on register memory
      4000 PAD 20 CMOVE  \ save the registers

      CR ." Register test for >FFFF"
      FF$ 4000 20 CMOVE
\      4000 20 DUMP
      4000 FF$ 20 S= ?SAMSCARD
      CR ." PASS "

      CR
      CR ." Register test for >AAAA"
      AA$ 4000 20 CMOVE
\      4000 20 DUMP
      4000 AA$ 20 S= ?SAMSCARD
      CR ." PASS "
      CR
      CR ." Restoring registers"
      PAD 4000 20 CMOVE  \ restore registers
      0SBZ
      SAMS-ON
;

HEX
7FFF CONSTANT 32K
FFFF CONSTANT 64K
1000 CONSTANT 4K

VARIABLE BLK
VARIABLE FATAL
VARIABLE PAT   \ remember the pattern we are using

: ?FATAL ( flag -- ) FATAL @ AND IF CR ." Stopped on failure" ABORT THEN ;

: ?BREAK   ?TERMINAL ABORT" *HALTED*" ;

CREATE PBUFFER   4K ALLOT  \ pattern buffer holds data we are testing

CODE MOVE16 ( addr1 addr2 len -- ) \ fast move 16bit cells
    C036 , C076 , C104 , 1306 , 0584 ,
    0244 , FFFE , CC31 , 0644 , 15FD ,
    C136 , NEXT,
ENDCODE

: BINARY   2 BASE ! ;
: .BIN ( c -- )  BASE @ >R  BINARY  8 U.R  R> BASE ! ;
: .HEX ( c -- )  BASE @ >R  HEX 3 U.R  R> BASE ! ;

: FILLREFBUFF  ( -- )  PBUFFER 4K PAT @  FILL ;

: .PATTERN ( c -- ) PAT @  DUP .HEX  ." (" .BIN  ." ) " ;
: SETPATTERN ( char -- )
        PAT !
        CR ." Bit Pattern = " .PATTERN
        FILLREFBUFF
        CR ;

\ move pattern-buffer into a SAMS block
: FILLBLOCK ( n -- ) PBUFFER SWAP SBLOCK 4K MOVE16 ;
: CLRBLOCK  ( n )  SBLOCK 4K 0 FILL ;
: TESTBLOCK ( n -- ?) DUP BLK ! SBLOCK PBUFFER 1000 S= ;

DECIMAL
: PAGETEST ( start end  -- )
          DECIMAL
          FILLREFBUFF
          SWAP ( end start )
          ?DO
              CR ." Page# " I  3 .R ." , " .PATTERN
              I 10 16 WITHIN ABORT" Illegal Page#"
              I FILLBLOCK
              I TESTBLOCK
              DUP 0= IF ." PASS"
              ELSE  ." FAIL"
              THEN  ?FATAL
              ?BREAK
        LOOP
;

DECIMAL
: LEGALTESTS   0 10 PAGETEST   16 256 PAGETEST ;

HEX AA SETPATTERN
DECIMAL
: SAMSTEST
      PAGE
      CR ." SAMS 1M Card memory test"
      CR ." -----------------------"
      REGTEST
      LEGALTESTS ;

HEX AA SETPATTERN
: PAT++   PAT @ 1+ 00FF AND PAT ! ;

DECIMAL
VARIABLE ITERATIONS
: REPTEST ( -- )
     DECIMAL
     ITERATIONS OFF
     PAGE ." SAMS Repeating Test"
     CR   ." --------------------"
     BEGIN
         CR
         CR ." >Iteration #" ITERATIONS @  5 .R
         CR ." >Memory Pattern= " .PATTERN
         CR
         2000 MS
         SAMSTEST
         ITERATIONS 1+!
         PAT++
         ?BREAK
     AGAIN ;

: HELP
  PAGE ." * SAMS 1Mb TESTER Help *"
  CR ." --------------------------"
  CR ." HEX xx SETPATTERN"
  CR
  CR ." SAMSTEST test pages"
  CR ." REPTEST  continous testing"
  CR ." x y PAGETEST  test pages x to y"
  CR
  CR ." FATAL ON   STOPS on error"
  CR ." FATAL OFF  No stop on error"
  CR
  CR ." HELP  show this screen"
  CR ." BYE   leave the program"
;

: COLD   WARM
         PAGE ." SAMS Tester V2.0  @theBF 2021"
         CR ." Initializing... "
         SAMSINI  ." Done "
         CR ." Test pattern is " .PATTERN
         CR ." Type HELP to see commands"
         ABORT ;

 LOCK
 INCLUDE DSK1.SAVESYS
 ' COLD SAVESYS DSK2.SAMSTESTER

 

 

 

  • Like 3
Link to comment
Share on other sites

SAMSTESTER Update

 

I sent the source code over RS232 to Camel99 TTY version to run on real hardware and left it running overnight.

It's still running. :) 

 

I found some duplicate definitions in the original code that were not needed (already in the SAMSBLOCK lib file)

I will update the source code in the spoiler in the previous post.

  • Like 2
Link to comment
Share on other sites

46 minutes ago, TheBF said:

SAMSTESTER Update

 

I sent the source code over RS232 to Camel99 TTY version to run on real hardware and left it running overnight.

It's still running. :)

 

I found some duplicate definitions in the original code that were not needed (already in the SAMSBLOCK lib file)

I will update the source code in the spoiler in the previous post.

Just think, maybe it's a good thing not to add a speed control, where F0 places the TI in regular speed, turbo like the older PCs had. 

 

Link to comment
Share on other sites

13 hours ago, TheBF said:

Good to know.  I read it in the docs so I passed it along. :) 

Given that Forth lets you do anything, it can go into random loops and do stuff, if one is not careful.

 

Murphy's law of Engineering

"It's impossible to make something idiot proof because idiots are too ingenious"

In this case, those random loops would have to be code running on the GPU inside the F18A, which, as far as I know, none of the Forth interpreters currently utilize.  Even using assembly you would have a hard time accidentally bricking the F18A.  At any rate, if experimenting with VDP registers is how anyone wants to mess with the F18A, that should be fine, nothing bad will happen.

  • Like 2
  • Thanks 1
Link to comment
Share on other sites

3 hours ago, matthew180 said:

In this case, those random loops would have to be code running on the GPU inside the F18A, which, as far as I know, none of the Forth interpreters currently utilize.  Even using assembly you would have a hard time accidentally bricking the F18A.  At any rate, if experimenting with VDP registers is how anyone wants to mess with the F18A, that should be fine, nothing bad will happen.

Thank you. That's very good to know.

So Mike can just bash away at the registers and explore the hardware until he's happy.

  • Haha 1
Link to comment
Share on other sites

6 hours ago, GDMike said:

Just think, maybe it's a good thing not to add a speed control, where F0 places the TI in regular speed, turbo like the older PCs had. 

 

Do you mean because I would be able to make more mistakes per minute?  :)  

You might be right.

  • Haha 2
Link to comment
Share on other sites

Better Code for ANSI Escape String Interpretation

 

Building an editor to operator over RS232 means you need to interpret strings of characters that are sent to TI-99 by the ANSI terminal.

These are short strings that begin with the Escape character.  (HEX 1B) 

Below is a list of some of the strings and their key strokes . Each of these strings is prefaced by the <ESC> character which makes it simple to call a different case statement for these key strokes. 

  "[B"      DOWN   
  "[C"      CURSRIGHT 
  "[D"      CURSLEFT  
  "[Z"      BACKTAB   
  "[1~"     HOME      
  "[2~"     INSERT    
  "[4~"     TOEOL     
  "[5~"     PGUP      
  "[6~"     PGDN      
  " [11~"   [F1]      
  "[12~"    [F2]      
  "[13~"    [F3]      
  "[14~"    [F4]      
  "[15~"    [F5]      
  "[17~"    [F6]      
  "[18~"    [F7]      
  "[19~"    [F8]     
  

In the BETTY editor I resorted to using an extension to the CASE statement that was first created as a curiosity to a question by @Vorticon as to how you could make a string case statement in Pascal.  $OF let Forth do this but it's not very fast since it has to do a string comparison on each case.

 

I was reading about higher order functions in other languages and came across something called REDUCE or FOLD. This lets you do something to a list of items like add them up. This made me realize that I could REDUCE the ANSI escape strings into a number very easily. 

 

My first code accepted the string into memory then ran FOLD to derive the sum of the characters.


: FOLD  ( addr len -- n) 0 -ROT BOUNDS ?DO  I C@ +  LOOP ; 

\ TKEY wait for a key -or- counter hits zero
\ Approx. 1 mS per count value on TI-99/4A
DECIMAL
: TKEY ( wait-time -- 0 | c )
        BEGIN
          DUP
        WHILE
          CKEY? ?DUP
          IF   NIP EXIT
        THEN 1-
        REPEAT ;

\ ESCape sequence reader. Needed for polled RS232.
: KEYS  ( caddr n -- n') \ store n KEYS into caddr[i] sequentially
        OVER + OVER
        BEGIN
          150 TKEY   \ wait 250 mS MAX for a character
        DUP WHILE
            OVER C!  \ store char in caddr
            1+       \ bump n
        REPEAT
        OVER C!       \ store last character
        NIP SWAP -    \ compute length
;

 

Then I realized I could combine those two functions and sum the characters while I read them.  Much more efficient.

\ ESCape sequence reducer covertS esc sequence into a number
: ESC-CODE  ( -- code) \ store n KEYS into caddr[i] sequentially
        0
        BEGIN
          120 TKEY   \ wait 120 mS for a character
        DUP WHILE
             +       \ add char value to accumulator
        REPEAT
        DROP
;

Using this I can use a normal integer case statement which is way faster than comparing strings.

 

All this to say I am porting ED99 to become ED99TTY to give me DV80 text file editing over RS232.

It is sooo much simpler with an 80 column display. :) 

 

  • Like 3
Link to comment
Share on other sites

In the 90s there was an amazing Forth system for DOS called FPC written by Tom Zimmer.

One of the cool innovations that it had was color coded words. This lets you quickly see the function of a word by the color.

 

Talking to the TI-99 over RS232 gives us the ability to colorize each letter individually if we want to so I tried making this work on Camel99 TTY.

Here I used white for colon definitions, green for variables, blue for constants, magenta for user variables and red for CODE words.

There are some warts in the guts of my implementation that make it a bit trickier to find the actual code field address to select the color but it works ok. 

 

Spoiler

\ color words
NEEDS RED  FROM DSK1.VT100COLOR
NEEDS CASE FROM DSK1.CASE

MARKER /COLORS

DECIMAL
: ?BREAK  ( -- ) ?TERMINAL ABORT" *BREAK*" ;

: SPACEBAR ( -- ) KEY? BL = IF KEY DROP  THEN ;

: ?CR     ( addr len -- addr len) VCOL @ OVER + 132 >  IF  CR  THEN ;

HEX
: NFA>COLOR  ( nfa -- )
           NFA>CFA @
           CASE
                   839E OF  WHT <FG>  ENDOF
              ['] DOVAR OF  GRN <FG>  ENDOF
              ['] DOCON OF  BLU <FG>  ENDOF
              ['] DOUSER @ OF MAG <FG>  ENDOF
                  RED <FG>
           ENDCASE ;

: .COLORID  ( NFAaddr --) DUP NFA>COLOR  COUNT 1F AND ?CR TYPE SPACE ;

DECIMAL
: WORDS   ( -- )
           CR
           0 >R        ( word counter on stack)
           LATEST @
           BEGIN
             ?BREAK  SPACEBAR
             ( -- nfa) DUP .COLORID
             R> 1+ >R       \ inc. the counter
             NFA>LFA @ DUP
           0= UNTIL
           DROP
           WHT <FG>  CR R> U. SPACE ." words" ;

 

 

  • Like 1
  • Thanks 1
Link to comment
Share on other sites

Github does not like DOS files?

 

Ed of DxForth fame found the references to DxForth here, where I borrowed some of his ideas for my own education.

He took the brave step of reading my instructions and starting up Classic99 and running Camel99 Forth. :) 

 

He then went one step further and tried to re-compile the kernel from the Github files and has discovered that GITHUB replaced all the CR chars with LF, a la UNIX I suppose, and of course my DOS compiler barfed all over that.

 

I will have to look at some way to convince GITHUB to not alter the files.

Does anyone know if this can be done?

 

 

Big thanks to Ed who should be awarded the medal for bravery.

 

 

 

  • Like 1
Link to comment
Share on other sites

Thank you.  

 

For all the amateurs out there like me,  the  .gitattributes file is used to configure this aspect of GIT.

 

I changed mine to this per instructions found on the inter-web.

  
*.HSF linguist-language=Forth

# Set the default behavior, in case people don't have core.autocrlf set.
* text eol=crlf

# Explicitly declare text files you want to always be normalized and converted
# to native line endings on checkout.
*.hsf text
*.fth text

 

Link to comment
Share on other sites

9 hours ago, TheBF said:

Github does not like DOS files?

 

Ed of DxForth fame found the references to DxForth here, where I borrowed some of his ideas for my own education.

He took the brave step of reading my instructions and starting up Classic99 and running Camel99 Forth. :) 

 

He then went one step further and tried to re-compile the kernel from the Github files and has discovered that GITHUB replaced all the CR chars with LF, a la UNIX I suppose, and of course my DOS compiler barfed all over that.

 

I will have to look at some way to convince GITHUB to not alter the files.

Does anyone know if this can be done?

 

 

Big thanks to Ed who should be awarded the medal for bravery.

 

 

 

Isn't it their antivirus doing the filtering. I'm assuming that is the catch.

Edited by GDMike
Link to comment
Share on other sites

10 hours ago, GDMike said:

Isn't it their antivirus doing the filtering. I'm assuming that is the catch.

As I understand it everything is filtered for line endings but you can control the filtering with this .gitattributes file.

 

 

  • Thanks 1
Link to comment
Share on other sites

How do you spell relief?

 

After being given some good tests for my mixed math addition operator M+, by Ed of DxForth, both of which failed, I spun around in circles trying to make things correct. 

I got one then the other correct, repeatedly, but never both. :( 

 

In desperation I took a look at the bible.  You know the one by the prophet Lee Stewart.

And there, in that sacred tome my eyes fell upon these holy words:

M+ This word is not in fbForth 2.0, but can be created with the following
definition:
: M+ 0 D+ ;

 

"Holy shit!"  I shouted. (hoping the deity would abide my foul language)

 

ANS Forth has this operator S>D that converts a single to a double integer. However it is not just a zero in ANS Forth. It's tricky

 

: S>D     DUP  0< ;   ( This will return a 0 or a -1 ) 

 

So I tried this:

 

: M+     S>D   D+ ;

 

And it worked!

 

When I regained consciousness...

 

I decided to change my kernel to include a new shorter version of D+  and use that to make M+.

M+ is used in Camel Forth for the number conversion routine so this subtle bug has been sitting in Camel99 Forth forever.

 

All this because I wondered what it would take to generate PI digits in Forth and Found Ed's program.

 

And the side-effect of all this work is that my D+ operator is 40% smaller than the old one.

 

New release will be out later in the week.

 

 

 

 

 

 

 

 

 

PI-digits.png

  • Like 4
Link to comment
Share on other sites

16 hours ago, TheBF said:

In desperation I took a look at the bible.  You know the one by the prophet Lee Stewart.

And there, in that sacred tome my eyes fell upon these holy words:


M+ This word is not in fbForth 2.0, but can be created with the following
definition:
: M+ 0 D+ ;

 

 

Hah! The only credit I can take for this morsel is changing “TI Forth” to “fbForth 2.0”. 

 

16 hours ago, TheBF said:

"Holy shit!"  I shouted. (hoping the deity would abide my foul language)

 

No worries—I’ve done worse. |:)

 

16 hours ago, TheBF said:

ANS Forth has this operator S>D that converts a single to a double integer. However it is not just a zero in ANS Forth. It's tricky

 

: S>D     DUP  0< ;   ( This will return a 0 or a -1 ) 

 

So I tried this:

 

: M+     S>D   D+ ;

 

I looked at the stack signature for M+ in Starting FORTH and was surprised to find that, given the definition by the TI Forth developers, it was

( d n -- d-sum )

rather than 

( ud u -- ud-sum )

which makes your definition the one that should have been suggested, though in TI Forth and fbForth, that would use S->D rather than S>D :

: M+   ( d n -- d-sum )
   S->D   D+ ;

...lee

  • Like 1
Link to comment
Share on other sites

Join the conversation

You can post now and register later. If you have an account, sign in now to post with your account.
Note: Your post will require moderator approval before it will be visible.

Guest
Reply to this topic...

×   Pasted as rich text.   Paste as plain text instead

  Only 75 emoji are allowed.

×   Your link has been automatically embedded.   Display as a link instead

×   Your previous content has been restored.   Clear editor

×   You cannot paste images directly. Upload or insert images from URL.

Loading...
  • Recently Browsing   0 members

    • No registered users viewing this page.
×
×
  • Create New...