FLASH ATTACK CABLE PLANS & CONCEPTS

Notes on Hardware and Software using the Flash Attack Style Parallel Port Data Cable

This cable is used in the 2-PET game Flash Attack as well as in the article from December 1980 Byte Magazine titled “Multi-Machine Games” (by Tim Stryker & Ken Wasserman). Even though this was originally intended just for the PET, like many of the Commodore 8-bit computer features, the interfacing and BASIC are similar enough that it can be applied to many of the machines in the 8-bit line.

So with the proper effort your two-machine game or other application can be between any combination of PET, VIC-20, Commodore 64/128, and Plus/4.

Possible non-commodore communication with this method could be accomplished through IBM compatible parallel ports as well (but that is for someone else to delve into)…

Hardware:

⇐ Image of a completed cable (note sound wires were added after construction and end in the center, thus the taping at even increments.) Below the main cable is the sound wire with a small pc board for the resistors and the 1/8“ plug for the amplifier. (see bottom of this page for sound connector diagram.)

The flash Attack cable uses the Commodore's Parallel data port located on the back of most Commodore 8-bit computers, the pinout for the PET VIC-20, and Commodore 64/128 are the same (except the CB2 sound is unnecessary on non-PET systems, but could be implemented if you really want to…) The Plus/4 will work too (sans the CB2 Sound), but the wiring is… different (see farther down).

FA Cable Diagram:

The cable uses mainly two 12/24 edge board connectors and a length of flat ribbon cable (3 to 5 feet is usual), the minimum conductors needed are 8, one wire for ground, and the seven data lines between the computers, 8 conductors are necessary

Pinout:

Pin Description
A Ground
C Parallel Data Line bit 0
D Parallel Data Line bit 1
E Parallel Data Line bit 2
F Parallel Data Line bit 3
H Parallel Data Line bit 4 (this pin is used on only one connector!)
J Parallel Data Line bit 5
K Parallel Data Line bit 6
L Parallel Data Line bit 7
M CB2 Handshake Line (used for PET sound in this text)
N Ground

Plus/4: the Commodore Exception (color coded cross-over lines for clarity):

The plus/4 can also be used but due to the differences of the parallel port pinout the connector has to be wired differently. Also it may not work with a Datasette connected as pin 4 is also used for Datasette sense line. (NOTE: if two plus/4 are being wired together one connector has to have a bridge wire between pin H and pin N)

Plus/4 Specific Pinout (I don't envy you on wiring this mess)

Pin Description
A Ground
B Parallel Data Line bit 0
K Parallel Data Line bit 1
4 Parallel Data Line bit 2 (also 'cassette sense', unplug datasette before use)
5 Parallel Data Line bit 3
6 Parallel Data Line bit 4* (this pin is used on only one connector!)
7 Parallel Data Line bit 5
J Parallel Data Line bit 6
F Parallel Data Line bit 7

The connectors will fit in the Plus/4 if you file off a tad of the left/right edges of the opening for the parallel port.

FA Cable Parts:

QTY DESCRIPTION
2 12/24 contact Edge board Connectors with .156” spacing between contacts*
1 3 to 5 feet of 8 or 9 conductor ribbon cable or wire
2 Connector housings (hard to find in the U.S.)
or
4 screws to use as connector grips (I suggest size 6-32 x 1.5“ machine screws)

* Edge board connectors can be purchased (in any quantity) from Digikey Corporation Part # EDC307240-ND ($2.08 ea or $18.43 for 10)

Adding PET Sound Circuitry:

if you also require CB2 sound output for PET usage. For PET sound add:

QTY DESCRIPTION
2 50-500k resistors
1 small piece of breadboard or electrical tape (to isolate bare wires)
1 1/8” phono plug
1 Small Audio Amplifier
(like the one used in Radio Shack's Handset Listener part # 430-0231B) about $12

Wire as described above, with the ground as the casing and the CB2 signal going to the tip. Notes on how to create your own sound with a note table can be found on the PET FAQ.

—-

* remember if you make a cable, one side must have bit 4 grounded, only one side!)

Software:

Communication via the flash attack cable can be easily accomplished in BASIC or Assembly Language, and mainly deals with setting the 'data' direction of the ports and reading and sending bytes. The data bytes are sent in two 4-bit chunks (called nybbles) with the other four lines used to see who sends first (that;s what the jumper on one end if for ), indicate that data has been sent/received by the other computer.

BASIC test program

This is a two way communications test program where each computer can type to the other, using the principles of a simple recieve-send-recieve-send-recieve protocol. Everything you type on one machine will appear on the other, and visa-versa. To end the program properly one person types a shifted-Q character, it will end the program on both computers. Line 210 checks for the presence of the wire on pin 4 if that computer does have the wire, it will start by sending, the other program will know to receive by the same test.

100 REM*** PROGRAM TO TEST INTER-
110 REM*** MACHINE COMMUNICATIONS
120 REM***
130 REM PARALLEL PRT: PET-59471, 64-56577, VIC20-37151, PLUS/4-64784
140 PRT=59471
150 REM DATA DIR. REGISTER: PET-59459, 64-56579, VIC20-37139, PLUS/4-64800
160 DDR=59459
200 GOSUB 10000
205 POKE DDR,239
210 IF PEEK(PRT) AND 16 THEN 260
220 GET S$
230 IF S$ = "[SHIFT-Q]" THEN S$ = CHR$(0)
240 GOSUB 10200
250 IF S$ = "[SHIFT-Q]" THEN 999
260 GOSUB 10400
270 PRINT R$;
280 IF R$ <> "[SHIFT-Q]" THEN 220
999 END
10000 REM***
10010 REM*** ROUTINE TO INITIALIZE PORT
10020 REM*** INPUTS: NONE
10030 REM*** OUTPUTS: NONE
10040 REM***
10050 POKE PRT,255
10060 POKE DDR,255
10070 RETURN
10200 REM***
10210 REM*** ROUTINE TO SEND BYTE
10220 REM*** INPUT: S$ = BYTE TO BE SENT
10230 REM***
10240 REM*** OUTPUTS: NONE
10250 REM***
10260 HN = INT(ASC(S$)/16)
10270 LN = ASC(S$)-HN*16
10275 POKE DDR,111
10280 POKE PRT,LN+128+32
10290 IF PEEK(PRT) AND 128 THEN 10290
10300 POKE PRT,HN+128+64
10310 IF PEEK(PRT) AND 128 THEN 10330
10320 GOTO 10310 
10330 POKE PRT,255
10340 RETURN
10400 REM***	
10410 REM*** ROUTINE TO RECEIVE BYTE
10420 REM*** INPUTS: NONE
10430 REM*** OUTPUT: R$ = BYTE RECEIVED
10440 REM***
10445 POKE DDR,128
10450 IF PEEK(PRT) AND 64 THEN 10450
10460 LN = PEEK(PRT) AND 15
10470 POKE PRT,127	
10480 IF PEEK(PRT) AND 32 THEN 10480
10490 HN = PEEK(PRT) AND 15
10500 POKE PRT,255
10510 R$ = CHR$(HN*16+LN)
10520 RETURN

ML ASSEMBLER

DISASSEMBLY OF FLASH ATTACK CABLE ROUTINES (MERLIN 128 FORMAT)

********************************
*      IMPROVED COMM-LINK      *
* ROUTINES FOR COMMODORE 8-BIT *
*          COMPUTERS           *
*------------------------------*
*      BY LARRY ANDERSON       *
*      REV DATE: 06/25/91      *
********************************
;
* 64 VERSION:
;
CHKCMA     =     $AEFD      ;CHECK FOR COMMA
EVALEXP    =     $AD9E      ;EVAUATE EXPRESSION AND LEAVE IN FAC#1
FLTFIX     =     $B7F7      ;FLOATING POINT TO FIXED INTERGER UN-SIGNED
;
GETIN      =     $FFE4      ;GET CHARACTER FROM INPUT DEVICE
KYTBL      =     $CF00      ;KEYBOARD DECODE TABLE (KEYPRESS TO PETASCII)
;
FIXFLT     =     $B3A2      ;FIXED INTERGER (IN .Y)  TO FLOATING POINT
PORT       =     $DD01      ;PARALLEL PORT ACCESS
DDR        =     $DD03      ;PARALLEL PORT DATA DIRECTION REGISTER
;
VECTORS    =     $033C
;
;
;
TEMP       =     VECTORS+1 ;TEMPORARY
UTIL1      =     VECTORS+2 ;AND UTILITY BYTES
UTIL2      =     VECTORS+3
;
           ORG   $C000      ;CODE WILL BE ASSEMBLED TO 49152-
;
; USAGE:
; FIRST, SET UP USR JUMP IN BASIC:
;        POKE785,0:POKE786,192
; SECONDWHEN READY, DETERMINE WHO SENDS/RECIEVES FIRST BY USING THIS:
:        POKE 59459,239:IF PEEK(59471) AND 16 THEN ***
; ONE COMPUTER WILL BRANCH, THE OTHER WON'T
;
; ML USAGE:
; TO SEND BYTES USE: SYS 49155,[#],[#],[#],[ETC],256 ([#] =0-255, AT LEAST ONE)
; TO RECEIVE BYTES: NUM=USR(0)   (ONE AT A TIME)
; TO SEND BLOCK OF MEMORY: SYS 49158,[START ADDRESS],[END ADDRESS]
; TO RECEIVE BLOCK OF MEMORY: SYS 49161
;
 
           JMP   USRPROC    ;USR() INPUT PROCESSOR: 0 PORT RECEIVE, -1 GET KYBD
           JMP   SNDBYTS    ;SEND BYTES: SYS SEND,0,23,123,33,>=256(END)
           JMP   SNDBLK     ;SEND BLOCK: SYS ADDR,START,END
           JMP   RCVBLK     ;RECEIVE BLOCK
           JMP   CLRPORT    ;RESET PORT
;
* SUBROUTINE TO GET NUMBERS
;
GETNUM     JSR   CHKCMA     ;GET A NUMBER APPENDED TO THE CALLING SYS
           JSR   EVALEXP    ; I.E. SYS 49152,123
           JMP   FLTFIX     ; NUMBER WILL BE UNSIGNED IN FAC1 AND Y/A
 
SNDBYT     JSR   SETUP
           STA   TEMP       ;STORE COPY OF BYTE
           LDX   #$6F       ;DDR MASK BYTE: 01101111
           STX   DDR        ;SET DDR TO: IOOIOOOO
           ORA   #$F0       ;MASK OUT LOW NYBBLE: ----****
           AND   #$BF       ;ADD IN NEW DATA: 1011**** (LOW NYBBLE READY)
           STA   PORT       ;SEND LOW-NYBBLE ON CABLE
           LDA   TEMP       ;GET SEND BYTE AGAIN
           LSR              ;SHIFT RIGHT -****---
           LSR              ;SHIFT RIGHT --****--
           LSR              ;SHIFT RIGHT ---****-
           LSR              ;SHIFT RIGHT ----****
           CLC
           ORA   #$D0       ;ADD IN NEW DATA: 1101**** (HIGH NYBBLE READY)
SNLOOP1    BIT   PORT       ;CHECK THE STATUS OF DATA RECEIVED 0------
           BMI   SNLOOP1    ;KEEP CHECKING TILL RECEIVED
           STA   PORT       ;SEND HIGH-NYBBLE ON CABLE
SNLOOP2    BIT   PORT       ;CHECK STATUS OF DATA RECEIVED 1------
           BPL   SNLOOP2    ;KEEP CHECKING TILL RECEIVED
           JSR   CLRPORT    ;RESET PORT
           JMP   SETDOWN    ;ALL DONE
;
RCVBYT     JSR   SETUP
           LDA   #$80       ;DDR MASK BYTE: 10000000
           STA   DDR        ;SET DDR TO: OIIIIIII
           STA   PORT       ;SET PORT AS WELL
RNLOOP1    BIT   PORT       ;WAIT TILL LOW NYBBLE READY -1------
           BVS   RNLOOP1    ;KEEP CHECKING TILL SET
           LDA   PORT       ;GET LOW-NYBBLE FROM CABLE
           AND   #$0F       ;GET RID OF STATUS GARBAGE: ----****
           STA   TEMP       ;SAVE IT AWAY
           LDA   #$7F       ;SET DATA RECEIVED 01111111
           STA   PORT       ;TELL SENDER
           LDA   #$20
RNLOOP2    BIT   PORT       ;WAIT TILL HIGH NYBBLE READY
           BNE   RNLOOP2    ;KEEP CHECKING TILL SET
           LDA   PORT       ;GET HIGH-NYBBLE FROM CABLE
           ASL              ;SHIFT LEFT ---****-
           ASL              ;SHIFT LEFT --****--
           ASL              ;SHIFT LEFT -****---
           ASL              ;SHIFT LEFT ****----
           CLC
           ORA   TEMP       ;COMBINE TO GET FULL BYTE
           JSR   CLRPORT    ;RESET PORT (WILL SET DATA RECEIVED)
           JMP   SETDOWN
;
CLRPORT    LDX   #$FF       ;RESET MASK: 1111111
           STX   DDR        ;RESET DATA DIRECTION REGISTER: OOOOOOOO
           STX   PORT       ;RESET PORT BUS: 11111111
           RTS
;
SETUP      STY   UTIL1
           STX   UTIL2
           RTS
;
SETDOWN    LDY   UTIL1
           LDX   UTIL2
           RTS
;
USRPROC    JSR   FLTFIX     ;CONVERT USR(X) INTO TWO BYTES  UN-SIGNED)
           CPY   #$00       ;IF HI-BYTE =0, YOU WANT IT FROM THE COM PORT?
           BEQ   GETBYT     ;YES, GET IT PLEASE..
           JSR   GETIN      ;GET VALUE FROM KEYBOARD
           LDA   KYTBL,Y    ;GET NEW PROCESSEED VALUE
           TAY
           JMP   FIXFLT     ;FINISH BY CONV IT TO BASIC READY VAL.
GETBYT     JSR   RCVBYT     ;GET A BYTE FROM THE CABLE
           TAY              ;SET LO SYSTEM POINTERS ACCORDINGLY
           LDA   #$00       ;  "                                 "
           JMP   FIXFLT     ;FIX BYTE TO BE RETURNED AND RETURN
;
SNDBYTS    JSR   GETNUM     ;GET NEXT VALUE
           CMP   #$00       ;IS THIS THE END? (GREATER THAN 255?)
           BNE   ENDSEND    ;YES, LETS END THIS.
           TYA              ;NO, TRANSFER LO TO ACCUMULATOR.
           JSR   SNDBYT     ;SEND IT OVER COMM
           JMP   SNDBYTS    ;GET NEXT VALUE.
ENDSEND    RTS              ;ALL DONE.
;
; THE FOLLOWING BLOCK SEND/RECIEVE ROUTINE USES SELF-MODIFYING
 
; M/L CODE; SOMETHING YOUR MOM OR YOUR PROGRAMMING INSTRUCTORS
; WARNED YOU TO AVOID.  BUT COOL PROGRAMMERS WHO LIVE DANGROUSLY
; GET ALL THE CHICKS.
;
SNDBLK     LDA   #$0D
           JSR   SETMODE
           JSR   GETNUM     ;GET START ADDRESS OF BLOCK
           STA   BLKPTR1+2  ;STORE IT IN BLOCK MOVER
 
           JSR   SNDBYT     ;SEND IT OVER CABLE
           TYA              ;GET LOW PART OF ADDRESS
           STA   BLKMOV+1   ;STORE IT IN BLOCK MOVER
           JSR   SNDBYT     ;SEND IT OVER CABLE
           JSR   GETNUM     ;GET END ADDRESS OF BLOCK
           STA   BLKPTR5+1  ;PUT IT IN BLOCK MOVER
           JSR   SNDBYT     ;SEND IT OVER CABLE
           TYA              ;GET LOW PART OF ADDRESS
           STA   BLKPTR3+1  ;PUT IT IN BLOCK MOVER
           JSR   SNDBYT     ;SEND IT OVER CABLE
           JMP   BLKMOV
;
RCVBLK     LDA   #$06
           JSR   SETMODE
           JSR   RCVBYT     ;GET START ADDR HI
           STA   BLKPTR2+2  ;STORE IN BLOCK MOVER
           JSR   RCVBYT     ;GET START ADDR LOW
           STA   BLKMOV+1   ;STORE IN BLOCK MOVER
           JSR   RCVBYT     ;GET END ADDR HI
           STA   BLKPTR5+1  ;STORE IN BLOCK MOVER
           JSR   RCVBYT     ;GET END ADDR LO
           STA   BLKPTR3+1  ;STORE IN BLOCK MOVER
;
                            ;************************************
                            ;DUAL PURPOSE BLOCK RECEIVE/TRANSMIT
                            ;, - CODE IS MOFIFIED BY SETMODE
                            ;
BLKMOV     LDY   #$FF       ;SET LOW COUNTER TO ??
BLKPTR1    JSR   RCVBYT     ;GET A BYTE
BLKPTR2    STA   $FF00,Y    ;STORE IT IN MEMORY
BLKPTR3    CPY   #$FF       ;LOW BYTES MATCH?
           BNE   MLOOP1     ;NO, CONTINUE
BLKPTR4    LDA   BLKPTR2+2  ;GET HIGH ADDRESS
BLKPTR5    CMP   #$FF       ;HIGH BYTES MATCH?
           BEQ   MLOOP3     ;YES! EXIT
MLOOP1     INY              ;INCREMENT COUNTER
           BNE   BLKPTR1    ;PAGE JUMP?
BLKPTR6    INC   BLKPTR2+2  ;YES, NEW PAGE
           JMP   BLKPTR1    ;START AGAIN
MLOOP3     RTS
;
SETMODE    TAX              ;STORE ROUTINE VALUE
           LDA   PTABLE,X   ;GET LOW BYTE OF ADDR HI LOC
           STA   BLKPTR4+1  ;STORE IT IN BOTH COMPARE
           STA   BLKPTR6+1  ; AND INCREMENT REGISTERS
           DEX              ;SET FOR SUBROUTINE MODIFICATIONS
           LDY   #$06       ;SET COUNTDOWN COUNTER
SLOOP1     LDA   PTABLE,X   ;READ MODIFICATIONS
           STA   BLKPTR1-1,Y  ;WRITE MODIFICATIONS
           DEX              ;DECREMENT COUNTERS
           DEY
           BNE   SLOOP1     ;DONE?
           RTS            ;YEP!
;
PTABLE     JSR   RCVBYT     ;RECEIVE MODIFICATIONS
           STA   $FF00,Y    ; FOR BLKMOV SUBROUTINE
           DFB   <BLKPTR2+2 ; LO-BYTE OF LOCATION TO PUT MODIFYING CODE
           LDA   $FF00,Y    ;SEND MODIFICATIONS
           JSR   SNDBYT     ; FOR BLKMOV SUBROUTINE
           DFB   <BLKPTR1+2 ; LO-BYTE OF LOCATION TO PUT MODIFYING CODE
;
Last modified:: 2020/11/22 21:33
   
Except where otherwise noted, content on this wiki is licensed under the following license: CC Attribution-Share Alike 4.0 International