COLLISION

From C64-Wiki
Jump to navigationJump to search
BASIC keyword
Keyword: COLLISION
Abbreviation: C, O SHIFT+L
Type: Function
Token code: $fe $17 (254 23)
Handling routine
in BASIC ROM:
List of all BASIC keywords


Remark: This article describes the BASIC function COLLISION in Commodore BASIC V7.0 or higher.

Type: Function
General Programming-Syntax: COLLISION <type> [,<line>]

The COLLISION function defines sprite collision interrupt handling. If the selected type collision happens the program jumps with the subroutine like GOSUB specified by the to specified line. Different collision handlers can be specified.

The parameters are

  • <type>: Valid values for type are:
    • 1: which handles sprite to sprite collision,
    • 2: which handles sprite to background collision
    • 3: which handles lightpen pulses
Other values results in a ?ILLEGAL QUANTITY ERROR.
If line is omitted then the collision handler is switched off.
  • <line>: denotes the start of the collision routine. Valid values range from 0 to 65535. Even values greater or equal 64000 do not make sense because such lines could not be created (maximum line number is 63399).
    In case this parameter is omitted the collision handling for the associated source is switched off. Although the parameter could be any valid expression it is recommended only to use a constant number, to ensure a RENUMBER is able to consider and correct the destination line number accordingly.

If the collision actually happens the current executed BASIC command is finished. If the line number of the collision routine does not exist the program stops with message ?UNDEF'D STATEMENT ERROR IN <line>, with <line> shows the last line which has been processed.
If another collision handling is requested during execution of collision routine then this is will be backed-off until the routine has been finished - there is no nesting.
Concurrent collision request are handled in the ascending order of the collision source number.

Notes:

  • To get a quick response it is recommended to place the routine on the beginning of the BASIC program. Not to mention, that the routine should be as short and efficient as possible. Interactive interactions must not be used.
  • It is very likely that whilst in the collision handling routine the same collision is requested again. The routine has to take precautions to be aware and cover this situation.
  • There is a race-condition during disarming a collision handler type: Internally the line number is set to zero. If a collision of this type occurs during this COLLISION execution the routine is called anyway which targets line 0. If this line does not exist the program exists with a ?UNDEF'D STATEMENT ERROR IN <line> message. With an existing line 0 the program could take a weird path of execution which is probably not easy to track. There are several approaches to tackle this:
    1. Ensure the occurrence of a collision of the specific type before unarming the collision handler (e.g. by disabling sprites).
    2. Catch the the error ?UNDEF'D STATEMENT ERROR with a TRAP routine.
    3. Define a line number 0 with a flag variable which provides a null handler in case it is not entered on program start:
      0 IF XX THEN RETURN:ELSE XX=1:GOTO 1000
  • If the program is interrupted by hitting RUN/STOP  or command STOP a continuation has the consequence of disarming all collision handlers.
  • COLLISION could be called in direct mode which has no effect at all.

Internals[edit | edit source]

COLLISION uses following RAM locations:

4726 ($1276) flag (byte) for sprite-to-sprite collision
4727 ($1277) flag (byte) for sprite-to-background collision
4728 ($1278) flag (byte) for lightpen pulse
4729-4731 ($1279-$127B) destination lines low byte
4732-4734 ($127C-$127E) destination lines high byte
4735 ($127F) flag (bit 7) for collision in progress

The main raster interrupt routine looks up the VIC IRQ register (offset 25, address $D019) and placing the value 255 ($FF) the corresponding source flag mentioned above.

The main interpreter loop checks right before handling the next statement if one of the three collision flag is set. For every flag set the value is reset to 0, bit 7 at location 4735 ($127F) is set to mark that the collision handling is in progress and the handler line is called with GOSUB. After returning from the routine (past RETURN) the previously set bit 7 will be reset.


See also[edit | edit source]

Another sprite commands in BASIC 7.0 are RSPCOLOR, RSPPOS, RSPRITE, SPRCOLOR, SPRITE, SPRDEF and SPRSAV, also BUMP, GSHAPE and SSHAPE.


Examples[edit | edit source]

Simple[edit | edit source]

100 COLLISION 1,1000

The programme branches to line 1000 as soon as at least 2 sprites collide with each other.

200 COLLISION 3

Switches off the handling of lightpen pulses.

Complex[edit | edit source]

A small game: Get a spaceship (a rotated square) through moving balls.

0 IF XX THEN RETURN: ELSE XX=1:GOTO 150: REM XX<>0 IF SPURIOUS COLLISIONS OCCURS
20 B=BUMP(2): IF B=0 THEN RETURN: REM BACK IF NOT MATCHING
30 DO
40 FOR I=1 TO 7
50 IF B AND BM(I) THEN BEGIN
60 Y=RSPPOS(I,1): IF Y<99 THEN MOVSPR I,180#SP(I): MOVSPR I,+0,60: ELSE MOVSPR I,0#SP(I): MOVSPR I,+0,218
70 BEND
80 NEXT
90 GET K$: IN=INSTR(I$,K$): IF IN THEN MOVSPR 8,-(DX(IN)),-(DY(IN)): IF RSPPOS(8,0)<24 THEN GS=2: EXIT
100 B=BUMP(2) AND NOT B: REM ONLY HANDLE NEW SPRITE COLLISIONS
110 LOOP WHILE B
120 RETURN
130 GS=1: REM GAME STATE = GAME OVER
140 RETURN
150 REM INITIALIZING SPRITES AND VARIABLES
155 XX=1
160 GRAPHIC 1,1: CIRCLE 1,12,10,5: PAINT 1,12,10: SSHAPE S$,0,0,23,20
170 BOX 1,27,5,37,15,45: SSHAPE R$,24,0,47,20: SPRSAV R$,8
180 I$="{LEFT}{RIGHT}{UP}{DOWN}": DIM DX(4),DY(4): DX(1)=5: DX(2)=-5: DY(3)=5: DY(4)=-5
190 DIM BM(8),SP(8): BM=1
200 FOR I=1 TO 7: BM(I)=BM: BM=BM2*2: SP(I)=1+(I AND 3): SPRSAV S$,I: NEXT
210 DO: REM SETUP GRAPHICS AND ENABLE SPRITES
220 SCNCLR 1: WIDTH 1: COLOR 1,1
230 BOX 1,0,0,319,12,0,1:BOX 1,0,187,319,199,0,1
240 FOR I=1 TO 7: MOVSPR I,40*I+5,200: MOVSPR I,A(I)#SP(I): SPRITE I,1,I,1: NEXT
250 MOVSPR 8,320,150: SPRITE 8,1,1,0: REM ACTIVATE SPACESHIP
260 B=BUMP(2): B=0: REM REMOVE OLD COLLISIONS
270 GS=0
280 COLLISION 1,130: REM SPRITE-TO-SPRITE COLLISIONS
290 COLLISION 2,20: REM SPRITE-TO-BACKGROUND COLLISIONS
300 REM MAIN PART
310 DO
320 GET K$: IN=INSTR(I$,K$): IF IN THEN MOVSPR 8,-(DX(IN)),-(DY(IN))
330 IF RSPPOS(8,0)<24 THEN GS=2: EXIT: REM GS (GAME STATE) = WIN
340 LOOP UNTIL GS
350 REM DISABLE SPRITES
360 COLLISION 1: COLLISION 2
370 FOR I=1 TO 8: SPRITE I,0: MOVSPR I,0#0: NEXT
380 IF GS=1 THEN CHAR 1,18,8,"GAME": CHAR 1,18,10,"OVER!": ELSE CHAR 1,15,8,"SUCCEEDED!"
390 CHAR 1,10,13,"PLAY AGAIN (Y/N)?"
400 DO: GETKEY K$: LOOP UNTIL K$="Y" OR K$="N"
410 LOOP WHILE K$="Y"
420 GRAPHIC 0

Alarm function/BASIC background task processing[edit | edit source]

A BASIC program basically runs as on thread of execution. With COLLISION and a self-moving sprite a timed routine could be constructed. This routine could implement some alarm functionality or process some background-task which is processed asynchronous and parallel to the main program's execution. Caveat: Since a the collision handler is activated after a completion of a command a currently running INPUT statement could block the background processing indefinitely. Therefore it is not possible to impose any timeout for such input situation.

The following program consists of a main input loop which is terminated as soon as the alarm triggers. Any input resets the alarm timer. In case of an alarm just a flag is set which is checked in the input loop. The alarm function might consists of some elaborate code (changes on the screen, like the example "background clock" below). In such cases, sensitive display states (such as the cursor position) must be retained to prevent any form of screen corruption.

In the event of a timeout the program ends and shows the elapsed time.

 100 GOTO 1000 START
 110 S1=1: S2=2: VI=51*1: REM 0/1 INVISIBLE/VISIBLE
 120 GRAPHIC 1,1:DRAW 1,0,0: REM SPRITE IMAGE (SINGLE PIXEL)
 130 SSHAPE A$,0,0,23,20: REM FROM BITMAP ...
 140 SPRSAV A$,S1:SPRSAV A$,S2:GRAPHIC 0: REM ... TO SPRITES 
 150 SPRITE S1,1,RCLR(0)-(VI>0),0,0,0,0: REM BACKGROUND COLOR
 160 SPRITE S2,1,RCLR(0)-(VI>0),0,0,0,0
 170 MOVSPR S1,24,VI: REM VI FROM 50 ON IS VISIBLE
 180 MOVSPR S2,24+TT*25,VI
 190 MOVSPR S1,90#1: REM 1 = 1/25 S PER PIXEL
 200 COLLISION S1,500
 210 RETURN
 220 :
 230 COLLISION S1
 240 MOVSPR S1,0#0: SPRITE S1,0: SPRITE S2,0
 250 RETURN
 498 :
 499 REM HINTERGRUNDAKTION
 500 GOSUB 230 DEACTIVATE ALARM
 510 AL=1: REM ALARMING FLAG
 599 RETURN
 999 :
1000 REM TIMEOUT TT: >0 BIS 13
1010 TT=5: GOSUB 110: TI$="000000"
1020 PRINT CHR$(147)CHR$(17)CHR$(17)CHR$(17)"PLEASE INPUT..."
1030 PRINT "TIMEOUT ="TT"SECS"
1040 DO
1050 GET A$: PRINT A$".";
1060 IF A$<>"" THEN TI$="000000": GOSUB 170 RESET ALARM
1070 IF AL THEN PRINT: PRINT"TIMEOUT "TI$" S,"TI"TICKS": END
1080 LOOP
  • Main entry points:
    • 110: Initialize alarm environment and setup alarm time from variable TT
    • 170: Reactivate alarm according to time from variable TT
    • 230: Deactivate alarm
    • 500: Alarm routine
    • 1000: Main program
  • Parameters:
    • 110: Assignment of 1 to VI makes the sprites visible. A 1×1 pixel sprite is moved 2 pixel rows above the upper frame border.
    • 190: The MOVSPR command influences the speed. #1 corresponds to 1/25 secs/pixel, #2 to 1/50. A greater speed parameter leads to a smaller maximum possible alarm time (which is limited only by the maximum X position of a sprite).
  • Used variables:
    • S1, S2: sprite numbers
    • VI: vertical position of sprites
    • A$: temporary: sprite image data
  • Parameter variables:
    • TT: timeout value in seconds, > 0, with 1/25 resolution (even a real number possible)
  • Application variables:
    • AL: flag, equal 1 if alarm has been triggered.
    • A$: pressed key


Variation "Background Clock":

Replacing the part starting from 499 with the following code gives a different behavior: During the input the current time derived from TI$ will be displayed in the right upper corner on the screen (with a one-second refresh interval).

 499 REM BACKGROUND ACTION
 500 GOSUB 170 NEW ALARM
 510 FOR I=1 TO 6: POKE 1056+I,ASC(MID$(TI$,I,1)): NEXT
 599 RETURN
 999 :
1000 REM TIMEOUT TT: >0 UP TO 13
1010 TT=1: GOSUB 110
1020 PRINT CHR$(147)CHR$(17)CHR$(17)CHR$(17)"PLEASE INPUT..."
1030 DO
1040 GET A$: PRINT A$;
1050 LOOP
BASIC V7.0 Commands

ABS | AND | APPEND | ASC | ATN | AUTO | BACKUP | BANK | BEGIN | BEND | BLOAD | BOOT | BOX | BSAVE | BUMP | CATALOG | CHAR | CHR$ | CIRCLE | CLOSE | CLR | CMD | COLLECT | COLLISION | COLOR | CONCAT | CONT | COPY | COS | DATA | DCLEAR | DCLOSE | DEC | DEF FN | DELETE | DIM | DIRECTORY | DLOAD | DO | DOPEN | DRAW | DS | DS$ | DSAVE | DVERIFY | EL | ELSE | END | ENVELOPE | ER | ERR$ | EXIT | EXP | FAST | FETCH | FILTER | FN | FOR | FRE | GET | GET# | GETKEY | GO64 | GOSUB | GOTO | GRAPHIC | GSHAPE | HEADER | HELP | HEX$ | IF | INPUT | INPUT# | INSTR | INT | JOY | KEY | LEFT$ | LEN | LET | LIST | LOAD | LOCATE | LOG | LOOP | MID$ | MONITOR | MOVSPR | NEW | NEXT | NOT | (OFF) | ON | OPEN | OR | PAINT | PEEK | PEN | (PI) | PLAY | POINTER | POKE | POS | POT | PRINT | PRINT USING | PRINT# | PUDEF | (QUIT) | RCLR | RDOT | READ | RECORD | REM | RENAME | RENUMBER | RESTORE | RESUME | RETURN | RGR | RIGHT$ | RND | RREG | RSPCOLOR | RSPPOS | RSPRITE | RUN | RWINDOW | SAVE | SCALE | SCNCLR | SCRATCH | SGN | SIN | SLEEP | SLOW | SOUND | SPC( | SPRCOLOR | SPRDEF | SPRITE | SPRSAV | SQR | SSHAPE | ST | STASH | STEP | STOP | STR$ | SWAP | SYS | TAB( | TAN | TEMPO | THEN | TI | TI$ | TO | TRAP | TROFF | TRON | USR | VAL | VERIFY | VOL | WAIT | WHILE | WINDOW | WIDTH | XOR