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