2015 Retrochallenge Winter Warmup, Retrochallenge

Retrochallenge 2015/01 – Final Post

(This is the final part of the chronicle of my Retrochallenge 2015/01 submission, which is to port the modern-day Apple II game, Structris, to the Atari 8-bit home computer using an obscure language called PL65. The mediocrity starts here.)

Before really jumping into it. Here are links I want to share:

Success! (that’s what I’m claiming)

I couldn’t have cut it any closer to the deadline, but I declare victory over my Retrochallenge 2015/01 project. Since the previous post, I’ve been able to put finishing touches on the game. These include:

  • Level advancement
  • Throttled game loop
  • Scoring
  • Level 11 and beyond
  • Allow movement after collision
  • Loading Time screen

Level Advancement

Each level range (1..10, 11..12, …) has a target number of rows to be collapsed before advancing to the next level. The game now tracks the rows collapsed and when the goal has been reached, play temporarily ends, and the playfield is animated to first drop all the pieces to the bottom, and then collapses the remaining pile. The Tetris well is cleared and re-drawn to be smaller than before. Levels 10, 20, 30, … are the most constrained.

Unfortunately my ongoing PL65 bug occurs during the animation sequence. The bug seems to occur when I use STRING datatypes. From my vantage point the PRIOR/GPRIOR register is being trespassed for some reason and the graphics mode will shift to either 8, 9, or 11 (or if I’m lucky, the desired mode, 10, will appear). It’s beyond my skill to find a solution for this one. I’ve decided to leave the bug in as Noahsoft’s artistic contribution since it does provide a startling exit to the current level and the graphics returns to normal when the game resumes.

Throttled Game Loop

The assembly code version of the “Scroll” routine is way too fast to allow running wide open. I played the original Apple version of the game and measured (crudely) the time it takes for a game piece to fall from top to bottom for a small sampling of levels. I derived a linear equation to variably adjust the game loop to match the timing on the Apple. I wouldn’t be surprised if I’m off and the Apple II’s speed increases with each level on a curved path rather than linearly. All I can say is it’s very playable.

Scoring

Simple. You get one point per row cleared. No bonuses for collapsing multiple rows at a time. Score is displayed in the text frame.

Level 11 and Beyond

Play advances beyond level 10, to match the competition version of Structis. The well returns to its level 1 size but your blip becomes mostly invisible, appearing maybe once every 5 seconds. If you make it to level 20, it’s even more invisible. But who’d go that far?

Allow Movement After Collision

I modified the keyboard routine to allow side-to-side movement after your blip comes into contact with a descending game piece. This feature is found in the Apple version but wasn’t working on my Atari version until now. This allows for some daring escapes.

Load Time Screens

Added the equivalent of the Apple’s version of the boot screen that contains abbreviated instructions and credits. Modified the “title” screen to include my name.

What’s Different?

Here’s some differences I’ve noticed between my version and the Apple version:

  • On the Atari version you can not descend faster than a falling piece. On the Apple version you can out-race a descending piece for an especially skillful escape.
  • The pink “S” shaped piece occasionally misses its cue. You may notice a pause when this piece is supposed to appear. If you stay where you are, it will appear on its second chance.
  • Level “cut-scene” animation glitches – but now it’s a feature.

Thanks, Retrochallenge!

Ton o’ fun. But now I need to get outside.

Advertisement
2015 Retrochallenge Winter Warmup, Retrochallenge

Retrochallenge 2015/01 – Post 06

Assembly Time

(This is part six of the chronicle of my Retrochallenge 2015/01 submission, which is to port the modern-day Apple II game, Structris, to the Atari 8-bit home computer using an obscure language called PL65. The mediocrity starts here.)

I was able to convert the scroll routine that moves the Tetris pieces down the screen from straight PL65 to 6502 Assembly. Recall that one of the brilliant virtues of Noahsoft’s PL65 is its ability to treat 6502 mnemonics as first-class commands. There are limitations and PL65’s documentation warns against intermingling PL65 and 6502 statements .unless you have a fetish for devious bugs.

Though you can’t help but use INC MYVAR instead of MYVAR = MYVAR + 1.

Earlier this month, I was dismayed that PL65, by itself, couldn’t render quickly enough to match speed of the Apple version. The Apple does use a machine language routine to perform the scrolling. It was implemented using Ivan X’s Applesoft extension called Slammer, which embeds monitor or assembly instructions as REM statements. I’m still relatively new to 6502 Assembly, so I wasn’t planning on having to spend time trying to figure that one out.

Holy Crap! I May Finish This Yet.

The performance difference using the 6502 routine is astounding.

This will give me plenty of cycles to spare to help finishing up any lingering features. In fact, if I don’t run out of time, my plan is to throttle the Atari version to animate the pieces to match the speed of the Apple version. In Martin Haye’s Apple II game, as the player advances to the next level, the Tetris well reduces in size. A happy side effect is the computer has fewer pixels to move and therefore the pieces fall faster as the level increases.

But there’s still several features needed before calling this one done:

  1. The calculation of “Rows Cleared” needs to be corrected
  2. Once the goal for rows-cleared is completed, play should advance to the next round
  3. Match the game’s speed exactly to the Apple II version (may vary by level) – this should aid in the player’s blip being more visible.
  4. Add scoring
  5. General cleanup
  6. Stretch 1: Add German/Czech/Polish versions of the instructions)
  7. Stretch 2: Add other instructions to the BeweDOS batch file to better mimic the Apple II version

Code Dump

Here’s the logic for the scroll routine first in PL65 and then re-implemented as 6502 instructions:

!---------------------------------------
! SCROLL
!---------------------------------------
PROC SCROLL()
INT A1, A2
BYTE R, S, CL
BEGIN
  ! CHECK TO SEE IF BOTTOM ROW IS CLEAR
  CL = 0 R = 0 S = 0 A1 = ORIGIN P1 = ORIGIN
  WHILE V1 <> $88 DO
    IF V1 = $00 THEN 
      INC R 
    ELSE  
      INC S 
    ENDIF
    A1 = A1 + 2  P1 = A1
  ENDWHILE

  ! IF CLEARED
  IF R = 0 AND S > 0 THEN
    INC RC INC CL
  ENDIF

  R = CL
  S = HEIGHT2
  A1 = ORIGIN
  A2 = A1 - 32
  P1 = A1 P2 = A2 P3 = A1 + 1 P4 = A2 + 1
  WHILE V1 <> $88 DO
    WHILE S > 0 DO
      IF R = 0 AND V1 = $00 THEN R = 1 ENDIF
      IF R = 1 THEN 
        V1 = V2 V3 = V4
        IF S = 1 THEN V2 = $00 V4 = $00 ENDIF
      ENDIF 
      P1 = A2 P3 = A2 + 1 A2 = A2 - 32 
      P2 = A2 P4 = A2 + 1
      DEC S
    ENDWHILE
    A1 = A1 + 2 A2 = A1 - 32
    P1 = A1 P2 = A2 P3 = A1 + 1 P4 = A2 + 1
    S = 37 - LV
    R = CL
  ENDWHILE
END

CONST DUMMY4 = @
@ = $8800
!-----------------------------
! SCROLL2
!-----------------------------
PROC SCROLL2()
INT A1, A2
BYTE FILL_FL, HGT, CL
BEGIN
  ! CHECK TO SEE IF BOTTOM ROW IS CLEAR
  ! SCAN BOTTOM ROW
  !CL = 0 R = 0 S = 0
  LDA #$00
  STA CL
  STA FILL_FL
  STA HGT

  !A1 = ORIGIN
  LDA ORIGIN+1
  LDY ORIGIN
  STY A1
  STA A1+1

  !P1 = ORIGIN
  STY P1
  STA P1+1

  !WHILE V1 <> $88 DO
  LDY #$00
:wh01
  LDA (P1),Y
  CMP #$88
  BEQ endw01
  CMP #$00
  BNE inc_s
  INC FILL_FL
  GOTO endif01
:inc_s
  INC HGT
:endif01
  INY 
  INY 
  JMP wh01
:endw01

  !IF R = 0 AND S > 0 THEN
  LDA FILL_FL
  BNE endif04
  LDA HGT
  BEQ endif04
  INC RC
  JSR PRINT_ROWS_CLEARED
  INC CL
:endif04

  ! FILL_FL = CL
  LDA CL
  STA FILL_FL

  !HGT = HEIGHT2
  LDA HEIGHT2
  STA HGT

  ! A1 = ORIGIN
  LDA ORIGIN+1
  LDY ORIGIN
  STY A1
  STA A1+1

  !A2 = A1 - 32
  SEC
  LDA A1
  SBC #$20
  STA A2
  LDA A1+1
  SBC #$00
  STA A2+1

  !P1 = A1
  LDA A1+1
  LDY A1
  STA P1+1
  STY P1

  !P2 = A2
  LDA A2+1
  LDY A2
  STA P2+1
  STY P2

  !P3 = A1 + 1
  LDA A1
  LDY A1+1
  STY P3+1
  CLC
  ADC #$01
  STA P3
  BCC add02
  INC P3+1
:add02

  !P4 = A2 + 1
  LDA A2
  LDY A2+1
  STY P4+1
  CLC
  ADC #$01
  STA P4
  BCC add03
  INC P4+1
:add03

  !WHILE V1 <> $88 DO
:wh02
  LDY #$00
  LDA (P1),Y
  CMP #$88
  BNE wh03
  GOTO endw02

    !WHILE HGT > 0 DO
:wh03
  LDA HGT
  BEQ endw03

      !IF FILL_FL = 0 AND V1 = $00 THEN FILL_FL = 1 ENDIF
  LDA FILL_FL
  BNE endif02
  LDY #$00
  LDA (P1),Y
  BNE endif02
  LDA #$01
  STA FILL_FL
:endif02

      !IF FILL_FL = 1 THEN 
  LDA FILL_FL
  BEQ endif03

        !V1 = V2 V3 = V4
  LDY #$00
  LDA (P2),Y
  STA (P1),Y
  LDA (P4),Y
  STA (P3),Y

        !IF HGT = 1 THEN V2 = $00 V4 = $00 ENDIF
  LDA HGT
  CMP #$01
  BNE endif03
  LDA #$00
  STA (P2),Y
  STA (P4),Y
      !ENDIF 
:endif03

      !P1 = A2
  LDA A2+1
  LDY A2
  STA P1+1
  STY P1  

      !P3 = A2 + 1
  LDA A2
  LDY A2+1
  STY P3+1
  CLC
  ADC #$01
  STA P3
  BCC add04
  INC P3+1
:add04

      !A2 = A2 - 32 
  SEC
  LDA A2
  SBC #$20
  STA A2
  LDA A2+1
  SBC #$00
  STA A2+1

      !P2 = A2
  LDA A2+1
  LDY A2
  STA P2+1
  STY P2

      !P4 = A2 + 1
  LDA A2
  LDY A2+1
  STY P4+1
  CLC
  ADC #$01
  STA P4
  BCC add05
  INC P4+1
:add05

  DEC HGT
    !ENDWHILE
  JMP wh03
:endw03

    !A1 = A1 + 2
    CLC
    LDA A1
    ADC #$02
    STA A1
    BCC add01
    INC A1+1
:add01

!    A2 = A1 - 32
    SEC
    LDA A1
    SBC #$20
    STA A2
    LDA A1+1
    SBC #$00
    STA A2+1

    !P1 = A1
    LDA A1+1
    LDY A1
    STA P1+1
    STY P1

    !P2 = A2
    LDA A2+1
    LDY A2
    STA P2+1
    STY P2

   ! P3 = A1 + 1
    LDA A1
    LDY A1+1
    STY P3+1
    CLC
    ADC #$01
    STA P3
    BCC add06
    INC P3+1
:add06

    !P4 = A2 + 1
    LDA A2
    LDY A2+1
    STY P4+1
    CLC
    ADC #$01
    STA P4
    BCC add07
    INC P4+1
:add07

    !S = HEIGHT2
    LDA HEIGHT2
    STA HGT

    !R = CL
    LDA CL
    STA FILL_FL

    JMP wh02

  !ENDWHILE
:endw02
END
@ = DUMMY4
2015 Retrochallenge Winter Warmup, Retrochallenge

Retrochallenge 2015/01 – Post 05

Collapse

(This is part five of the chronicle of my Retrochallenge 2015/01 submission, which is to port the modern-day Apple II game, Structris, to the Atari 8-bit home computer using an obscure language called PL65. The mediocrity starts here.)

Only a minor difference in this version versus the previous. Now for each completed row, the pile of pieces will collapse. I was surprised that it didn’t take much additional code in the scroll routine to implement. The algorithm scans the pixels along the bottom of the well. If no $00 (background) pixels are found then the scroll routine performs the “copy pixel from above” from the bottom of the pile (and up) instead of the top of the pile (and up).

Common sense should have me working some easy wins to see this game nearly functionally equivalent to its Apple II hero. This would be keeping track of the rows completed and advancing to the next level. Instead I’m consumed with trying to convert the scroll routine from PL65 to 6502 assembly, for which I have no skill. But then again, common sense should have me working on something entirely different.

Up Next

Despair

2015 Retrochallenge Winter Warmup, Retrochallenge

Retrochallenge 2015/01 – Post 04

Pieces Finally Coming Together

(This is part four of the chronicle of my Retrochallenge 2015/01 submission, which is to port the modern-day Apple II game, Structris, to the Atari 8-bit home computer using an obscure language called PL65. The mediocrity starts here.)

This week I added a lot of code that couldn’t easily be tested individually. It’s the code that derives which Tetris piece will be generated based on the profile underneath the player’s current position. For a long while, just part of a single Tetris piece would appear at the top of the playfield and smear down the screen.

A late Friday/early Saturday debugging session delivered magical results. One correction to a variable assignment made things go from “nothing works” to “everything works” (well, everything I’ve put in up to now).

From watching the video, several annoyances are immediately apparent:

  • The scroll routine is still unoptimized and the pieces shear as the pixels are moved down the screen
  • The player’s blip is barely visible. The scroll routine is taking too long and the other routines seem to be running very quickly. I’m following Martin’s original algorithm which has the player’s blip invisible during the scroll routine and visible during the “derive next piece” routines.

Mind If I Crash Here

Earlier in the week, it was looking very dark when my project was causing the Atari to immediately crash. I started commenting out blocks of code in an attempt to narrow down the culprit. Nothing I changed in the code would alleviate the error. At one point my wife was reminding me that I didn’t *have* to finish the project. And I was beginning to listen.

The whole time I was assuming something was wrong in my code, but it turned out something on the floppy disk image or with BeweDOS had gotten corrupted. I’m sure I’m to blame. I’d gotten into the habit of rebooting the emulator whenever I saw a compilation error appear. I realize now, this is probably a bad thing to do when the Atari is writing to the disk.

Code Dump

Here’s the current state of my source code. With the intent of keeping the feel of the original Apple II game and (selfishly) to help finish this in a short timeframe, many of the critical algorithms were lifted straight from Martin Haye’s Applesoft BASIC source code.

INCLUDE D:GRAPHICS.LIB
INCLUDE D:PEEKPOKE.LIB

! MEMORY MAP
BYTE DL[490]          = $8DA0
BYTE FRAME_TEXT[120]  = $9F86
BYTE FRAME_GR[5120]   = $A000

! GLOBALS
INT SCORE, LV, OX
INT ORIGIN
BYTE WELL, FLOOR
BYTE W, HEIGHT, MH, CX, CY, M, X, Y
BYTE H0, HL, HR, HB
BYTE RG, RC, RD
BYTE CI, BL, B0, BR, SL, SX, SR
BYTE H[22]

POINTER P1, P2, P3, P4
BYTE V1 BASED P1
BYTE V2 BASED P2
BYTE V3 BASED P3
BYTE V4 BASED P4
BYTE KEYCH  = $02FC

! SYMBOLS
CONST GRWIDTH = $20

CONST LMARGN = $52
CONST ROWCRS = $54
CONST COLCRS = $55
CONST SAVMSC = $58
CONST CRSINH = $02F0
CONST SDMCTL = $022F
CONST SDLIST = $0230
CONST GPRIOR = $026F
CONST PCOLR0 = $02C0
CONST PCOLR1 = $02C1
CONST PCOLR2 = $02C2
CONST PCOLR3 = $02C3
CONST COLOR0 = $02C4
CONST COLOR1 = $02C5
CONST COLOR2 = $02C6
CONST COLOR3 = $02C7
CONST COLOR4 = $02C8
!CONST KEYCH  = $02FC

! HARDWARE REGISTERS
CONST COLPM0 = $D012
CONST COLPM1 = $D013
CONST COLPM2 = $D014
CONST COLPM3 = $D015
CONST COLPF0 = $D016
CONST COLPF1 = $D017
CONST COLPF2 = $D018
CONST COLPF3 = $D019
CONST COLBK  = $D01A
CONST PRIOR  = $D01B
CONST WSYNC  = $D40A

! COLORS
CONST BLACK  = $00
CONST GRAY   = $08
CONST WHITE  = $0F
CONST YELLOW = $2C
CONST ORANGE = $36
CONST PURPLE = $54
CONST PINK   = $5C
CONST DKBLUE = $64
CONST LTBLUE = $8C
CONST BLUE   = $84
CONST GREEN  = $C6

!---------------------------------------
! DISPLAY LIST INTERRUPTS
!---------------------------------------
CONST DUMMY=@
@=$8B00
INTERRUPT DLINT1()
INT VDSLST = $0200
BEGIN
  STA WSYNC
  LDA $84     STA PRIOR
  LDA #ORANGE STA COLPF1
  LDA #YELLOW STA COLPF2
  LDA #GRAY   STA COLBK
  VDSLST = $8C00
END

@=$8C00
INTERRUPT DLINT2()
INT VDSLST = $0200
BEGIN
  STA WSYNC
  LDA #$00   STA PRIOR
  LDA #WHITE STA COLPF1
  LDA #BLACK STA COLPF2 STA COLBK
  VDSLST = $8B00
END
@=DUMMY

!---------------------------------------
! DISPLAY INTERRUPT ENABLE
!---------------------------------------
PROC DLI_ENABLE()
INT  VDSLST = $0200
BYTE NMIEN  = $D40E
BEGIN
  VDSLST = $8B00
  NMIEN  = $C0
END

!---------------------------------------
! DISPLAY INTERRUPT DISABLE
!---------------------------------------
PROC DLI_DISABLE()
BYTE NMIEN  = $D40E
BEGIN
  NMIEN  = $00
END

!---------------------------------------
! RND returns a random 16 bit number
!---------------------------------------
FUNC RND*()
BYTE RANDOM=$D20A
BEGIN
  LDA RANDOM
  LDY RANDOM
  JSR PUSH
END

!---------------------------------------
! RAND returns a random number
!      in the range 0 to range-1
!---------------------------------------
FUNC RAND(BYTE range)
BEGIN
END RND()/(65535/range)

!---------------------------------------
! SET COLORS
!---------------------------------------
PROC SET_COLORS()
BEGIN
  POKE(PCOLR0, BLACK)
  POKE(PCOLR1, PURPLE)
  POKE(PCOLR2, BLUE)
  POKE(PCOLR3, DKBLUE)
  POKE(COLOR0, PINK)
  POKE(COLOR1, ORANGE)
  POKE(COLOR2, YELLOW)
  POKE(COLOR3, GREEN)
  POKE(COLOR4, GRAY)
END

!---------------------------------------
! SET DISPLAY LIST
!---------------------------------------
PROC SET_DL()
INT  I, J, K, GR_ADR
BEGIN
  POKE(SDMCTL,$00)
  DLI_DISABLE()
  GR_ADR = .FRAME_GR

  ! 2x 8 BLANK SCANLINES 
  ! 1x 8 BLANK SCANLINES & DLI
  DL[0] = $70
  DL[1] = $70
  DL[2] = $F0

  ! 160 LINES OF MODE 10
  ! EACH SET OF 4 SCANLINES 
  ! POINT TO SAME MEMORY RANGE
  K = 3
  FOR I = 0 TO 39 DO
    FOR J = 0 TO 3 DO
      DL[K] = $4F
      DOKE(.DL+K+1, GR_ADR)
      K = K + 3
    NEXT
    GR_ADR  = GR_ADR + $20
  NEXT 

  ! OVERWRITE LAST MODE F ADD DLI
  ! TO ENABLE NORMAL TEXT AT BOTTOM
  DL[K-3] = $CF

  ! TEXT FRAME
  DL[K+0] = $42
  DOKE(.DL+K+1, .FRAME_TEXT)
  DL[K+3] = $02
  DL[K+4] = $02
  DL[K+5] = $02

  ! JVB
  DL[K+6] = $41
  DOKE(.DL+K+7, .DL)

  ! INSTALL NEW DISPLAY LIST
  ! 1. TURN OFF ANTIC
  ! 2. POINT TO NEW DISPLAY_LIST
  ! 3. TURN ON ANTIC
  POKE(SDMCTL,$00)
  DOKE(SDLIST,.DL)
  POKE(SDMCTL,$21)

  ! ENABLE GTIA MODE 10
  POKE(GPRIOR,$84)
  POKE(PRIOR,$84)

  DLI_ENABLE()
END

!---------------------------------------
! GET KEY
!---------------------------------------
FUNC GET_KEY()
BYTE KEY
BEGIN
  CLOSE(1)
  OPEN(1,4,0,"K:")
  KEY = GET(1)
  CLOSE(1)
END KEY

!---------------------------------------
! MYSTR
!---------------------------------------
FUNC MYSTR$(INT NUM)
STRING SBUFF$[16]
BYTE A,B
BYTE BASE
BEGIN
  BASE = 10
  SBUFF$[15] = "0"; A = 16
  REPEAT
    DEC A
    B = NUM MOD BASE + 48
    IF B >= 58 THEN
      B = B + 7
    ENDIF
    NUM = NUM/BASE
    P1 = .SBUFF+A
    V1 = B
  UNTIL NUM = 0
END SBUFF$[A]

!---------------------------------------
! SET LEVEL
!---------------------------------------
PROC SET_LEVEL(INT L)
BEGIN
  LV = L
  WELL = LV MOD 10
  IF WELL = 0 THEN  WELL = 10 ENDIF
  FLOOR = 39 - 2 * WELL
END

!---------------------------------------
! HOME
!---------------------------------------
PROC HOME()
BEGIN
  WRTLN(CHR$(125))
END

!---------------------------------------
! HELP SCREEN
!---------------------------------------
PROC HELP_SCREEN()
BYTE KEY
BEGIN
  SETCOLOR(2,0,0)
  POKE(CRSINH,$FF)
  POKE(LMARGN,0) CR()
  HOME()
  WRTLN("WELCOME TO STRUCTRIS!")
  WRTLN("BY MARTIN HAYE, INTRO'D KFEST 2010")
  CR() CR()
  WRTLN("(FANCY OPENING SCREEN GOES HERE)")
  CR() CR()
  WRTLN("KEYS:")
  WRTLN("  I: UP")
  WRTLN("  J: LEFT")
  WRTLN("  K: RIGHT (ALTERNATE: L)")
  WRTLN("  M: DOWN") CR()
  WRTLN("BUILD UP THE TETRIS BLOCKS. YOU CANNOT")
  WRTLN("ROTATE THEM. EVIL PROGRAMMER LAUNCHES")
  WRTLN("BLOCKS WHERE YOU ARE TO TRAP YOU. DON'T")
  WRTLN("GET TRAPPED. FINISHED ROWS FALL AWAY.")
  CR()
  WRTLN("CLEAR ENOUGH ROWS: NEXT LEVEL! HARDER!")
  CR()
  WRTLN("HIT A KEY TO BEGIN THE TORTURE.")
  KEY = GET_KEY()
  POKE(CRSINH,0)
END

!---------------------------------------
! INIT
!---------------------------------------
PROC INIT()
INT I
BEGIN
  SET_LEVEL(1)
  DLI_ENABLE()
  SET_COLORS()
  SET_DL()
END

!---------------------------------------
! CLEAR WELL
!---------------------------------------
PROC CLEAR_WELL()
INT I, J
BEGIN
  P1 = .FRAME_GR
  FOR I = 0 TO 31 DO
    FOR J = 0 TO FLOOR DO
      V1 = $00
      P1 = P1 + 1
    NEXT
  NEXT
END

!---------------------------------------
! LPLOT
!---------------------------------------
PROC LPLOT (BYTE X, Y, C)
BEGIN
  P1 = .FRAME_GR + $20 * Y + X
  V1 = C
END

!---------------------------------------
! SCRN
!---------------------------------------
FUNC SCRN (BYTE X, Y)
BEGIN
  P1 = .FRAME_GR + $20 * Y + X
END V1

!---------------------------------------
! HLIN - PLOT HORIZ LINE AT Y=0
!---------------------------------------
PROC HLIN (BYTE X1, X2, C)
BEGIN
  WHILE X1 <= X2 DO
    LPLOT(X1,1,C)
    INC X1
  ENDWHILE 
END

!---------------------------------------
! LPRINT
!---------------------------------------
PROC LPRINT(BYTE X, Y INT ADDR BYTE LEN)
BEGIN
  P1 = .FRAME_TEXT + $20 * Y + X
  P2 = ADDR
  WHILE LEN > 0 DO
    V1 = V2 - $20
    P1 = P1 + 1
    P2 = P2 + 1
    DEC LEN
  ENDWHILE
END

!---------------------------------------
! PRINT LEVEL
!---------------------------------------
PROC PRINT_LEVEL()
BYTE D, L
BEGIN
  LPRINT(12,0,"LEVEL:     ")

  L = 1
  IF LV >= 10 THEN L = 2 ENDIF
  IF LV >= 99 THEN L = 3 ENDIF

  D = LV MOD 10 + $10
  POKE(.FRAME_TEXT + 17 + L, D)

  IF LV >= 10 THEN
    D = LV /  10 + $10  
    POKE(.FRAME_TEXT + 17 + L - 1, D)
  ENDIF

  IF LV >= 100 THEN
    D = (LV MOD 100) / 10 + $10
    POKE(.FRAME_TEXT + 17 + L - 1, D)

    D = LV / 100 + $10
    POKE(.FRAME_TEXT + 17 + L - 2, D)
  ENDIF
END

!---------------------------------------
! DRAW WELL
!---------------------------------------
PROC DRAW_WELL()
BYTE X1, X2, Y1, Y2
INT I
BEGIN
  X1 = WELL
  X2 = 31 - WELL
  Y1 = 41 - 2 * WELL - 1
  Y2 = Y1 + 1

  CLEAR_WELL()

  ! DRAW WALLS
  FOR I = 0 TO Y2 + 1 DO
    LPLOT(X1, I, $88)
    LPLOT(X2, I, $88)
  NEXT

  ! DRAW BLACK LINES OVER PREV WALLS
  FOR I = 0 TO Y2 DO
    LPLOT(X1-1, I, $00)
    LPLOT(X2+1, I, $00)
  NEXT

  ! DRAW CHECKBOARD1
  FOR I = X1 + 1 TO X2 - 1 STEP 2 DO
    LPLOT(I, Y1, $88)
    LPLOT(I, Y2, $22)
  NEXT

  ! DRAW CHECKBOARD1
  FOR I = X1 + 2 TO X2 - 1 STEP 2 DO
    LPLOT(I, Y1, $22)
    LPLOT(I, Y2, $88)
  NEXT

  PRINT_LEVEL()
END

!---------------------------------------
! PRINT NUM CLEARED
!---------------------------------------
PROC PRINT_NUM_CLEARED()
BEGIN
  LPRINT (11, 2, "CLEARED ")
END

!---------------------------------------
! LEVEL INIT
!---------------------------------------
PROC LEVEL_INIT()
INT I
BEGIN
  ORIGIN = .FRAME_GR + 1249 - 63 * WELL
  W = 15 - LV
  HEIGHT = 20 - LV
  MH = HEIGHT - 1
  OX = (32 - W * 2) / 2
  M = 0; HB = 0
  H[0] = -9 H[W + 1] = -9
  FOR I = 1 TO W DO H[I] = 0 NEXT
  X = -99
  CX = OX + W; CY = 37 - LV + 1
  RG = 5 + LV * 2; RD = 0; RC = 0 
  DRAW_WELL()
  PRINT_NUM_CLEARED()
END

!---------------------------------------
! SCROLL
!---------------------------------------
PROC SCROLL()
INT A1, A2
BYTE H, F
BEGIN
  F = 0; H = 37 - LV
  A1 = ORIGIN
  A2 = A1 - 32
  P1 = A1; P2 = A2; P3 = A1 + 1; P4 = A2 + 1
  WHILE V1 <> $88 DO
    WHILE H > 0 DO
      IF F = 0 AND V1 = $00 THEN F = 1 ENDIF
      IF F = 1 THEN 
        V1 = V2 V3 = V4
        IF H = 1 THEN V2 = $00 V4 = $00 ENDIF
      ENDIF 
      P1 = A2 P3 = A2 + 1 A2 = A2 - 32 
      P2 = A2 P4 = A2 + 1
      DEC H
    ENDWHILE
    A1 = A1 + 2 A2 = A1 - 32
    P1 = A1 P2 = A2 P3 = A1 + 1 P4 = A2 + 1
    F = 0; H = 37 - LV
  ENDWHILE
END

!---------------------------------------
! KB PROC
!---------------------------------------
FUNC KB_PROC()
BYTE RC
BEGIN
  RC = 1
  LPLOT(CX,CY,$00)
  SCROLL()
  IF SCRN(CX,CY) = $00 THEN 
    CASE KEYCH
      OF $0D DO IF SCRN(CX, CY-1) = $00 AND CY > 1 THEN DEC CY ENDIF ENDOF
      OF $01 DO IF SCRN(CX-1, CY) = $00            THEN DEC CX ENDIF ENDOF
      OF $05 DO IF SCRN(CX, CY+1) = $00            THEN INC CY ENDIF ENDOF
      OF $44 DO IF SCRN(CX, CY+1) = $00            THEN INC CY ENDIF ENDOF
      OF $00 DO IF SCRN(CX+1, CY) = $00            THEN INC CX ENDIF ENDOF
    ENDCASE
    KEYCH = $FF
  ELSE
    IF SCRN(CX,CY+1) <> $00 THEN 
      RC = 0
    ENDIF 
    INC CY
  ENDIF
  LPLOT(CX,CY,$66)
END RC

!---------------------------------------
! PICK_X_COORD
!---------------------------------------
PROC PICK_X_COORD()
BYTE I
BEGIN
  IF X > 128 THEN X = (CX - OX) / 2 + 1 ENDIF
  IF X > 128 OR X < 1 THEN X = -9 RETURN ENDIF
  IF X > W THEN X = -9 RETURN ENDIF
  IF X > 1 AND H[X-1] < H[X] THEN DEC X
  ELSE
    IF X < W AND H[X+1] < H[X] THEN INC X ENDIF
  ENDIF
  IF H[X] - HB < MH THEN INC M ENDIF
END

!---------------------------------------
! CALC_SHAPE_CONSTRAINTS
!---------------------------------------
PROC CALC_SHAPE_CONSTRAINTS()
BEGIN
  H0 = H[X]
  HL = H[X-1] - H0
  HR = H[X+1] - H0
  IF HR > 3   THEN HR = 3 ENDIF
  IF HL > 3   THEN HL = 3 ENDIF
  INC M
END

!---------------------------------------
! APPLY CHOSEN COORD
!---------------------------------------
PROC APPLY_CHOSEN_COORD()
BEGIN
  H[X-1] = H[X-1] + BL
  H[X]   = H[X]   + B0
  H[X+1] = H[X+1] + BR
  SX = (X - 1) * 2 + OX
  IF BL = 0 THEN SL = 0 GOTO L745 ENDIF
  BL = BL * 3; SL = HL * 3
:L745
  IF BR = 0 THEN GOTO L755 ENDIF
  BR = BR * 3; SR = HR * 3
:L755
  B0 = B0 * 3 
  INC M
END

!---------------------------------------
! CHOOSE_SHAPE
!---------------------------------------
PROC CHOOSE_SHAPE()
BYTE I
BEGIN
  INC M
  I =  HL * 4 + HR
  CASE I
    OF 0 DO 
      CASE RAND(4) 
        OF 0 DO CI = $11 BL = 1 B0 = 1 BR = 2 ENDOF
        OF 1 DO CI = $22 BL = 2 B0 = 1 BR = 1 ENDOF
        OF 2 DO CI = $66 BL = 1 B0 = 2 BR = 1 ENDOF
        OF 3 DO CI = $77 BL = 1 B0 = 1 BR = 1 ENDOF
      ENDCASE
    ENDOF
    OF 1 DO     CI = $44 BL = 1 B0 = 2 BR = 1 ENDOF
    OF 2 DO     CI = $22 BL = 0 B0 = 3 BR = 1 ENDOF
    OF 3 DO
      CASE RAND(3)
        OF 0 DO CI = $11 BL = 3 B0 = 1 BR = 0 ENDOF
        OF 1 DO CI = $22 BL = 1 B0 = 3 BR = 0 ENDOF
        OF 2 DO CI = $33 BL = 2 B0 = 2 BR = 0 ENDOF
      ENDCASE
    ENDOF
    OF 4 DO     CI = $55 BL = 1 B0 = 2 BR = 1 ENDOF
    OF 5 DO     CI = $66 BL = 1 B0 = 2 BR = 1 ENDOF
    OF 6 DO
      CASE RAND(2)
        OF 0 DO CI = $44 BL = 2 B0 = 2 BR = 0 ENDOF
        OF 0 DO CI = $66 BL = 1 B0 = 3 BR = 0 ENDOF
      ENDCASE
    ENDOF
    OF 7 DO
      CASE RAND(2)
        OF 0 DO CI = $44 BL = 2 B0 = 2 BR = 0 ENDOF
        OF 0 DO CI = $66 BL = 1 B0 = 3 BR = 0 ENDOF
      ENDCASE
    ENDOF
    OF 8 DO     CI = $11 BL = 1 B0 = 3 BR = 0 ENDOF
    OF 9 DO     CI = $11 BL = 1 B0 = 3 BR = 0 ENDOF
    OF 10 DO
      CASE RAND(2)
        OF 0 DO CI = $11 BL = 1 B0 = 3 BR = 0 ENDOF
        OF 1 DO CI = $22 BL = 0 B0 = 3 BR = 1 ENDOF
      ENDCASE
    ENDOF
    OF 11 DO    CI = $11 BL = 1 B0 = 3 BR = 0 ENDOF
    OF 12 DO
      CASE RAND(3)
        OF 0 DO CI = $11 BL = 0 B0 = 3 BR = 1 ENDOF
        OF 1 DO CI = $22 BL = 0 B0 = 1 BR = 3 ENDOF 
        OF 2 DO CI = $33 BL = 0 B0 = 2 BR = 2 ENDOF
      ENDCASE
    ENDOF
    OF 13 DO
      CASE RAND(2)
        OF 0 DO CI = $55 BL = 0 B0 = 2 BR = 2 ENDOF
        OF 1 DO CI = $66 BL = 0 B0 = 3 BR = 1 ENDOF
      ENDCASE
    ENDOF
    OF 14 DO    CI = $22 BL = 0 B0 = 3 BR = 1 ENDOF
    OF 15 DO    CI = $77 BL = 0 B0 = 3 BR = 0 ENDOF
  ENDCASE
END

!---------------------------------------
! PLOT_A_LINE
!---------------------------------------
PROC PLOT_A_LINE()
BEGIN
  IF BL = 0 THEN GOTO L835 ENDIF
  IF SL > 0 AND SL < 128 THEN 
      DEC SL
      GOTO L835
  ENDIF
  DEC BL
  HLIN(SX-2,SX-1,CI)
  IF SL <> 0 THEN LPRINT (0,0,"WHOA!") ENDIF
:L835
  IF B0 = 0 THEN GOTO L850 ENDIF
  DEC B0
  HLIN(SX,SX+1,CI)
:L850
  IF BR = 0 THEN GOTO L870 ENDIF
  IF SR > 0 AND SR < 128 THEN
    DEC SR
    GOTO L870
  ENDIF
  DEC BR
  HLIN(SX+2,SX+3,CI)
:L870
  IF BL + B0 + BR = 0 THEN
    X = -99
    M = 0
  ENDIF
END

!---------------------------------------
! MYDEBUG
!---------------------------------------
PROC MYDEBUG()
BEGIN
  LPRINT(0,0,"CX:  ") LPRINT(3,0,MYSTR$(CX))
  LPRINT(0,1,"CY:  ") LPRINT(3,1,MYSTR$(CY))
  LPRINT(0,2,"OX:  ") LPRINT(3,2,MYSTR$(OX))
  LPRINT(0,3,"W:   ") LPRINT(3,3,MYSTR$(W))

  LPRINT(6,0,"X:  ") LPRINT(9,0,MYSTR$(X))
  LPRINT(6,1,"HL: ") LPRINT(9,1,MYSTR$(HL))
  LPRINT(6,2,"H0: ") LPRINT(9,2,MYSTR$(H0))
  LPRINT(6,3,"HR: ") LPRINT(9,3,MYSTR$(HR))

  LPRINT(12,0,"M:  ") LPRINT(15,0,MYSTR$(M))
  LPRINT(12,1,"BL:  ") LPRINT(15,1,MYSTR$(BL))
  LPRINT(12,2,"B0:  ") LPRINT(15,2,MYSTR$(B0))
  LPRINT(12,3,"BR:  ") LPRINT(15,3,MYSTR$(BR))

  LPRINT(17,0,"SL:  ") LPRINT(20,0,MYSTR$(SL))
  LPRINT(17,1,"SR:  ") LPRINT(20,1,MYSTR$(SR))
  LPRINT(17,2,"SX:  ") LPRINT(20,2,MYSTR$(SX))
END

!---------------------------------------
! GOTCHA
!---------------------------------------
FUNC GOTCHA()
BYTE KEY
BYTE R,N,Q
BEGIN
  KEY = 0
  KEYCH = $FF
  R = ASC("R")
  N = ASC("N")
  Q = ASC("Q")
  LPRINT(9,0,"    OOPS!     ")
  LPRINT(0,2,"R)ESTART, N)EW, OR Q)UIT?") 
  OPEN(1,4,0,"K:")
  WHILE KEY <> R AND KEY <> N AND KEY <> Q DO
    KEY = GET(1)
    LPRINT(26,2,.KEY,1)
  ENDWHILE
  CLOSE(1)
END KEY

!---------------------------------------
! BYE_NOW
!---------------------------------------
PROC BYE_NOW()
INT I
BEGIN
  I = 3000 
  WHILE I > 0 DO
    I = I - 1
  ENDWHILE
  GRAPHICS(0) HOME() WRTLN("BYE NOW.")
END

!---------------------------------------
! MAIN
!---------------------------------------
MAIN()
BYTE LOOP
BEGIN
  HELP_SCREEN() HOME()
:_init
  INIT() 
:_level_init
  LEVEL_INIT()
  LOOP = 1
  WHILE LOOP = 1 DO
    CASE M
      OF 0 DO PICK_X_COORD()            ENDOF
      OF 1 DO CALC_SHAPE_CONSTRAINTS()  ENDOF
      OF 2 DO CHOOSE_SHAPE()            ENDOF
      OF 3 DO APPLY_CHOSEN_COORD()      ENDOF
      OF 4 DO PLOT_A_LINE()             ENDOF
    ENDCASE
    LOOP = KB_PROC()
  ENDWHILE
  LOOP = GOTCHA()
  CASE LOOP
    OF ASC("R") DO GOTO _level_init ENDOF
    OF ASC("N") DO GOTO _init       ENDOF
    OF ASC("Q") DO BYE_NOW()        ENDOF
  ENDCASE
END

Up Next (Yikes! Less than a week left)

  1. Add row clearing
  2. Implement level advancement
  3. Re-write scrolling subroutine in 6502
2015 Retrochallenge Winter Warmup, Retrochallenge

Retrochallenge 2015/01 – Post 03

Status Update

(This is part three of the chronicle of my Retrochallenge 2015/01 submission, which is to port the modern-day Apple II game, Structris, to the Atari 8-bit home computer using an obscure language called PL65. The mediocrity starts here.)

Nice weather persuaded me to go for a mountain bike ride rather than code so I didn’t make much progress this weekend. But a few nights ago, I was able to get a scrolling routine working. It is currently written in straight PL65 and isn’t animating as quickly as I would’ve hoped. I plan to ignore this problem for now. I’d rather have something that resembles the original Apple II version of Structris at the end of the month even if that means it’s running poorly.

!---------------------------------------
! SCROLL
!---------------------------------------
PROC SCROLL()
INT A1, A2
POINTER P1, P2
BYTE V1 BASED P1
BYTE V2 BASED P2
BYTE H, FILL
BEGIN
  FILL = 0 H = HEIGHT
  A1 = BL ! Address of bottom left of the Tetris well
  A2 = A1 - 32
  P1 = A1 P2 = A2 
  ! loop until we hit the gray wall on the right
  WHILE V1 <> $88 DO
    ! loop until we hit the top of the screen
    WHILE H > 0 DO
      IF FILL = 0 AND V1 = $00 THEN FILL = 1 ENDIF
      IF FILL = 1 THEN 
        V1 = V2  ! Copy pixel from above
      ENDIF 
      P1 = A2       ! Point to prev pixel
      A2 = A2 - 32  ! Address of next pixel (the one above)
      P2 = A2       ! Point to the next pixel 
      DEC H         ! Decrement 
    ENDWHILE
    A1 = A1 + 2 A2 = A1 - 32
    P1 = A1 P2 = A2  
    FILL = 0 H = HEIGHT
  ENDWHILE
END

 Slightly De-Mystifying the Ill-Behaved STR$()

In my last post, I expressed disbelief that calling the STR$() function to convert integers to strings could cause my custom graphics mode to freak out. After a little bit of RTFM, I see now that PL65’s pointer data type relies on zero page memory locations.

pl65_pointers_noteSo it does make more sense that the function has the possibility of interfering with system-related zero-page shadow registers. I’ll need to look at that compiler option to see if anything is suspicious. And if I’m willing to really get to the bottom of it, I can force the function to compile to a specific memory location and attempt tracing through the generated code. For now I have a work-around in place.

Here is the definition of Noahsoft’s STR$() function.

POINTER strptr
BYTE strval BASED strptr
BYTE BASE DATA 10; 

FUNC STR$(INT NUM)
STRING SBUFF$[16]
BYTE A,B 
BEGIN
  SBUFF$[15]="0";A=16
  REPEAT
    DEC A
    B=NUM MOD BASE+48
    IF B>=58 THEN
      B=B+7
    ENDIF
    NUM=NUM/BASE
    strptr=.SBUFF+A
    strval=B
 UNTIL NUM=0
END SBUFF$[A]

Apple LoRes Graphics on the Atari

The original version of Structris on the Apple II uses the LoRes graphics mode. This is a very blocky but also very colorful 40×80 mode that uses very little RAM (1 nybble per pixel). This means that each Tetris shape can have its own color and the player and walls can have distinct colors, too. Because not much RAM is required, this means that moving shapes around doesn’t take as many cycles as a higher resolution graphics mode.

Mode Pixel Width Pixel Hgt Bytes per Line Screen Resolution Total RAM
Apple LoRes 4 color clocks 4 scan lines 40 bytes 40×80 800

On the Atari computer, only with the GTIA chip, which replaced the CTIA chip found on the earliest model 400s and 800s, does the Atari begin to approach the level of freedom for number of colors found in Apple’s LoRes mode. Atari’s graphics modes 9, 10, and 11 allow going beyond the 4 or 5 color modes possible with the CTIA, but each with its own tradeoffs.

I decided to go with mode 10 (ANTIC mode F), which allows me to pick any 8 color/luminance combinations along with the background which will be black. Unfortunately this still isn’t quite enough to faithfully reproduce Structris. I have enough colors for the Tetris pieces and walls but not enough for a blinking white pixel for the player.

The bad news is, out of the box, Atari mode 10 requires 8K of RAM. This would make moving pixels around very expensive. My solution was to take advantage of Atari’s ability to create custom graphics modes using the display list.

To save processor and RAM resources, my display list is set up to point to the same memory location for each set of 4 scan lines. This brings down the RAM required from 8K to 2K. But I noticed that the original Apple II Structris never exceeds using 32 of the 40 available pixels on any line. This allowed me to set the presumably rarely used Narrow Playfield bit in the DMACTL register. So instead of 80 bytes per line, it will be 64 bytes per line. This means the ANTIC chip requires less time to scan memory and gives that time back to the 6502.

More cycles means I can be a lazier programmer.

Mode Pixel Width Pixel Hgt Bytes per Line Screen Resolution Total Bytes
Standard Mode 10 2 Color Clocks 1 scan line 40 bytes 80×192 7680
My Custom Mode 10 2 Color Clocks 4 scan line 32 bytes 64×40 1280

Here is my display list at the moment. Note that each set of 4 scan lines point to the same memory location and each row requires 32 bytes ($20). (Output generated from the sweet “atari800” emulator’s debug console).

> dlist
8DA0: 2x 8 BLANK
8DA2: DLI 8 BLANK
8DA3: 4x LMS A000 MODE F
8DAF: 4x LMS A020 MODE F
8DBB: 4x LMS A040 MODE F
8DC7: 4x LMS A060 MODE F
8DD3: 4x LMS A080 MODE F
8DDF: 4x LMS A0A0 MODE F
8DEB: 4x LMS A0C0 MODE F
8DF7: 4x LMS A0E0 MODE F
8E03: 4x LMS A100 MODE F
8E0F: 4x LMS A120 MODE F
8E1B: 4x LMS A140 MODE F
8E27: 4x LMS A160 MODE F
8E33: 4x LMS A180 MODE F
8E3F: 4x LMS A1A0 MODE F
8E4B: 4x LMS A1C0 MODE F
8E57: 4x LMS A1E0 MODE F
8E63: 4x LMS A200 MODE F
8E6F: 4x LMS A220 MODE F
8E7B: 4x LMS A240 MODE F
8E87: 4x LMS A260 MODE F
8E93: 4x LMS A280 MODE F
8E9F: 4x LMS A2A0 MODE F
8EAB: 4x LMS A2C0 MODE F
8EB7: 4x LMS A2E0 MODE F
8EC3: 4x LMS A300 MODE F
8ECF: 4x LMS A320 MODE F
8EDB: 4x LMS A340 MODE F
8EE7: 4x LMS A360 MODE F
8EF3: 4x LMS A380 MODE F
8EFF: 4x LMS A3A0 MODE F
8F0B: 4x LMS A3C0 MODE F
8F17: 4x LMS A3E0 MODE F
8F23: 4x LMS A400 MODE F
8F2F: 4x LMS A420 MODE F
8F3B: 4x LMS A440 MODE F
8F47: 4x LMS A460 MODE F
8F53: 4x LMS A480 MODE F
8F5F: 4x LMS A4A0 MODE F
8F6B: 4x LMS A4C0 MODE F
8F77: 3x LMS A4E0 MODE F
8F80: DLI LMS A4E0 MODE F
8F83: LMS 9F86 MODE 2
8F86: 3x MODE 2
8F89: JVB 8DA0

Finally, a custom LPLOT function maps screen into a 32×40 matrix so that two adjacent pixels are assigned the same color. This is effectively the 4 color color x 4 scan line pixel found on the Apple II LoRes mode.

!---------------------------------------
! LPLOT
!---------------------------------------
PROC LPLOT (BYTE X, Y, C)
POINTER P1
BYTE V1 BASED P1
BEGIN
  P1 = .FRAME_GR + $20 * Y + X 
  V1 = C 
END
...

! DRAW WALLS
FOR I = 0 TO Y2 + 1 DO
  LPLOT(X1, I, $88)
  LPLOT(X2, I, $88)
NEXT

In the code snippet here, the instruction LPLOT(X1, I, $88) sets 4 color clocks  to whatever color/luminance is defined in color register 8.

Up Next…

Dunno. Hopefully some progress.

2015 Retrochallenge Winter Warmup, Retrochallenge

Retrochallenge 2015/01 – Post 02

(This is part two of the chronicle of my Retrochallenge 2015/01 submission, which is to port the modern-day Apple II game, Structris, to the Atari 8-bit home computer using an obscure language called PL65. The mediocrity starts here.)

Arrrrrrgggghhh!

This week I’ve been wading into the cold water of PL65 programming for the Atari 8-bit. There are moments when I’m lulled into thinking I’m really using a modern language to cross-develop for the Atari. And then there are moments when I want to throw my laptop through the wall. I’ve lost a lot of time fighting what I perceive as bugs in PL65. Though I wouldn’t be surprised to find one day that the bugs were in my code and not in PL65.

I’ve been having fun, but I’m a little disappointed that my efforts don’t correspond to progress. Granted, I have been able to explore a lot of  territory new to me, like creating a custom display list (graphics mode) and implementing display list interrupts (to change graphics mode and color registers on-the-fly as the electron gun is traveling down the screen), but for sure I thought I’d to this point after the first weekend.

The only time computers irritate me is when they don’t appear to be acting logical.

A couple of examples:

  • Calling the string function STR$(val) to convert a numeric value to a string is inexplicably affecting my custom display mode, switching from GTIA mode 10 (9 Hues/9 Intensities) to GTIA mode 11 (16 Hues/1 Intensity). I was able to prove that by itself, the inclusion of the most trivial call to STR$() would cause my program to go awry. The PL65 source code for the STR$() function is on public display in the STRING.LIB library.
  • My original idea was to implement 3 display list interrupts:
  1. At the top of the screen to set the PRIOR register to render GTIA mode 10
  2. At the start of the base of the Tetris well to alter the color registers used in the tiles.
  3. At the bottom of the Tetris well base to turn off the GTIA settings so the 4-line text window displays properly.

With 3 display list interrupts (DLIs), the graphics mode became unstable. The DLIs were running in the wrong region. For many hours, I thought this was on me, but like the STR$() problem, it looked to me like calling unrelated PL65 functions was altering the graphics registers. In the end, I had to concede and use only two DLIs.

Paranoia, The Destroya

So now I don’t completely trust the system. I feel compelled to run a tedious compile/run/test cycle for each new line of code so I know which pieces of code might result in new odd behavior.

I know that dealing with display lists and DLIs are extremely sensitive to timing, so it’s possible a logical explanation exists. I just hope nothing else freaks-out. Otherwise I’ll need to come up with a different challenge – or try doing this in Action!.

“Cross-Compiling” using vim, make, and the Atari800 Emulator

Despite the very nice KED full-screen editor, doing the development on a real Atari 800 would be too painful. By now I’ve run a thousand edit/compile/run/debug cycles so I’m glad I spent some time up front to have a Linux-based toolchain. To compile my PL65 code, I run “make”. The basic idea is:

  1. Edit the PL65 source file using vim
  2. Run “make” to convert/move the source file to a Unix directory that is mapped as a hard-drive device within the “atari800” emulator and launch the emulator.
  3. Use the -record, -playback, and max-speed features of the “atari800” emulator to automate the keyboard entry needed to compile the source.
  4. When testing on the Atari, use BeweDOS’s STARTUP.BAT to launch the executable.

Here my toolchain is in action:

vim Syntax file

Here is my vim syntax file. Mostly just syntax-highlighting, however there is a feature with binary numbers which will change color only after 8 bits have been typed.

  1. Copy/paste this text to the file ~/.vim/syntax/pl65.vim
" Vim syntax file
" Language: PL65 for Atari 8-bit computers
" Maintainer: Michael Sternberg
" Latest Revision: 02 January 2015

if version < 600
    syntax clear
elseif exists("b:current_syntax")
    finish
endif

" Todo.
syn keyword pl65Todo TODO FIXME XXX DEBUG NOTE

" pl65CommentGroup allows adding matches for special things in comments.
syn cluster pl65CommentGroup  contains=pl65Todo

" Keywords
syn keyword pl65Command PROC FUNC INTERRUPT BODY CONST LINK INCLUDE 
syn keyword pl65Command BEGIN END LINK FORWARD MAIN ENDFILE

syn keyword pl65Type BYTE INT STRING POINTER BASED

syn keyword pl65Conditional IF THEN ELSE ENDIF 

syn keyword pl65State WHILE DO ENDWHILE REPEAT FOREVER UNTIL
syn keyword pl65State FOR TO STEP NEXT DOWNTO
syn keyword pl65State CASE OF ENDOF ENDCASE GOTO TRAP NOTRAP RETURN

syn keyword pl65Mneumonic BNE BEQ BMI BPL BCC BCS BVS BVC JMP JSR
syn keyword pl65Mneumonic INX DEX INY DEY PHA PLA PHP PLP ASLA LSA 
syn keyword pl65Mneumonic RORA ROLA TSX TXA TAX TYA TAY NOP BRK RTS 
syn keyword pl65Mneumonic RTI SED CLD SEC CLC SEI CLI CLV LDA STA LDX 
syn keyword pl65Mneumonic STX LDY STY CMP CPX CPY AND ORA EOR BIT ASL 
syn keyword pl65Mneumonic LSR ROL ROR INC DEC ADC SBC 

syn region pl65String start='"' end='"'

syn match pl65Comment "!.*$"
syn match pl65Comment "!.*!$"

syn match   pl65Label          display "[:]<w+>"
syn match   cexprNumber        display "<d+>"
syn match   cexprNumberHex     display "[$]<[0123456789ABCDEFabcdef]+>"
syn match   cexprNumberBin     display "[%]<[01][01][01][01][01][01][01][01]>"

syn region  pl65CommentL start="!" skip="\$" end="$" keepend contains=@pl65CommentGroup,@Spell

" Define the default highlighting.
" For version 5.x and earlier, only when not done already.
" For version 5.8 and later, only when and item doesn't have highlighting
" yet.
if version >= 508 || !exists("did_pl1_syn_inits")
    if version < 508
        let did_pl1_syn_inits = 1
        command -nargs=+ HiLink hi link <args>
    else
        command -nargs=+ HiLink hi def link <args>
    endif

    hi def link pl65Command         PreProc
    hi def link pl65Type            Type
    hi def link cexprNumber         Number
    hi def link pl65State           Statement
    hi def link pl65Mneumonic       Statement
    hi def link pl65Conditional     Statement
    hi def link pl65Todo            Todo
    hi def link pl65Label           Label
    hi def link cexprNumberHex      Special
    hi def link cexprNumberBin      Special
    hi def link pl65String          String
    hi def link pl65CommentL        pl65Comment
    hi def link pl65Comment         Comment

    delcommand HiLink
endif

let b:current_syntax = "pl65"

Then copy this text to the file ~/.vim/ftdetect/pl65.vim
This allows files with a .pl65 extension to have syntax-highlighting automatically applied.

au BufRead,BufNewFile *.pl65 set filetype=pl65

Makefile

The makefile supports the following targets.

Command Description
make Convert source file to Atari format and launch emulator with PL65 in D1: and target diskette in D2: using keyboard playback
make run Launch emulator with diskette containing target executable
make record Launch emulator with keyboard recording enabled
make edit Launch vim with project-specific preferences, such as 2-space indentation
BAS=STRUCTRS
IMG=../Disks/$(BAS).atr

TAR=$(BAS).PRG
SRC=$(BAS).pl65
UTL=pl65_to_prg

all:	$(IMG)

$(IMG):	$(TAR)
	atari800 -atari -playback build.rec ../Disks/PL65_BW.atr $(IMG) 2> /dev/null

$(TAR): $(SRC) $(UTL)
	./pl65_to_prg $(SRC) > ../Work/$(TAR)

$(UTL): $(UTL).c
	gcc -o $(UTL) $(UTL).c

.PHONY: run
run:
	atari800 -atari $(IMG)

.PHONY: record
record:
	atari800 -atari -record build.rec ../Disks/PL65_BW.atr $(IMG)

.PHONY: edit
edit:
	vim -u ./.vimrc $(SRC)

.PHONY: norun
norun:
	atari800 -atari ../Disks/PL65_BW.atr $(IMG)

Utility for Converting PL65 source from Unix to Atari

This C program converts a Unix text file to have Atari end-of-line characters. It also strips out PL65 comments, but doesn’t support comments on the same line as PL65 code. Instead it makes a mess of things.

/* Convert EOL from Unix to Atari
   Also skip PL65 comments "! this is a comment"
   Note: Does not support comments on same line as code.
 */
#include <stdio.h>

void display_usage(void);

#define A8_EOL 0x9b

int main (int argc, char* argv[])
{
    FILE* fp; 
    unsigned char ch;
    char state = 0;

    if (argc != 2)
    {
        display_usage();
        return(1);
    }

    fp = fopen(argv[1], "r");

    if (fp == NULL)
    {
        fprintf (stderr, "Unable to open [%s] for readn", argv[1]);
        return(1);
    }

    /* while (!feof(fp)) */
    while (state >= 0)
    {
        ch = fgetc(fp);
        if (feof(fp)) { state = -1; }
        else
        {
            /* Convert Unix EOL to Atari 8-bit EOL */
            if (ch == 'n') { ch = A8_EOL; }

            if (state == 0 && ch == '"') 
                state = 1;
            else if (state == 1 && (ch == '"' || ch == A8_EOL))
                state = 0;
            else if (state == 0 && ch == '!') 
                state = 2;
            else if (state == 2 && (ch == A8_EOL))
                state = 3;
            else if (state == 3 && (ch == '!'))
                state = 2;
            else if (state == 3 && (ch != '!'))
                state = 0;

            /* Skip comments (!) */
            if (state == 0 || state == 1) fputc(ch, stdout);
        }
    }

    fclose(fp);

    return(0);
}

void display_usage(void)
{
    fprintf(stderr, "Usage: pl65_to_prg <filename>n");
    fprintf(stderr, "Output sent to stdoutn");
    return;
}

 Up Next…

Mimicking (well, closely enough) the Apple’s Lo-Res graphics mode on the Atari 8-bit. This time. I promise.

2015 Retrochallenge Winter Warmup, Retrochallenge

Retrochallenge 2015/01 – Post 01

(This is part one of the chronicle of my Retrochallenge 2015/01 submission, which is to port the modern-day Apple II game, Structris, to the Atari 8-bit home computer using an obscure language called PL65. The mediocrity starts here.)

Hello, PL65

To get things going, I wanted to talk a bit about Noahsoft’s PL65. It was published towards the end of the 8-bit era and, as far as I know, distributed but for a few months solely via mail order. Quarter-page ads for PL65 can be found in Atari User (UK) between late 1987 and early 1988. Given it’s timing and duration on the market, it’s often regarded as the rarest of programming software titles for the Atari home computer.

If you are reading this in early 2015, you can still examine a current eBay auction for a copy of Noahsoft’s PL65. The asking price is 295.95 GBP or $461.46 USD. Yikes.

Just so there is no confusion, another programming language called PL/65 pre-dated Noahsoft’s. As early as 1978, Rockwell International offered a language called PL/65 to support their second-sourced R6500 microprocessors, and later, their single-board computer, the AIM-65. However, after looking through a copy Rockwell’s user manual, I saw nothing to suggest Noahsoft’s PL65 was a derivative of the earlier work. The only commonality is the use of ALGOL-like code blocks.

Here’s my demonstration of editing, compiling, and running a minimal program using Noahsoft’s PL65 for the Atari 8-bit home computers.

PL65 Disk Image and User Manual

In case you want to play along, below are links to a PDF of the PL65 User Manual and my version of the PL65 disk image. The disk image is in the ATR file format used by Atari 800 emulators and SIO2PC programs.

PL65 Programming Manual Title
PL65_Manual.pdf
PL65 Diskette image
PL65_BW.atr

I modified the 2nd cracked image originally created by the heroic hackers on the AtariAge forums from being a SpartaDOS X-formatted disk to the more 48K-friendly BeweDOS version 1.30 (pronounced Bay-Vay or Bay-Way Dos).

I also re-created the “WELCOME TO PL65” program using screenshots included in the recent eBay auction mentioned earlier. It was missing in the original AtariAge-cracked disk images. The greeting program is found in the file AUTOEXEC.SYS.

Originally PL65 was distributed on an Atari DOS II version 2.5 diskette. Copy protection was enforced by having the compiler stomp over your object code using XOR if it discovered it was not running on the original diskette. For what it’s worth, my version of the “WELCOME TO PL65” program uses the BeweDOS CIO command 40 with AUX1 = 128 to perform the binary load/run needed to launch the compiler and editor. This CIO command is undefined in Atari DOS II, so my program won’t run properly there.

If you are new to BeweDOS, like I am, note that, unlike the menu-driven Atari DOS II operating systems, it uses a command-line interface. To save space on the diskette, I didn’t include all the BeweDOS utilities in the DOS directory. Here are some essential BeweDOS 1.30 commands:

DIR - List contents of the current working directory
CWD - Change current working directory. Path separator is ">".
      For example, to visit the DOS directory, type "CWD >DOS" 
      To return to the root directory, type "CWD >"
ERASE - Delete a file. 
        For example "ERASE MYFILE.PRG"
Dn:  - To switch to another device. For example to switch to
       drive 2, type "D2:". To return to drive 1, type "D1:".

To execute a binary file, usually named with the .COM extension,
simply type the name of the file. If named properly, you may skip the extension.
For example, to run the KED editor, type "KED.COM" or just "KED"

Hello World in Noahsoft’s PL65 for the Atari 400/800

As a brief diversion before diving into coding Structris in PL65, I wanted to share some of the flavor of PL65. First by sharing a minimal “Hello World” example. And later, by adding a few more lines of code that showcase some of the features of the language.

Example Program 1

INCLUDE D:TERMINAL.LIB
MAIN()
BEGIN
  WRTLN("HELLO, WORLD!")
END

To spare you the trouble of reading through the PL65 manual, here are some notes about the example program:

  • No line numbers. Oy! Up, Scumbag!
  • PL65 uses the ALGOL concept of organizing code blocks which are defined by the bounding keywords “BEGIN” and “END”.
  • Every program must have a “MAIN” procedure. It is the code block that will be executed first.
  • The “WRTLN” procedure prints text to the terminal display. It appends a carriage return.
  •  The WRTLN procedure is defined in an external library file, TERMINAL.LIB, that must be included at compile-time. PL65 is a single-pass compiler, therefore all procedures and functions must be defined before they can be called.

Example Program 2

INCLUDE D:GRAPHICS.LIB

PROC HOME()
BEGIN
  WRTSTR(CHR$(125))
END

MAIN()
INT I
BEGIN
  HOME()           ! CLEAR SCREEN
  SETCOLOR(2,4,0)  ! CHANGE BACKGROUND
  I=0
  WHILE I<$0A DO   ! WHY NOT USE HEX
    WRTSTR(STR$(I)) WRTSTR(":")
    WRTLN("RETROCHALLENGE 2015/01")
    I=I+1
  ENDWHILE
  REPEAT FOREVER
END
  •  HOME() is an example of a user-defined procedure. In this case, the magic ATASCII character #125 is used to clear the screen and move the cursor to the home position.
  • The GRAPHICS library is included so we can use the SETCOLOR procedure to change the playfield background color (register 2) to dark lavender (color 4, intensity 0). The GRAPHICS library itself includes TERMINAL and STRING libraries that would otherwise be needed for WRTSTR, WRTLN, and STR$.
  • The WHILE/ENDWHILE loop uses a 2-byte integer variable, “I”, which is defined just before the start of the code block. A pitfall looms in that someone may be tempted to declare and initialize the variable using “INT I = 0”. While this is legal, it actually tell the compiler to use addresses $00/$01 (LO/HI) to store integer “I”.
  • The REPEAT/FOREVER is an empty loop construct. It could have other statements between the keywords similar to the WHILE/ENDWHILE example.
  • The language allows numeric values to be represented in decimal, hexadecimal, and binary.

Next Up…

Mimicking (well, as close as possible) Apple’s Lo-Res graphics mode using the Atari display list.