;*; Updated on 04-May-90 at 2:37 PM by Matt Badger; edit time: 0:00:44
;SPACE.M68 - Game of Space Invaders
;Copyright (C) 1986 by UltraSoft (ULTR/AM)
;
;Written by: David Pallmann
;
;Edit History:
;1.0 24-Feb-86 created. /DFP
;
;The game performs best when run on a terminal at 19200 baud.  Running at a
;slower baud rate will make Space Invaders less challenging and the quality
;of the graphics illusions will suffer.
;
;This program was designed so that it should run on just about any kind of
;terminal, no matter how smart of dumb.  The only calls required are Clear
;Screen and Position Cursor.  Cursor On and Cursor Off are used if supported
;by the terminal driver.
;
;Space Invaders requires 3K of memory.
;
;Space Invaders is FreeWare. Like the program?  Send me a few complements
;and I will continue to write more games like this.
;              Address: David Pallmann
;                       UltraSoft
;                       367 Wildwood Rd
;                       Ronkonkoma, NY  11779
;
;SPACE.M68 is complete and requires no external files (other than those
;included with AMOS/L).  To assemble: .M68 SPACE    To run: .SPACE

;Program version number
       VMAJOR=1
       VMINOR=0

;Universal (.UNV) files referenced - all included with AMOS/L
       SEARCH  SYS
       SEARCH  SYSSYM
       SEARCH  TRM

;Registers
;'MEM' (same as A5) - used to point to work memory (variable space)
       MEM=A5

;Game definition parameters
;ROWS is set to the number of rows of aliens
;COLS is set to the number of columns of aliens
;WIDTH is set to the screen width
       ROWS=4
       COLS=8.
       WIDTH=80.

;The following defines an alien record as consisting of:
;       a row (if this is zero then the alien no longer exists) - one byte
;       a column - one byte
;       a type code (different types draw different aliens) - also one byte
;There is one alien record for each alien-- the total number is ROWS*COLS
       .OFINI
       .OFDEF  AROW,1                  ; cursor row
       .OFDEF  ACOL,1                  ; cursor column
       .OFDEF  ATYPE,1                 ; alien type
       .OFSIZ  ASIZE

;The following defines variable space used in this program:
       .OFINI
       .OFDEF  ADATA,ASIZE*ROWS*COLS   ; alien data - one record for each alien
       .OFDEF  SCORE,4                 ; player's score - one longword
       .OFDEF  SAUCNT,2                ; saucer appearance timer - one word
       .OFDEF  SAUVAL,2                ; point value of next saucer - one word
       .OFDEF  SAUCER,1                ; position (column) of saucer (0=no saucer)
       .OFDEF  SAUDIR,1                ; direction of saucer movement (0=left,-1=right)
       .OFDEF  ROW,1                   ; row - used by some subroutines - one byte
       .OFDEF  COL,1                   ; column - used by some subroutines - one byte
       .OFDEF  TYPE,1                  ; type - used by some subroutines - one byte
       .OFDEF  ACOUNT,1                ; number of aliens left
       .OFDEF  POS,1                   ; position (column) of laser base
       .OFDEF  MROW,1                  ; row of user's missile (0=no missile)
       .OFDEF  MCOL,1                  ; column of user's missile
       .OFDEF  XROW,1                  ; row of alien's missile (0=no missile)
       .OFDEF  XCOL,1                  ; column of alien's missile
       .OFDEF  LIVES,1                 ; number of spare lives left
       .OFDEF  ATTCNT,1                ; cycles between attacks
       .OFSIZ  MEMSIZ

;Macro CURSOR {row},{column} addresses the cursor
;{row} and {column} arguments must be BYTES
DEFINE  CURSOR  ROW,COL
       CLRW    D1
       MOVB    ROW,D1
       ROLW    D1,#8.
       ADDB    COL,D1
       TCRT
       ENDM

;Macro TCALL is used to define TAB(-1,x) codes (see below)
DEFINE  TCALL   CODE
       MOVW    #-1_8.+CODE'.,D1
       TCRT
       ENDM

;Terminal Special Functions:
;CLS = TAB(-1,0); clear screen
;ON = TAB(-1,28); cursor on
;OFF = TAB(-1,29); cursor off
DEFINE CLS=TCALL 0
DEFINE ON=TCALL 28
DEFINE OFF=TCALL 29

;Start of Code
;Program header defines program as reentrant and reusable (can be LOADed into
;system or user memory safely), and stores version number.
;GETIMP call allocates memory variable space and points register MEM to it.
START:  PHDR    -1,0,PH$REE!PH$REU      ; program header
       GETIMP  MEMSIZ,MEM              ; allocate local memory

;The memory allocated by GETIMP is cleared to zeroes, which is generally
;what the programmer wants.  Here, though, we need to pre-load some values:
SETUP:  MOVB    #4,LIVES(MEM)           ; user starts out w/4 extra lives
       MOVW    #1000.,SAUVAL(MEM)      ; value of next saucer is 1000 points
       MOVB    #5,ATTCNT(MEM)          ; set 5 cycles between alien attacks

;Set Terminal
;Set image (single character) mode and turn off terminal echo
;If terminal supports it, turn off cursor
TERM:   JOBIDX  A0                      ; index Job Control Block
       MOV     JOBTRM(A0),A1           ; get terminal definition area addr
       ORW     #T$IMI!T$ECS,T.STS(A1)  ; set image mode & turn off echo
       OFF                             ; turn off cursor

;Intro Screen
INTRO:  CLS                             ; clear screen
       MOVB    #12.,ROW(MEM)           ; set row to 12
       MOVB    #10.,COL(MEM)           ;  and column to 10
       CLRB    TYPE(MEM)               ; set alien type to 0
       LEA     A1,MESSAG               ; index display message
10$:    CALL    DRAW                    ; draw alien
       MOVB    COL(MEM),D2             ; get column
       SUBB    #3,D2                   ; subtract 3 from it
       CURSOR  ROW(MEM),D2             ; re-address cursor
       MOVB    (A1)+,D1                ; get next char of message
       BEQ     40$                     ; branch if end-of-message
       CMPB    D1,#'~                  ; delay command?
       BNE     20$                     ;  no
       SLEEP   #3000.                  ; yes - sleep 1/3 second
       BR      30$                     ; branch
20$:    TTY                             ; display char on screen
30$:    INCB    COL(MEM)                ; increment alien column
       BR      10$                     ; loop back
40$:

;First or New Screen of Aliens
;Automatically give user a new life as a reward for finishing previous screen
;Clear the screen;
;Retype name 'SPACE INVADERS' at the top of the screen, and display spare
;laser bases (lives) at the bottom of the screen.
NEWSET: CMMB    LIVES(MEM),#19.         ; does user have 19 spare lives?
       BGE     10$                     ;  yes - can't fit any more on line 24
       INCB    LIVES(MEM)              ; give user another life
10$:    CLRB    SAUCER(MEM)             ; no saucer
       MOVW    #1000.,SAUCNT(MEM)      ; 1000 cycles till next saucer appears
       CLRB    MROW(MEM)               ; no player missile
       CLRB    XROW(MEM)               ; no alien missile
       CLS                             ; clear the screen
       TYPE    Space Invaders          ; name of the game
       CURSOR  #24.,#1                 ; address cursor
       CLR     D0                      ; get number
       MOVB    LIVES(MEM),D0           ;  of addition lives
20$:    TYPESP  _A_                     ; print laser base
       SOB     D0,20$                  ; loop till done
       CALL    DISCOR                  ; display score

;Adjust attack frequency based on score
ADJUST: CMM     SCORE(MEM),#10000.      ; score < 10000?
       BLT     BASE                    ;  yes - branch
       MOVB    #4,ATTCNT(MEM)          ;  no - attack 1 out of 5 times
       CMM     SCORE(MEM),#25000.      ; score < 25000?
       BLT     BASE                    ;  yes - branch
       MOVB    #3,ATTCNT(MEM)          ;  no - attack 1 out of 4 times
       CMM     SCORE(MEM),#50000.      ; score < 50000?
       BLT     BASE                    ;  yes - branch
       MOVB    #2,ATTCNT(MEM)          ;  no - attack 1 out of 3 times
       CMM     SCORE(MEM),#75000.      ; score < 75000?
       BLT     BASE                    ;  yes - branch
       MOVB    #1,ATTCNT(MEM)          ;  no - attack every other time
       CMM     SCORE(MEM),#100000.     ; score < 100000?
       BLT     BASE                    ;  yes - branch
       CLRB    ATTCNT(MEM)             ;  no - attack every change we get
                                       ;       (this guy is good!)

;Set laser base to center of horizon (column 41) and draw laser base
BASE:   MOVB    #41.,POS(MEM)           ; set laser base position
       CALL    DRWLSR                  ; draw laser base

;Initialize alien data array
;Loop through matrix assigning rows, columns, and types
;Top row becomes type 0 aliens, next row is type 1, and so on
;Different type aliens get displayed differently by DRAW subroutine
;Plot all aliens on the screen
;Set ACOUNT (alien count) to total number of aliens
INIT:   MOVB    #ROWS*COLS,ACOUNT(MEM)  ; set alien count
       LEA     A0,ADATA(MEM)           ; index alien data area
       MOVB    #2,COL(MEM)             ; set current column to 2
       MOV     #COLS,D3                ; set up outer loop
10$:    MOV     #ROWS,D2                ; set up inner loop
       MOVB    #4,ROW(MEM)             ; set row to 4
       CLRB    TYPE(MEM)               ; set type to 0
20$:    MOVB    ROW(MEM),AROW(A0)       ; set alien row
       MOVB    COL(MEM),ACOL(A0)       ; set alien column
       MOVB    TYPE(MEM),ATYPE(A0)     ; set alien type
       CALL    DRAW                    ; draw alien
       ADD     #ASIZE,A0               ; advance to next data record
       ADDB    #3,ROW(MEM)             ; add 3 to next row
       INCB    TYPE(MEM)               ; add 1 to next type
       SOB     D2,20$                  ; loop till row of aliens defined
       ADDB    #8.,COL(MEM)            ; add 8 to next column
       SOB     D3,10$                  ; loop till all columns of aliens defined

;This is the main body of code.  MOVER and MOVEL are nearly identical pieces
;of code.  The difference is that MOVER processes the aliens in a different
;order (column-by-column, starting at the right) from MOVEL (column-by-column,
;starting at the left).  When MOVER cannot move the aliens any further right,
;it calls the local subroutine NXTROW (which moves all the aliens down a row),
;and branches to MOVEL.  MOVEL then moves the aliens left.  When MOVEL can't
;go any further left, it too calls the NXTROW routine.  Finally, control loops
;right back to MOVER.
;Both MOVEL and MOVER operate in terms of "cycles".  In a cycle, the following
;occurs:        1. the next alien is moved left or right
;               2. the saucer (if present) is moved (or possibly created)
;               3. the keyboard is scanned and any commands are acted upon
;               4. if a missile has been fired by the user, or by an alien,
;                  it is advanced.
;
;Processing for right-moving aliens
MOVER:  LEA     A0,<ADATA+<ROWS*COLS*ASIZE>-ASIZE>(MEM) ; index last alien record
       MOV     #ROWS*COLS,D0           ; set up loop to process every alien
       CLRB    D5                      ; clear flag
10$:    CTRLC   FINISH                  ; branch on ^C
       TSTB    AROW(A0)                ; is this alien still alive?
       BEQ     20$                     ;  no - branch
       CALL    CHKCMD                  ; check and act on player commands
       CALL    MOVSAU                  ; move or create flying saucer
       CALL    MISSIL                  ; move player missile
       TSTB    ACOUNT(MEM)             ; time for a new screen?
       JEQ     NEWSET                  ;  yes - branch
       CALL    ATTACK                  ; move or create alien missile
       TSTB    AROW(A0)                ; has this alien been destroyed?
       BEQ     20$                     ;  yes
       INCB    ACOL(A0)                ; move alien right
       MOVB    AROW(A0),ROW(MEM)       ; copy row,
       MOVB    ACOL(A0),COL(MEM)       ;  column, and
       MOVB    ATYPE(A0),TYPE(MEM)     ;  type
       CALL    DRAW                    ; re-draw alien
       CMPB    ACOL(A0),#WIDTH-5       ; is alien at far-right of screen?
       BLE     20$                     ;  no
       SETB    D5                      ;  yes - set flag
20$:    SUB     #ASIZE,A0               ; advance backwards to previous record
       SOB     D0,10$                  ; loop till all aliens moved
       TSTB    D5                      ; is it time to move left?
       BEQ     MOVER                   ;  no - branch
       BCALL   NXTROW                  ;  yes - move all aliens down a row

;Processing for left moving aliens
MOVEL:  LEA     A0,ADATA(MEM)           ; index first alien data record
       MOV     #ROWS*COLS,D0           ; set up loop to process every alien
       CLRB    D5                      ; clear flag
10$:    CTRLC   FINISH                  ; branch on ^C
       TSTB    AROW(A0)                ; is this alien still alive?
       BEQ     20$                     ;  no - branch
       CALL    CHKCMD                  ; check and act on player commands
       CALL    MOVSAU                  ; move or create flying saucer
       CALL    MISSIL                  ; move player missile
       TSTB    ACOUNT(MEM)             ; time for a new screen?
       JEQ     NEWSET                  ;  yes - branch
       CALL    ATTACK                  ; move or create alien missile
       TSTB    AROW(A0)                ; has this alien been destroyed?
       BEQ     20$                     ;  yes - branch
       DECB    ACOL(A0)                ; move alien left
       MOVB    AROW(A0),ROW(MEM)       ; copy row,
       MOVB    ACOL(A0),COL(MEM)       ;  column, and
       MOVB    ATYPE(A0),TYPE(MEM)     ;  type
       CALL    DRAW                    ; re-draw alien
       CMPB    ACOL(A0),#3             ; is alien at far-left of screen?
       BGE     20$                     ;  no - branch
       SETB    D5                      ;  yes - set flag
20$:    ADD     #ASIZE,A0               ; advance to next data record
       SOB     D0,10$                  ; loop till all aliens moved
       TSTB    D5                      ; is it time to move right?
       BEQ     MOVEL                   ;  no - branch
       BCALL   NXTROW                  ;  yes - move all aliens down a row
       JMP     MOVER                   ; loop back to right-moving routine

;Local Subroutine - increments rows of all aliens
;This routine is called when the array of aliens moves to the far left or
;right of the screen.  If any aliens make it line 24 of the screen, the game
;is over and control is passed to GAMOVR.
NXTROW: LEA     A0,ADATA(MEM)           ; index alien data area
       MOV     #ROWS*COLS,D0           ; set up loop to process each alien
10$:    TSTB    AROW(A0)                ; is alien alive?
       BEQ     20$                     ;  no - branch
       INCB    AROW(A0)                ; increment row
       CMMB    AROW(A0),#23.           ; have we exceeded row 23?
       JGE     GAMOVR                  ;  yes - game is over
20$:    ADD     #ASIZE,A0               ;  no - advance to next alien
       SOB     D0,10$                  ; loop till done
       RTN                             ; return

;Move Saucer Routine - called every cycle
;If no saucer is currently on the screen, a counter is decremented.  When the
;counter finally reaches zero, a saucer is created.  The decision to create
;the saucer on the left or right hand side of the screen is determined by
;whether there are an odd or even number of aliens left on the screen.
;If a saucer is already on the screen, it is advanced.
MOVSAU: TSTB    SAUCER(MEM)             ; is there a saucer on the screen?
       BNE     ADVSAU                  ;  yes
       DECW    SAUCNT(MEM)             ; decrement saucer count
       BEQ     10$                     ; branch if time for a new saucer
       RTN                             ; else return
10$:    CLR     D7                      ; get number
       MOVB    ACOUNT(MEM),D7          ;  of aliens left?
       BTST    #0,D7                   ; even?
       BEQ     20$                     ;  yes
       MOVB    #WIDTH-7,SAUCER(MEM)    ; set column to 75
       CLRB    SAUDIR(MEM)             ; set direction to left
       CALL    DRWSAU                  ; draw saucer
       RTN                             ; return
20$:    MOVB    #2,SAUCER(MEM)          ; set column to 2
       SETB    SAUDIR(MEM)             ; set direction to right
       CALL    DRWSAU                  ; draw saucer
       RTN                             ; return
ADVSAU: TTYI                            ; ring
       BYTE    7,0                     ;  bell
       TSTB    SAUDIR(MEM)             ; are moving left or right?
       BEQ     ADVLFT                  ; left
ADVRHT: INCB    SAUCER(MEM)             ; advance to next column
       CMMB    SAUCER(MEM),#WIDTH-7    ; end of screen?
       BGT     10$                     ;  yes - branch
       CALL    DRWSAU                  ;  no - re-draw saucer
       RTN                             ; return
10$:    CALL    CLRSAU                  ; erase saucer from screen
       RTN                             ; return
ADVLFT: DECB    SAUCER(MEM)             ; move saucer left
       CMMB    SAUCER(MEM),#3          ; end of screen?
       BLT     10$                     ;  yes - branch
       CALL    DRWSAU                  ;  no - re-draw saucer
       RTN                             ; return
10$:    CALL    CLRSAU                  ; erase saucer from screen
       RTN                             ; return

;Check Command - called every cycle
;Left-arrow (^H) moves laser base to the left
;Right-arrow (^L) moves laser base to the right
;Space Bar fires a missile
;Control-C exits game
CHKCMD: TCKI                            ; has a key been pressed?
       BEQ     10$                     ;  yes - branch
       RTN                             ;  nope - return
10$:    KBD     FINISH                  ; get char into D1 (branch on ^C)
       CMPB    D1,#'H-'@               ; is it... ^H (left-arrow)?
       BEQ     MOVLFT                  ;  yes - branch
       CMPB    D1,#'L-'@               ; is it... ^L (right-arrow)
       BEQ     MOVRHT                  ;  yes - branch
       CMPB    D1,#40                  ; is it... a space
       JEQ     FIRE                    ;  yes - branch
       RTN                             ; ignore char and return

;Move laser base left
MOVLFT: CMPB    POS(MEM),#5             ; is laser base at extreme left?
       BLE     10$                     ;  yes - branch
       SUBB    #2,POS(MEM)             ; move laser base two columns left
       CALL    DRWLSR                  ; re-draw laser base
10$:    RTN                             ; return

;Move laser base right
MOVRHT: CMPB    POS(MEM),#WIDTH-5       ; is laser base at extreme right?
       BGE     10$                     ;  yes - branch
       ADDB    #2,POS(MEM)             ; move laser base two columns right
       CALL    DRWLSR                  ; re-draw laser base
10$:    RTN                             ; return

;Fire missile (from player)
;This code is run when the user presses the space bar
;If a missile is already on the screen, nothing happens
;Otherwise, a missile is created and plotted using the DRWMSL routine
;Ensuing cycles will automatically advance the missile in the MISSIL routine
FIRE:   TSTB    MROW(MEM)               ; missile in the air?
       BEQ     10$                     ;  no
       RTN                             ;  yes
10$:    MOVB    #22.,MROW(MEM)          ; locate missile at column 22
       MOVB    POS(MEM),MCOL(MEM)      ; set missile column to laser base column
       CALL    DRWMSL                  ; draw the missile
       RTN                             ; return

;Missile Processing - called every cycle
;This routine advances a missile if there is one on the screen
;The missile will cease to exist if (1) it reaches the top of the screen,
;(2) it collides with an alien (which destroys it and increases the player's
;score, or (3) it collides with a saucer (which also destroys it and increases
;the player's score).
MISSIL: SAVE    A0,D0-D3                ; save registers
       TSTB    MROW(MEM)               ; is a player missile on the screen?
       BEQ     MSLRTN                  ;  no - branch
       CALL    CLRMSL                  ; erase missile from screen
       DECB    MROW(MEM)               ; move missile one row up
       CMMB    MROW(MEM),#2            ; is missile at top of screen?
       BEQ     MSLSAU                  ;  yes - branch
       CALL    DRWMSL                  ; re-draw missile
       CMMB    MROW(MEM),XROW(MEM)     ; collision with alien missile?
       BNE     10$                     ;  no
       CMMB    MCOL(MEM),XCOL(MEM)     ; collision with alien missile?
       BNE     10$                     ;  no
       CALL    COLLID                  ; handle collision
       BR      MSLRTN                  ; all done
10$:    LEA     A0,ADATA(MEM)           ; index alien data array
       MOV     #ROWS*COLS,D0           ; prepare to process all records
MSLCHK: CLR     D2                      ; clear D2
       MOVB    AROW(A0),D2             ; D2 := upper row
       MOV     D2,D3                   ; copy D2 to D3
       INCB    D3                      ; D3 := lower row
       CMMB    MROW(MEM),D2            ; is missile above this alien?
       BLT     MSLNXT                  ;  yes - branch
       CMMB    MROW(MEM),D3            ; is missile below this alien?
       BGT     MSLNXT                  ;  yes - branch
       MOVB    ACOL(A0),D2             ; D2 := alien column position (left)
       MOV     D2,D3                   ; c
opy D2 to D3
       ADDB    #3,D3                   ; D3 := alien column position (right)
       CMMB    MCOL(MEM),D2            ; is missile to left of alien?
       BLT     MSLNXT                  ;  yes - branch
       CMMB    MCOL(MEM),D3            ; is missile to right of alien?
       BGT     MSLNXT                  ;  yes - branch
       CALL    CLEAR                   ; clear alien from screen and memory
       BR      MSLRTN                  ; branch
MSLNXT: ADD     #ASIZE,A0               ; advance to next alien data record
       SOB     D0,MSLCHK               ; loop till all aliens checked
MSLRTN: REST    A0,D0-D3                ; restore registers
       RTN                             ; return
MSLSAU: CLR     D2                      ; clear D2
       MOVB    SAUCER(MEM),D2          ; D2 := saucer column (left)
       BEQ     10$                     ; branch if not active
       MOV     D2,D3                   ; copy D3 to D2
       ADDB    #6,D3                   ; D3 := saucer column (right)
       TSTB    MROW(MEM)               ; is player missile active?
       BEQ     10$                     ;  no - branch
       CMMB    MCOL(MEM),D2            ; is player missile to left of saucer?
       BLT     10$                     ;  yes - branch
       CMMB    MCOL(MEM),D3            ; is player missile to right of saucer?
       BGT     10$                     ;  yes - branch
       CURSOR  #2,SAUCER(MEM)          ; erase saucer
       TYPESP                          ;  by print a space,
       CLR     D1                      ;  the point
       MOVW    SAUVAL(MEM),D1          ;   value of
       DCVT    4,OT$TRM!OT$ZER         ;    the saucer,
       TYPE    <  >                    ;  and another space
       SLEEP   #2500.                  ;  wait 1/4 second
       CURSOR  #2,SAUCER(MEM)          ;  and then
       TYPE    <       >               ;  type space to complete erase saucer
       CLRB    SAUCER(MEM)             ; mark saucer as inactive
       MOVW    #1000.,SAUCNT(MEM)      ; reset saucer cycle count
       CLR     D7                      ; load
       MOVW    SAUVAL(MEM),D7          ;  value of saucer
       ADD     D7,SCORE(MEM)           ;  and add to score
       ADDW    #500.,SAUVAL(MEM)       ; add 500 to value of next saucer
       CALL    DISCOR                  ; re-display score
10$:    CLRB    MROW(MEM)               ; mark player missile inactive
       REST    A0,D0-D3                ; restore registers
       RTN                             ; return

;Alien Attack Routine - called once every cycle
;This routine is responsible for (1) generating alien missile attacks on the
;player every so often and (2) advancing said missile down the screen.
ATTACK: TSTB    AROW(A0)                ; is this alien alive?
       BEQ     10$                     ;  no - branch
       TSTB    XROW(MEM)               ; is an alien missile active?
       JNE     ATTMOV                  ;  yes - branch
       MOVB    ACOL(A0),D1             ; add one to
       INCB    D1                      ;  alien column
       CMPB    D1,POS(MEM)             ; is laser base within range of an attack?
       BEQ     ATTCHK                  ;  yes - branch
       INCB    D1                      ; add one more to alien column
       CMPB    D1,POS(MEM)             ; is laser base withing range now?
       BEQ     ATTCHK                  ;  yes - branch
10$:    RTN                             ; return

;Player is in a position where he/she can be attacked by the current alien.
;Now scan to see if there are any aliens blocking the way
ATTCHK: LEA     A1,ADATA(MEM)           ; index alien data array
       MOV     #ROWS*COLS,D1           ; prepare to process all records
10$:    CMP     A0,A1                   ; is this the current alien?
       BEQ     20$                     ;  yes - no checking required
       CMMB    ACOL(A1),ACOL(A0)       ; are aliens at the same column?
       BNE     20$                     ;  no - branch
       CMMB    AROW(A1),AROW(A0)       ; is check-alien below curr. alien?
       BLE     20$                     ;  no - branch
       RTN                             ; return
20$:    ADD     #ASIZE,A1               ; advance to next record
       SOB     D1,10$                  ; loop till all aliens checked
       INCB    D4                      ; increment attack counter
       CMPB    D4,ATTCNT(MEM)          ; can we attack?
       BLT     30$                     ;  no - branch
       MOVB    AROW(A0),XROW(MEM)      ; set missile
       ADDB    #3,XROW(MEM)            ;  row
       MOVB    ACOL(A0),XCOL(MEM)      ;  and
       INCB    XCOL(MEM)               ;  column
       CALL    DRWATK                  ; draw missile
       CLRB    D4                      ; clear attack count
30$:    RTN                             ; return

;move attacking alien missile down screen
;to keep the missile from moving too rapidly, bit 0 of D3 is set and reset;
;only when bit 0 of D3 is one is the missile advanced
ATTMOV: BTST    #0,D3                   ; is bit 0 = 0?
       BEQ     10$                     ;  yes - branch
       BCLR    #0,D3                   ;  no - set bit zero on
       BR      20$                     ; branch
10$:    BSET    #0,D3                   ; set bit 0 on
       RTN                             ; return
20$:    CALL    CLRATK                  ; clear attack missile from screen
       INCB    XROW(MEM)               ; increment row
       CMMB    XROW(MEM),#22.          ; at bottom of screen?
       BGE     ATTEND                  ;  yes - branch
       CMMB    XROW(MEM),MROW(MEM)     ; collision with player missile?
       BNE     30$                     ;  no
       CMMB    XCOL(MEM),MCOL(MEM)     ; collision with player missile?
       BNE     30$                     ;  no
       CALL    COLLID                  ; handle collision
       RTN                             ; return
30$:    CALL    DRWATK                  ;  no - re-draw missile
       RTN                             ; return
ATTEND: SAVE    D2-D3                   ; save registers
       MOVB    POS(MEM),D2             ; load position of laser base
       MOV     D2,D3                   ; set D2 to left column
       DECB    D2                      ;  of laser base
       INCB    D3                      ; set D3 to right column of laser base
       CMMB    XCOL(MEM),D2            ; is alien missile to left of laser base?
       JLT     KILMSL                  ;  yes - branch
       CMMB    XCOL(MEM),D3            ; is alien missile to right of laser base?
       JGT     KILMSL                  ;  yes - branch
       TTYI                            ; ring
       BYTE    7,0                     ;  bell
       SUBB    #3,POS(MEM)             ; subtract 3 from position
       CURSOR  #23.,POS(MEM)           ; re-position cursor
       TYPE    < *ARG* >               ; print Aaargh!! message
       SLEEP   #2500.                  ; wait 1/4 second
       CURSOR  #23.,POS(MEM)           ; re-position cursor
       TYPE    < ..... >               ; type rubble
       SLEEP   #2500.                  ; wait 1/4 second
       CURSOR  #23.,POS(MEM)           ; re-position cursor
       TYPE    <       >               ; wipe out laser base
       SLEEP   #2500.                  ; wait 1/4 second
       TSTB    LIVES(MEM)              ; any lives left?
       BEQ     GAMOVR                  ;  nope - game over - branch
       SAVE    D0                      ; save D0
       CLR     D0                      ; load D0
       MOVB    LIVES(MEM),D0           ;  w/number of lives
       DECB    D0                      ; subtract by one
       MUL     D0,#4                   ; multiply by 4 to get column
       INCB    D0                      ; and add one
       CURSOR  #24.,D0                 ; position cursor
       TYPE    <   >                   ; and type spaces
       REST    D0                      ; restore D0
       DECB    LIVES(MEM)              ; decrement spare live count
       MOVB    #41.,POS(MEM)           ; re-set position to middle
       CALL    DRWLSR                  ; re-draw laser base
       CLRB    XROW(MEM)               ; erase alien attack missile
       REST    D2-D3                   ; restore registers
       RTN                             ; return

;Missile collision
;erase player and alien missile from screen

COLLID: CALL    CLRATK
       CLRB    XROW(MEM)
       CALL    CLRMSL
       CLRB    MROW(MEM)
       RTN

;Game over
GAMOVR: CURSOR  #1,#36.
       TYPE    Game Over
       JMP     FINISH

;mark alien missile as destroyed
KILMSL: CLRB    XROW(MEM)
       CLRB    XCOL(MEM)
       REST    D2-D3
       RTN


;Finish
;This routine cleans up a few things before exiting the program
;Control-C flag is cleared so display doesn't get messed up
;Cursor is turned back on
FINISH: JOBIDX  A0                      ; index Job Control Block
       ANDW    #^C<J.CCC>,JOBSTS(A0)   ; clear ^C flag if set
       CURSOR  #23.,#1                 ; address cursor
       ON                              ; turn on cursor
       CRLF                            ; print newline
       EXIT                            ; exit

;Draw Missile routine
;Draws player's missile on the screen
DRWMSL: CURSOR  MROW(MEM),MCOL(MEM)
       TYPE    !
       RTN

;Clear Missile routine
;Clears player's missile off the screen
CLRMSL: CURSOR  MROW(MEM),MCOL(MEM)
       TYPE    < >
       RTN

;Draw Laser base routine
;Draws player's laser base on the screen
DRWLSR: MOVB    POS(MEM),D7
       SUBB    #3,D7
       CURSOR  #23.,D7
       TYPE    <  _A_  >
       RTN

;Clear alien missile routine
;Clears alien missile from the screen
CLRATK: CURSOR  XROW(MEM),XCOL(MEM)
       TYPE    < >
       RTN

;Draw alien missile routine
;Draws alien missile on the screen
DRWATK: CURSOR  XROW(MEM),XCOL(MEM)
       TYPE    |
       RTN

;Clear saucer
CLRSAU: SAVE    D0                      ; save registers
       MOVB    SAUCER(MEM),D0
       DECB    D0
       CURSOR  #2,D0
       TYPE    <       >
       CLRB    SAUCER(MEM)             ; mark saucer as gone
       MOVW    #1000.,SAUCNT(MEM)      ; set 1000 cycles till next saucer
       REST    D0                      ; restore registers
       RTN

;Draw saucer
DRWSAU: SAVE    D0
       MOVB    SAUCER(MEM),D0
       DECB    D0
       CURSOR  #2,D0
       TTYI
       ASCIZ   " <***> "
       EVEN
       REST    D0
       RTN

;Clear alien from display.  The display space previously occupied by the
;alien is cleared to blanks and the alien's value is displayed for 1/10th
;of a second and then cleared as well.  A0 is expected to point to the
;alien data record in ADATA(MEM).
CLEAR:  SAVE    D2-D5                   ; save registers
       MOVB    AROW(A0),D2             ; copy alien row
       MOVB    ACOL(A0),D3             ; copy alien column
       DECB    D2                      ; subtract one
       DECB    D3                      ;  from each
       TTYI                            ; ring
       BYTE    7,0                     ;  bell
       CURSOR  D2,D3                   ; address cursor
       TYPE    <      >                ; print blank line
       INCB    D2                      ; next row
       CURSOR  D2,D3                   ; address cursor again
       TYPE    <      >                ; print blank line again
       INCB    D2                      ; next row
       CURSOR  D2,D3                   ; address cursor once more
       MOV     #4,D5                   ; load D5 w/4
       SUBB    ATYPE(A0),D5            ; subtract alien type from D5
       MUL     D5,#100.                ; multiply by 100 to get points
       MOV     D5,D1                   ; copy to D1 for output
       DCVT    5,OT$TRM!OT$ZER         ; print number of points
       TYPESP                          ; print a space
       SLEEP   #1000.                  ; wait 1/10 second
       CURSOR  D2,D3                   ; next row
       TYPE    <      >                ; print more spaces (alien now gone)
       ADD     D5,SCORE(MEM)           ; update score
       CALL    DISCOR                  ; display score
       CLRB    MROW(MEM)               ; cancel
       CLRB    MCOL(MEM)               ;  player missile
       CLRB    AROW(A0)                ; mark alien
       CLRB    ACOL(A0)                ;  as destroyed
       DECB    ACOUNT(MEM)             ; decrement live alien count
       REST    D2-D5                   ; restore registers
       RTN

;Draw alien.  ROW(MEM), COL(MEM), and TYPE(MEM) are expected to contain
;values for the currently selected alien.  ROW(MEM) and COL(MEM) are the
;coordinates of the upper left-hand part of the alien.  TYPE(MEM) determines
;the type of alien drawn.
DRAW:   SAVE    A0,D0-D3                ; save registers
       LEA     A0,PIX                  ; point A0 to picture data
       CLR     D0                      ; load D0
       MOVB    TYPE(MEM),D0            ;  with alien type
       MUL     D0,#24.                 ; multiply alien type by 2x6
       ADD     D0,A0                   ; A0 now points to proper alien
       MOVB    ROW(MEM),D2             ; copy row
       MOVB    COL(MEM),D3             ; copy column
       DECB    D2                      ; subtract one
       DECB    D3                      ;  from both
       CURSOR  D2,D3                   ; address cursor
       TYPE    <      >                ; print blank line above alien
       INCB    D2                      ; point D2 to next row
       BTST    #0,D3                   ; is this an even number column?
       BEQ     10$                     ;  yes - use version A of alien
       ADD     #12.,A0                 ;  no  - use version B of alien
10$:    CURSOR  D2,D3                   ; address cursor
       BCALL   PIXLIN                  ; print 1st line of alien picture
       INCB    D2                      ; advance to
       CURSOR  D2,D3                   ;  next row
       BCALL   PIXLIN                  ; print 2nd line of alien picture
       REST    A0,D0-D3                ; restore registers
       RTN                             ; return

;Display 6 characters of data @A0
PIXLIN: MOV     #6.,D0                  ; prepare for 6 iterations
10$:    MOVB    (A0)+,D1                ; get char, increment pointer
       TTY                             ; print char in D1
       SOB     D0,10$                  ; loop 6 times
       RTN                             ; return

;Display score at top right hand of screen
DISCOR: CURSOR  #1,#WIDTH-10.           ; address cursor
       MOV     SCORE(MEM),D1           ; load D1 w/score
       DCVT    9.,OT$TRM!OT$ZER        ; print score, right justified
       RTN                             ; return

;Alien pictures.  Each alien is 2x4 characters in size, plus spaces on the
;and right.  The spaces are there in case the alien has moved.
;There are two versions of each alien-- the picture changes slightly as the
;alien slides across the screen.  The type of alien drawn (there are four)
;depends on ATYPE(alien).
PIX:    ASCII   " (oo) "                ; type 0 alien
       ASCII   " -^^- "
       ASCII   " (oo) "
       ASCII   " _/\_ "
       ASCII   " v__v "                ; type 1 alien
       ASCII   " (oo) "
       ASCII   " v__v "
       ASCII   " (..) "
       ASCII   " #oo# "                ; type 2 alien
       ASCII   " <()> "
       ASCII   " #oo# "
       ASCII   " (<>) "
       ASCII   " o!!o "                ; type 3 alien
       ASCII   " <==> "
       ASCII   " o!!o "
       ASCII   " >==< "

;Message displayed on introduction screen - must be terminated w/NUL byte
;(ASCIZ does this).  A tilde character (~) is not displayed but instead
;causes a 1/3 second delay.
MESSAG: ASCIZ   /S P A C E ~ I N V A D E R S ~ b y   U L T R A S O F T ~~~~/
       EVEN

       END