home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
The Party 1994: Try This At Home
/
disk_image.bin
/
source
/
gallery
/
a_rays.asm
< prev
next >
Wrap
Assembly Source File
|
1994-06-14
|
12KB
|
418 lines
; A_RAYS.ASM -- Ray tracer // A.R-M. 7/93
; Ported from original TP6.0 assembler to TASM "not-so-" Ideal
; This is the heart of the whole thing.
; (c) 1993, ARM. All rights reserved.
; Protected by Federal Law.
; Violators will be prosecuted.
; Trespassers will be shot.
; Keep off the grass.
; Wet paint.
; No U turn.
; Speed limit 55 MPH.
IDEAL
MODEL Compact, Pascal
RADIX 16
P286
INCLUDE "a_ray_t.inc" ; include SRay type def
; slope data structure
STRUC SSlope
DistFactor DW ?
Slope DW ?
ENDS SSlope
; sector data structure
STRUC SSector
Along DW ?
Across DW ?
AcrossWall DB ?
AlongWall DB ?
hit DB ?
DB ? ; makes length 8 bytes
ENDS SSector
; * MAP SIZE *
mps = 64d ; 64 x 64 map
IF (mps NE 64d)
IF (mps NE 128d)
Display "A_RAYS.ASM: mps invalid (only 64d or 128d supported)."
ERR
ENDIF
ENDIF
DATASEG
PUBLIC Map, NumberOfBearings ; might want to play with map from outside!
Map:
HERE = $
%NOLIST
RADIX 16
INCLUDE "data\mapdata.inc" ; Map (mpsxmps byte map)
%LIST
; quick check on mapdata.inc file:
IF $-HERE NE mps*mps
Display "A_RAYS.ASM: mapdata.inc size does not match mps value!"
ERR
ENDIF
; NumberOfBearings and SlopeData defined in slopes.inc
HERE = $
%NOLIST
RADIX 10
INCLUDE "data\slopes.inc"
%LIST
; more checks:
IFNDEF NumberOfBearings
Display "A_RAYS.ASM: slopes.inc does not define NumberOfBearings : Word"
ERR
ENDIF
IFNDEF SlopeData
Display "A_RAYS.ASM: slopes.inc does not define SlopeData"
ERR
ENDIF
; SectorData. Increments & hit coords for the 8 45° sectors:
SectorData:
SSector < +mps, + 1, 3,0, 00b > ; sector 0
SSector < + 1, +mps, 0,3, 00b > ; 1
SSector < - 1, +mps, 0,1, 01b > ; 2
SSector < +mps, - 1, 1,0, 10b > ; 3
SSector < -mps, - 1, 1,2, 11b > ; 4
SSector < - 1, -mps, 2,1, 11b > ; 5
SSector < + 1, -mps, 2,3, 10b > ; 6
SSector < -mps, + 1, 3,2, 01b > ; 7
RADIX 16
CODESEG
PUBLIC ShootRay ;(var Ray : SRay ):byte. Shoots Ray till
; first hit w/ a wall. Returns map array
; byte at that point.
;NOTE: Shoots ray from inRay. Returns:
; - impact location and path length
; in outRay.MapX,MapY,FineX,FineY,Length.
; - map contents at hit in AL
; - wall side in AH (0=S, 1=W, 2=N, 3=E)
; - wall side hit offset (0..32768) in DX
MACRO SubFrom1 r ; calculates 32768-Rx
P386
or r&x,1 ;; "neg Rx, and Rh,7f" trick doesn't
neg r&x ;; with Rx=0.
and r&h,7fh
P286
ENDM
; I'm sure no one would care to try to crack this code,
; but in case someone does let's have some fun:
db 'Polygon list too long'
; That ought to throw 'em way off track... }:-DDD
PROC ShootRay NEAR
ARG inRay : NEAR PTR SRay, outRay : NEAR PTR SRay
LOCAL DistanceFactor : Word, X0 : Word, \
HitOfs : Word, Walls : Word, Contents : Byte
pusha
; Those [es:di+SRay.Angle] & the like below were the only way I
; could figure out to get the darn things to assemble, should've
; been "SRay ptr [es:di].Angle" like in good ol' TP6.0's ASM :-(
mov di, [inRay]
mov si, [outRay]
mov dx, [di+SRay.Angle] ; dx = angle offset
mov cx, [di+SRay.Sector] ; cl = sector; ch = 0
and cl, 7 ; (take mod 8)
; copy constant values from inRay to outRay
mov [si+SRay.Angle], dx
mov [si+SRay.Sector], cx
mov ax,[di+SRay.length]
mov [si+SRay.length], ax
P386
xor ax, ax
bts ax, cx
mov ch, al ; ch = bit-mapped sector
P286
test cl, 1 ; sector no. odd?
jz @@skipodd
neg dx ; if odd, offset=NumberOfBearings-offset
add dx, [NumberOfBearings]
@@skipodd:
; └── here ch:cl=sector; dx = corrected bearing
shl dx, 2 ; dx <- dx * sizeof SlopeData
mov si, offset SlopeData
add si, dx ; ds:si -> SlopeArray[offset]
mov ax, [si+SSlope.DistFactor]
mov [DistanceFactor], ax ; save DistFactor for later
mov bx, [si+SSlope.Slope] ; bx = slope
; └── here ch:cl=sector; bx=slope, "distancefactor"
mov ah, [di+SRay.MapY]
xor al, al
IF mps EQ 128d ; 128x128 map:
shr ax, 1 ; ax = 128*MapY
ENDIF
IF mps EQ 64d ; 64x64 map:
shr ax, 2 ; ax = 64*MapY
ENDIF
mov dl, [di+SRay.MapX]
xor dh, dh
add ax, dx ; ax = mps*MapY + MapX
add ax, offset Map
mov si, ax ; ds:si -> Map[MapY,MapX]
; └── here ch:cl=sector; bx = slope; ds:si->MapContents
; load map coordinates:
mov dx, [di+SRay.FineX] ; dx = FineX
mov ax, [di+SRay.FineY] ; ax = FineY
; swap FX <-> FY for sectors 1, 2, 5, and 6
test ch, 01100110b ; sector bit in 1,2,5,6 ?
jz @@skipswitch
xchg ax, dx ; ...if so, swap
@@skipswitch:
; └── here ch:cl=sector; ds:si->Map; ax=across; dx=along; bx=slope
; NOTE: no test is made for walls at observer's position [MapY,MapX]
; * calculate initial step to first border *
; dx = FX
mov [X0], dx ; save initial X0
test ch, 10000111b ; sectors 0,1,2,7 ?
jz @@skipPreSubX
SubFrom1 d ; dx = 1 - dx
@@skipPreSubX:
mov di, ax ; save "across"
mov ax, bx ; ax = slope
mul dx ; dx:ax = increment*32768
shl ax,1
rol dx,1 ; dx = increment
mov ax, di
test ch, 10110100b ; sectors 4,5,2,7 ?
jz @@add
@@subtract:
sub ax, dx
jmp @@continue
@@add:
add ax, dx
@@continue:
; └── here ch:cl=sector; ds:si->Map; ax=across; bx=slope
; * load registers to enter ray-tracing loop *
mov di, offset SectorData
mov dl, cl
xor dh, dh ; dx = sector
shl dx,3
add di, dx ; di <- di + 8*sector
mov dx, [word ptr di+SSector.AcrossWall]
mov [Walls], dx
mov cl, [di+SSector.hit]
mov dx, [di+SSector.along]
mov di, [di+SSector.across]
xchg bx, di ; bx = SectorData.across; di = slope
test ch, 10110100b
jz @@skipNegativeSlope
neg di ; sectors 4,5,2,7 have negative slope
@@skipNegativeSlope:
; └── here ch=sector; ds:si->Map; ax=across; di=slope;
; cl=().hit; bx=().across; dx=().along
; ** RAY-TRACING LOOP **
; Upon entry:
; ds:si -> MapContents[MapY,MapX]
; ax = FineY or FineX ("across" coord)
; di = slope ("across" increment)
; bx = map increment for "across" step
; dx = map increment for "along" step
; ch = sector (bit-mapped)
; cl bit 0 = "across" hit coord (0 or 1)
; cl bit 1 = "along" hit coord (0 or 1)
PUSH CX ; save bit-mapped sector byte
xor ch, ch ; ch will be our counter now
inc ch
@@RayLoop:
test ah,80 ; FY <0 or >32767 ?
jz @@skip
and ah, 7f ; ... if so, reset FY...
add si, dx ; ... and update map ptr
mov cl, [si]
or cl, cl ; anything along our path ?
jnz @@HitX
@@skip:
add si, bx
mov cl, [si]
or cl, cl ; how about across out path ?
jnz @@HitY
add ax, di ; update "across" coord
inc ch
jmp @@RayLoop
@@HitY: ; "across" (normal) hit
POP BX ; retrieve bit-mapped sector info
xor dx, dx
shr bl, 2
rcr dx, 1 ; dx = "along" coord = 0 or 32768
mov [HitOfs], ax ; ax = "across" coord
jmp @@leave
@@HitX: ; "along" (overflow) hit
mov bx, [Walls]
xchg bl,bh
mov [Walls], bx ; signal which wall was hit
; ax = FY
POP BX
test bh, 10110100b ; sectors 2,7,4,5 ?
jz @@noPreSub
neg di ; (these sectors had negative slope)
SubFrom1 a ; ...if so, "presubtract": ax = 1 - FY
;neg ax
;and ah,7f
@@noPreSub:
mov dx, ax
xor ax, ax ; dx:ax = 65536 * ax
shr dx,1
rcr ax, 1 ; dx:ax = 32768 * ax
div di ; ax = (32768*ax)/slope
test bh, 10000111b ; sectors 0,1,2,7 ?
jz @@noPostSub
SubFrom1 a ; ...if so, "postsubtract": ax = 1 - ax
;neg ax
;and ah,7f
dec ch
@@noPostSub:
mov dx, ax ; result is "along" coord value for hit
mov [HitOfs], dx ; save it!
xor ax, ax
shr bl, 1
rcr ax, 1 ; ax = "across" coord = 0 or 32768
@@leave:
mov [Contents], cl ; save cl = Map[MapY,MapX] of hit!
test bh, 01111000b ; sectors 3,6,4,5 ?
jz @@grows
@@shrinks:
mov di, [X0]
sub di, dx
test bl, 1
jz @@continue2
dec ch
jmp @@continue2
@@grows:
mov di, dx
sub di, [X0]
@@continue2:
sar di, 7 ; di = (Xfinal-X0)/128 (32768/128=256)
xor cl, cl ; cx = 256 * #steps
add cx, di ; cx = EndX - StartX
test bh, 01100110b ; did we switch FX <-> FY ?
jz @@skipswitch2
xchg ax, dx
@@skipswitch2:
; here ds:si points to map coords of hit and ax=FY, dx=FX
mov di, [outRay]
mov [di+SRay.FineX], dx ; save coords
mov [di+SRay.FineY], ax
mov ax, si
sub ax, offset Map
IF mps EQ 128d
shl ax, 1 ; AH = MapY = ofs div 128
shr al, 1 ; AL = MapX = ofs mod 128
ENDIF
IF mps EQ 64d
mov bl, al
shl ax, 2 ; AH = MapY = ofs div 64
mov al, bl
and al, 3f ; AL = MapX = ofs mod 64
ENDIF
mov [di+SRay.MapX], al
mov [di+SRay.MapY], ah
mov ax, cx
mul [DistanceFactor] ; dx:ax = 32768*distance
shl ax,1
rcl dx, 1 ; dx = distance (in 1/256 units)
add [di+SRay.Length], dx
@@Exit:
P286
popa
mov al, [Contents] ; al = return map contents
mov ah, [byte ptr Walls] ; ah = side of wall which was hit
mov dx, [HitOfs] ; dx = hit offset along wall
test ah, 02
jz @@skipMirror ; wall sides 2 & 3 run against
SubFrom1 d ; coord direction, dx = 32768-HitOfs
@@skipMirror:
ret
ENDP
END