Update README.
[pyrit.git] / pyrit.asm
1 ; Pyrit
2
3 ; a 256-byte intro by Rrrola <rrrola@gmail.com>
4
5 ; greets to everyone who's computer is too fast :)
6
7 ; This is loosely based on my intro 'Gem' (shown on Demobit),
8 ; but the code is much better.
9
10 ; Vector3: X right, Y down, Z forward.
11 ; On the FP stack it looks like {Y X Z} (Y is often used in comparisons).
12 ; In memory it looks like {Z X Y}, which saves a displacement byte.
13 ; (u'v) is the dot product: ux*vx + uy*vy + uz*vz.
14
15         org 0x7c00
16         xor ax,ax
17         xor bx,bx
18         mov cx,0ffh
19         mov di,-2
20 ;        mov ss,dx
21         mov sp,di
22         mov si,100h
23         mov bp,091ch
24
25 ; assume al=0 bx=0 sp=di=-2 si=0100h bp=09??h
26
27 ;Set video mode and earth+sky palette
28   dec di       ; u16[100h] = -20401, u16[10Ch] = -30515
29   mov al,13h
30   dec di       ; initial pixel_adr@di = -4
31
32 P:shr cl,1     ; B@cl = 0..8..31,31..0
33
34   int 10h      ; set video mode / color: bx=index dh=R ch=G cl=B
35
36   movsx cx,bl  ; 0..127,128..255 (palette index)
37   xor ch,cl    ; 0..127,127..0
38   mov cl,ch
39   mov ax,cx
40   mul ax       ; R@dh = 0..16..63,63..16..0
41
42   shr cx,1     ; G@ch = 0..63,63..0
43
44   inc bl       ; keep default color 0
45   js Q         ; R@dh = 0..63,63..16..0
46   xchg cl,dh   ; B@cl = 0..16..63,63..0
47 Q:mov ax,1010h
48   jnz P        ;bx=0 cx=0
49
50         ; Constants expected at a fixed address below.
51         mov ax,0b04fh
52         mov word[100h],ax
53         mov ax,04f13h
54         mov word[102h],ax
55         mov ax,0e9d0h
56         mov word[104h],ax
57         mov ax,010cdh
58         mov word[106h],ax
59         mov ax,0be0fh
60         mov word[108h],ax
61         mov ax,030cbh
62         mov word[10ah],ax
63         mov ax,088cdh
64         mov word[10ch],ax
65         mov ax,089e9h
66         mov word[10eh],ax
67
68 ;Each frame: Generate normals to p0..p11=[bp+200h,300h,...].
69 M:mov ax,0x4731 ; highest 9 bits: float32 exponent 1/256 (for T)
70                 ; lower byte = 2*number of rotations+1
71                 ; lowest 4 bits must be 0x1 for 'test cl,al'
72   mov dx,0xA000-10-20-20-4
73   mov es,dx    ; dx:bx = YX:XX = 0x9fca:0
74   pusha  ; adr:   -18 -16 -14 -12 -10  -8  -6  -4  -2
75          ; stack:  di  si  bp  sp  bx  dx  cx  ax   0
76          ; data:   -4 100 9??  -2  0  9fca {T/256}
77   mov cx,12
78 G:add bp,si    ; i@cx = 12...1; bp points to p[12-i]; carry=0
79   pusha
80
81 ;Generate 12 planes with unit normals.
82
83 ;  fld1         ; platonic dodecahedron: exact is atan((1+sqrt5)/2)=1.017rad
84   fld dword[di-2]    ;|t=T/256: morphing shape: cube, platonic12, rhombic12
85
86   fsincos
87
88   fldz               ;|a=0 b c (a*a+b*b+c*c = 1)
89 ;  fldlg2 ;irregular shape
90
91 N:test cl,al ;=1     ;|a b c
92   jnz K
93   fchs
94 K:fstp st3           ;|b c +-a (scramble so that all 12 planes are generated)
95   loop N  ;cl=0      ;|z x y
96
97 ;Do a bunch of slow rotations. z x y -> cx-sy cy+sx z
98
99 R:fstp st3           ;|x y z
100 Z:fld st1            ;|y x y z                     ;|x sy x cy z
101   fld dword[di-2]    ;|t=T/256
102   fsincos            ;|c=cos(t) s=sin(t) y x y z   ;|c s x sy x cy z
103   fmulp st4          ;|s y x cy z                  ;|s x sy cx cy z
104   fmulp              ;|sy x cy z                   ;|sx sy cx cy z
105   add al,0x7F ; loop 2x
106   jo Z
107   faddp st3          ;|sy cx cy+sx z
108   fsubp              ;|new.z=cx-sy .x=cy+sx .y=z
109   jc R       ; loop 24x
110
111 S:fstp dword[bp+si] ;[bp+100]=.z [bp+104]=.x [bp+108]=.y
112   sub si,di
113   jpo S
114
115   popa
116   loop G
117   popa
118
119 ; the visible pixels are A0000..AF9FF, I want X=0 Y=0 in the center
120 ;Each pixel: cx=T dx:bx=YX:XX(init=9fca:0) di=adr(init=-4)
121 X:inc dx       ; part of "dx:bx += 0x0000CCCD"
122 X2:
123   stosb
124
125   pusha        ; adr:     -18 -16 -14 -12 -10  -8  -6  -4  -2
126   fninit       ; stack:    di  si  bp  sp  bx  dx  cx  ax   0
127   mov bx,es    ; s16:  pixadr 100 9??  -2  ..X..Y  T result
128   mov di,-4 ;di = address of pushed ax
129
130 ;Compute ray direction.
131   fild word[BIG] ; store 28799 as a double, read as two floats
132   fst qword[bx]     ; t_front@float[bx] = 0, t_back@float[bx+4] = 6.879
133   fild word[di+4-9]
134   fild word[di+4-8]  ;|y=Y x=X z=BIG
135
136 ;Intersect the pyrite.
137   call GEM
138   popa         ; color -> pushed ax
139 ;  mov al,dl    ; show only palette
140
141 ;; Faster, but lower quality: draw each pixel twice.
142 ;  stosb
143 ;  add bx,0xCCCD; dx:bx = YXX += 0000CCCD
144 ;  adc dx,0
145
146   add bx,0xCCCD; dx:bx = YXX += 0000CCCD
147   jnc X2
148   jnz X        ; do 65536 pixels
149
150   in al,60h
151   dec ax  ; ah=0 (checkboard uses positive color indices)
152   loopnz M        ; T--
153 ;  ret          ; fallthrough
154
155 GEM:
156 ;Hit the pyrite.
157   xchg ax,cx   ; ax = T
158
159 ; Faster (+4 or +8 bytes): test the shape only in the center of the screen
160   add dh,dh
161   jo B
162   add dl,dl
163   jo B
164
165 ;Ray-plane intersection.
166 ;Find the front plane with maximum t and back plane with minimum t.
167 ; tf@[bx],    tb@[bx+4]      ray parameter t
168 ; pf@[bx+si], pb@[bx+4+si]   pointer to plane
169   mov cx,12  ; i@cx = 12...1
170 I:add bp,si    ; bp points to p[i]
171   fldlg2             ;|pd=0.301 y x z
172   fadd dword[bp+si]  ;|N=pd-(ro'p[i]) y x z  ; ro = 0 0 -1
173
174   push si      ; Dot product:
175 D:fld dword[bp+si]   ;|p[i].z ...
176   fmul st4           ;|rd.z*p[i].z ...
177   sub si,di    ; 100 104 108
178   jpo D              ;|(rd*p[i]).y .x .z N rd.y .x .z
179   pop si
180   faddp
181   faddp              ;|D=(rd'p[i]) N y x z
182
183 ;If we hit the plane from the front (D<0), update tf. Otherwise update tb.
184   push bx
185   fst dword[bp+di]; -> p[i].dot_rd (will be read later)
186   test [bp+di+2],sp ; sf=1 if we're in front of the plane
187   js FRONT
188   sub bx,di    ; bx = address of tf?tb
189 FRONT:         ; D<0:  if tf*D < N { tf=N/D; pf=current; }  maximalize tf
190   fld st0      ; D>=0: if tb*D < N { tb=N/D; pb=current; }  minimalize tb
191   fmul dword[bx]     ;|(tf?tb)*D D N y x z
192
193 ;;DosBOX-compatible FPU comparison, +5 bytes (+3 but we need ax)
194 ;  push ax
195 ;  fcomp st2          ;|D N y x z
196 ;  fnstsw ax
197 ;  sahf         ; cf = (tf?tb)*D < N
198 ;  pop ax
199 ;  jc NEXT
200
201   fcomip st2
202   jc NEXT
203
204 ;another alternative, +6 bytes
205 ;  fsub st2
206 ;  fstp dword[bp-8]
207 ;  test [bp-6],sp ; sf=1 if <0
208 ;  js NEXT
209
210
211   fdivr st1          ;|t=N/D N y x z
212   fst dword[bx] ; -> tf?tb
213   mov [bx+si],bp ; pf?pb = current
214 NEXT:
215   fcompp
216   pop bx             ;|y x z
217
218   mov dx,[bx+6]
219   cmp dx,[bx+2]  ; if tf>tb { no_hit: early exit }
220   jng B     ;si=100   ;|y x z
221
222   loop I
223
224 ;Reflect: reflect(i,n) = i - 2*n*(i'n)
225   mov bx,[bx+si] ; pf
226 Y:fld dword[bx+di]   ;|(rd'pf) rd.y .x .z  ; reads pf->dot_rd
227   fmul dword[bx+si]  ;|(rd'pf)*pf.z rd.y .x .z
228   fadd st0           ;|2*(rd'pf)*pf.z rd.y .x .z
229   fsubr st3          ;|R.z=rd.z-2*(rd'pf)*pf.z rd.y .x .z
230   sub si,di   ;100 104 108
231   jpo Y     ;si=10C  ;|(R=i-2*n(i'n)).y R.x R.z rd.y .x .z
232
233 ;Environment map: chessboard below, sky gradient above.
234 B:
235 ; Subtle highlight on the pyrite.
236   fld st0
237   fimul word[C]  ; 16993 (background) or 20036 (pyrit)
238   fistp dword[di]     ;|y x z
239   sar dword[di],22    ; if y>=-0.5 { chessboard } else { sky }
240   js E             ; the sky is just y (= y^2 after gamma)
241
242 ; Everything the same brightness. (-6 bytes)
243 ;  fist word[di]      ;|y x z
244 ;  sar word[di],8  ; if y>=-0.5 { chessboard } else { sky }
245 ;  js E            ; the sky is just y (= y^2 after gamma)
246
247 ; Dark background version.
248 ;  fist word[di]      ;|y x z
249 ;  shld cx,si,16-3
250 ;  xor cl,9        ; hit?8:9 - make the background darker
251 ;  sar word[di],cl ; if y>=-0.5 { chessboard } else { sky }
252 ;  js E            ; the sky is just y (= y^2 after gamma)
253
254   fidivr word[si]    ;|C/y x z (C = hit?-30515:-20401)
255   fmul st1,st0
256   fmul st2           ;|u=z*C/y v=x*C/y z
257
258   fistp dword[bp+di]
259   sub al,[bp+di+1]
260   fistp dword[bp+di]
261   xor al,[bp+di+1] ; xortex@ax = (T-u) XOR v
262
263 ;  aam -32-24     ; more interesting floor texture
264   and al,9<<3
265   add al,10<<3    ; tex = (xortex AND 0b1001) + 10 [10|11|18|19]
266   mul byte[di]
267   mov [di],ah     ; pushed al = tex*y
268
269 E:ret
270
271 BIG     dw 28799
272 C       dw 16993
273 C2      dw 20036
274
275         times 510-($-$$) db 0
276         db 0x55,0xaa