Fortran CHIP-8 interpreter

I’d like to introduce fc8 - a Fortran CHIP-8 interpreter:

CHIP-8 is an interpreted programming language developed by Joseph Weisbecker for the COSMAC RCA 1802, an 8-bit microprocessor launched in 1974. Essentially, it’s a minimalist game platform and can also be seen as a virtual machine.

Here is a demonstration of fc8 in action for the game “BRIX”, a CHIP-8 variation of the famous Breakout game:

Screenshot_2023-11-11_14-33-33

CHIP-8 programs are written with hexadecimal opcodes, similar to machine instructions. There are just over 30 instructions. Since assembling CHIP-8 by hand is tedious, today there exist some high-level assemblers, such as Octo. For fun, I have implemented my own CHIP-8 assembly syntax using the customasm assembler.

To learn more about CHIP-8, I recommend the article Programming in CHIP-8 by Harry Kleinberg. A scan of the article can be found here (PDF, 4MB) starting on page 28.

The article from Kleinberg gives the “Jumping X and O” program. I have re-written the program in customasm for clarity:

Jumping X and O
#include "chip8.asm"

; Jumping X and O Program
;
; The original hexadecimal listing of this program can be 
; found in the article,
;
;   H. Kleinberg. Programming in CHIP-8.
;   RCA Corporation, 1978.

main:
    LD I, block_pattern ; Set I to block pattern
    LD V5, 0x30         ; Coordinates (x,y) of block
    LD V6, 0x04         
    DRW V5, V6, 6       ; Show block at V5, V6
.setx:
    LD I, x_pattern     ; Set I to X pattern
    CALL jump           ; Do subroutine "jump"
.seto:
    LD I, o_pattern     ; Set I to O pattern
    CALL jump           ; Do subroutine "jump"
    JP .setx            ; Go to "setx" (Return to X pattern)
    
jump:
    LD V1, 30       ; Set V1, V2 to center coordinates
    LD V2, 13
.show1:
    DRW V1, V2, 5   ; Show the pattern
    LD V3, 0x0C     ; Set V3 to 0C (= 1/5 second)
    LD DT, V3       ; Set timer from V3
.timer:
    LD V4, DT       ; Timer -> V4
    SE V4, 0        ; Skip if V4 (timer) = 0
    JP .timer       ; Return to "timer" if V4 /= 0
    SNE VF, 1       ; Skip if VF = 1 (checking for overlap)
    JP .show2       ; Go to "show2" if VF /= 01 (overlap, switch patterns)
    DRW V1, V2, 5   ; If no overlap, show old pattern to erase
    RND V1, 0x3F    ; Random number (6-bit) to V1 (new x-coordinate)
    RND V2, 0x1F    ; Random number (5-bit) to V2 (new y-coordinate)
    JP .show1       ; Go back to "show1" to show pattern in new location
.show2:
    DRW V1, V2, 5   ; Show old pattern to erase
    RET             ; Return from subroutine
    
    
; Reserve some space for future changes directly
; in the hexadecimal listing
; (the value 14 is chosen to match the locations in the original listing)
#res 14

;
; Sprites
;
x_pattern:
    #d8 0b10001000
    #d8 0b01010000
    #d8 0b00100000
    #d8 0b01010000
    #d8 0b10001000

#align 16
o_pattern:
    #d8 0b11111000
    #d8 0b10001000
    #d8 0b10001000
    #d8 0b10001000
    #d8 0b11111000
    
#align 16
block_pattern:
    #d8 0b11111100
    #d8 0b11111100 
    #d8 0b11111100 
    #d8 0b11111100 
    #d8 0b11111100
    #d8 0b11111100

The compiled program listing is passed to the Fortran interpreter, which loads the instructions into memory, and reads them, byte-by-byte, decoding them and executing the corresponding action.

Looking forward to your comments!

Ivan

11 Likes

Nice! I compiled with GFortran on macOS and sdl2, it works.

With LFortran I got to 70% so far with some minor workarounds: Compiling fc8 · Issue #2845 · lfortran/lfortran · GitHub.

2 Likes

@ivanpribec did a great job with modern Fortran on this retro-computing project.

People could be surprised by the size of those CHIP-8 programs:

fc8/cartridges$ ls -Shor
total 32K
-rw-rw-r-- 1 osboxes   16 nov.  11 17:23 number_eight.ch8
-rw-rw-r-- 1 osboxes   82 nov.  11 17:23 jumping_x_and_o.ch8
-rw-rw-r-- 1 osboxes  132 nov.  11 17:23 IBM_logo.ch8
-rw-rw-r-- 1 osboxes  156 nov.  11 17:23 README.md
-rw-rw-r-- 1 osboxes  160 nov.  11 17:23 Fishie.ch8
-rw-rw-r-- 1 osboxes  280 nov.  11 17:23 BRIX
-rw-rw-r-- 1 osboxes  478 nov.  11 17:23 test_opcode.ch8
-rw-rw-r-- 1 osboxes 1,3K nov.  11 17:23 SPACE_INVADERS.ch8

The BRIX game (Steve Wozniak’s Breakout) is only 280 bytes long! Space Invaders is far longer, but maybe because there is a lot animated text before the game begins.

You may also be interested by:

2 Likes

Thanks @vmagnin, also for your book recommendation for Fire in the Valley, which I read in parallel to working on this project. It was a fun way to reconnect with the past and comprehend the significance of 8-bit microcomputers on computing as we know it today.

Fortran has always lived in a different neighbourhood, where the accuracy needs of scientists and engineers exceeded what 8-bits can provide. For this reason, I doubt any Fortran CHIP-8 interpreters were written in the past. At least I couldn’t find any.

Since you mention the modest program size, Space Invaders would already be on the limit of what the COSMAC VIP was capable of:

Keep in mind that the CHIP-8 interpreter must also reside in the computer memory! The original interpreter (written in RC 1802 machine instructions) fits in just 512 bytes (two pages of memory). You can find it in the original COSMAC VIP manual:

To play CHIP-8, you would need to manually load the interpreter into memory using the HEX keyboard (watch out for error!). You could then save it on a cassette tape for reuse. Games were shared as letters via the mail :email: :post_office: .

I’m not sure about the RCA 1802, but on the 6502 used in the Apple II, the zero page of memory would be faster than the rest, so that’s where you’d put your virtual registers and the interpreter itself. Steve Wozniak used this trick to get 16-bit addressing for his version of BASIC, using a bytecode language called SWEET16.

In the Fortran interpreter, I use the first 512 bytes of available memory to store the fonts, which frees up some space for games.

Sizewise, if I compile fc8 with the flag -Os it uses around 88 kilobytes, and the I/O library is about double of that:

~/fortran/FC8/build$ ll -lh *fc*
-rwxrwxr-x 1 ivan ivan  88K Nov 11 23:12 fc8*
-rw-rw-r-- 1 ivan ivan  587 Nov 11 23:09 fc8_cmd.mod
-rw-rw-r-- 1 ivan ivan 1,7K Nov 11 23:09 fc8_io.mod
-rw-rw-r-- 1 ivan ivan  595 Nov 11 23:09 fc8_vm.mod
-rw-rw-r-- 1 ivan ivan  50K Nov 11 23:12 libfc8_io.a
-rwxrwxr-x 1 ivan ivan 164K Nov 11 00:44 libfc8_io.so*

On top of this, it needs a bunch of shared libraries:

~/fortran/FC8/build$ ldd fc8
	linux-vdso.so.1 (0x00007fffdd69b000)
	libX11.so.6 => /lib/x86_64-linux-gnu/libX11.so.6 (0x00007faf67444000)
	libgfortran.so.5 => /lib/x86_64-linux-gnu/libgfortran.so.5 (0x00007faf6715e000)
	libm.so.6 => /lib/x86_64-linux-gnu/libm.so.6 (0x00007faf6700f000)
	libgcc_s.so.1 => /lib/x86_64-linux-gnu/libgcc_s.so.1 (0x00007faf66fea000)
	libc.so.6 => /lib/x86_64-linux-gnu/libc.so.6 (0x00007faf66df8000)
	libxcb.so.1 => /lib/x86_64-linux-gnu/libxcb.so.1 (0x00007faf66dcc000)
	libdl.so.2 => /lib/x86_64-linux-gnu/libdl.so.2 (0x00007faf66dc6000)
	/lib64/ld-linux-x86-64.so.2 (0x00007faf675b5000)
	libXau.so.6 => /lib/x86_64-linux-gnu/libXau.so.6 (0x00007faf66dc0000)
	libXdmcp.so.6 => /lib/x86_64-linux-gnu/libXdmcp.so.6 (0x00007faf66db8000)
	libbsd.so.0 => /lib/x86_64-linux-gnu/libbsd.so.0 (0x00007faf66d9e000)

It’s astonishing how the layers of the software stack accumulate so quickly…

1 Like

Thanks, great to hear that!

It would be super cool to use LFortran to compile a subset of Fortran to CHIP8. This could be used for a basic computer and compiler course for students.

Essentially the CHIP-8 virtual machine can support the following elements of Fortran

  • integer bitwise and arithmetic operations
  • loading and storing memory
  • control flow (if, select case)
  • goto
  • subroutines and functions (to a maximum call depth of 12 levels)

In addition there would be an intrinsic library of “hardware” routines for:

  • drawing sprites to the screen
  • clearing the screen
  • setting the sound and delay timers
  • checking for key presses
  • converting an integer to a binary-coded decimal

Returning to the jumping X and O program, a relaxed Fortran dialect targeting CHIP-8 could look something this:

program jumping_x_and_o

! X sprite
word :: xs(*) = [b'10001000', &
                 b'01010000', &
                 b'00100000', &
                 b'01010000', &
                 b'10001000']

! O sprite
word :: os(*) = [b'11111000', &
                 b'10001000', &
                 b'10001000', &
                 b'10001000', &
                 b'11111000']

! block sprite
word :: bs(*) = [b'11111100', &
                 b'11111100', &
                 b'11111100', &
                 b'11111100', &
                 b'11111100', &
                 b'11111100']

word :: i, j

! Draw the square block
call draw(48,4,bs)

do
    call jump(xs) ! X jumping around
    call jump(os) ! O jumping around
end do

contains

    ! Randomly draw a pattern, until it overlaps with the block
    subroutine jump(pattern)
        word, intent(in) :: pattern(:)
        logical :: overlaps
        word :: x, y, k
        x = 30
        y = 13
        do
            call draw(x,y,pattern,overlaps)
            call delay(put=12)  ! wait for 12/60 of a second
            do 
                call delay(get=k)
                if (k == 0) exit
            end do
            if (overlaps) then
                call draw(i,j,pattern)  ! drawing the same pattern to erase it
                return
            else
            call draw(i,j,pattern) ! drawing the same pattern to erase it
            
            ! generate new coordinates
            x = rand(mask=z'3F') ! 6-bit random number [0, 63]
            y = rand(mask=z'1F') ! 5-bit random number [0, 31]
        end do

    end subroutine

end program

Here is how the manually-assembled program looks like (running in fc8),

2 Likes

I was wondering now what might programming CHIP-8 in F77 look like, given that it was developed at roughly the same time. :see_no_evil:

It appears to be doable with a few language extensions:

C JUMPING X AND O
C
C A CHIP8 PROGRAM, ORIGINALLY BY HARRY KLEINBERG
C                                RCA CORPORATION, 1978
C
C REWRITTEN IN F77, IN 2023, BY IVAN PRIBEC
C
      PROGRAM JUMPING_X_AND_O
      INTEGER*1 XS(5),OS(5),BS(6)
C SPRITE DATA
      DATA XS,OS,BS/
     *  Z'88',Z'50',Z'20',Z'50',Z'88',
     *  Z'F8',Z'88',Z'88',Z'88',Z'F8',
     *  6*Z'FC'/
C SUBROUTINES USED
      EXTERNAL DRAW, JUMP
C START PROGRAM
      CALL DRAW(48,4,BS,6)
   10 CALL JUMP(XS,5)
      CALL JUMP(OS,5)
      GO TO 10
      END
C
C RANDOMLY DRAW A PATTERN, UNTIL IT OVERLAPS WITH THE BLOCK
C
      SUBROUTINE JUMP(PTRN,N)
      INTEGER*1 PTRN(*), N
      INTEGER*1 X, Y, K
      LOGICAL*1 OVRLPS
      INTEGER*1 IRAND
      EXTERNAL DRAW, DELAY, TIMER, IRAND
      X = 30
      Y = 13
C START JUMPING AROUND
   10 CALL DRAW(X,Y,PTRN,N,OVRLPS)
C
C COUNT DOWN DELAY TIMER
C DELAY TIMER CAN BE FOUND AT UNIT=33
C
      WRITE (33) 12
   20 READ (33) K
      IF (K > 0) GO TO 20
C IF PATTERN OVERLAPS WITH BLOCK, WE SWITCH
      IF (OVRLPS) GO TO 30
C
C ERASE PATTERN, SO WE CAN REDRAW AT NEW COORDINATES
C
      CALL DRAW(X,X,PTRN,N)
      X = IRAND(Z'3F') ! 6-BIT RANDOM NUMBER [0, 63]
      Y = IRAND(Z'1F') ! 5-BIT RANDOM NUMBER [0, 31]
      GO TO 10
C
C ERASE PATTERN AND RETURN
C
   30 CALL DRAW(X,Y,PTRN,N)
      RETURN
      END

The question now, is how to implement a Fortran compiler for the CHIP-8 virtual machine, which would emit the following hexadecimal bytecode:

a24c 6530 6604 d566 a240 2212 a246 2212
1208 611e 620d d125 630c f315 f407 3400
121c 4f01 122e d125 c13f c21f 1216 d125
00ee 0000 0000 0000 0000 0000 0000 0000
8850 2050 8800 f888 8888 f800 fcfc fcfc
fcfc 
1 Like

I think you just implement a backend. LFortran compiles Fortran code to ASR, and you write ASR->CHIP-8 backend, similar to our WASM or LLVM backends. I don’t have time to do it myself, but if you are interested, I am happy to get you started!

1 Like

But who takes care of assigning variables to registers, creating stackframes, and memory management? I’m also lacking a call convention and ABI. Are these duties of the linker?

Integer multiplication and division have to be done with shifting too, so a “math” runtime library would need to be implemented.

The backend. It will be similar to our direct ASR->x86 backend here: https://github.com/lfortran/lfortran/blob/1c90bc45995a5303e20ef903654ff71c7252bac0/src/libasr/codegen/asr_to_x86.cpp. We are keeping this backend as a prototype only, since it’s a lot of work to get a full featured backend, so we decided to reuse our WASM backend and WASM->x86 backend.

That might be an option here too, to just implement WASM->CHIP-8 backend. Then you could compile any code that compiles to WASM, which is almost all languages now.

Integer multiplication and division have to be done with shifting too, so a “math” runtime library would need to be implemented.

It’s the job of the backend to call into the proper runtime library.

There are 512 bytes, therefore 1024 keys to type without error (no Backspace on the keyboard :laughing:)… But you could do it in less than one hour…
In the book, they said that with the Altair you had to enter the Microsoft Altair Basic bit by bit with the switches on the panel (no keyboard).

That’s quite big, my first machine with more than 64K was the Sony HB-F700F (MSX2 Japanese standard) bought in 1986 (or 87?), with 256 K RAM. It replaced a MSX Sanyo PHC-28L with only 64 K.

Yes, a high level of abstraction implies a whole stack of things…

1 Like