version 0.8: pickups, enemy improvements, invulnerability
[nemesis.git] / nemesis.z80
1         .include "asm86.h"
2         .include "ti86asm.inc"
3
4         .org _asm_exec_ram
5
6 TEXT_MEM = _textShadow
7
8         nop
9         jp  init
10         .dw $0001               ;description type 2 (= +YASicon)
11         .dw Title               ;pointer to description
12         .dw spr_ship            ;pointer to YAS icon
13
14 Title:  .db "Nemesis v0.8.93 by Shiar",0
15
16 just_fired      = TEXT_MEM      ;byte
17 temp1           = TEXT_MEM+1    ;word
18 RanPos          = TEXT_MEM+3    ;byte
19
20 ;---------------------- init --------------------------------------------------
21
22 init:
23         call _runindicoff       ;turn the run-indicator off, obviously
24         call _clrLCD            ;clean the screen
25
26         ld  a,(CONTRAST)        ;load current contrast level
27         cp  $1f                 ;if already at maximum...
28         jr  z,skipdarken        ;...then skip level increase
29         inc a                   ;otherwise increase contrast level
30 skipdarken:
31         out (2),a               ;set it
32
33 ;---------------------- main menu ---------------------------------------------
34
35 LogoPut:
36         ld hl,logo_nemesis      ;from...
37         ld de,VIDEO_MEM+16      ;...to one line from top
38         ld a,19                 ;19 rows
39 LogoLoop:
40         ld bc,16                ;set screen width
41         ldir                    ;display one line
42         dec a                   ;decrease line-counter
43         jr nz,LogoLoop          ;repeat when counter is not yet zero
44
45 menutext:
46         ld  hl,$1608            ;just below logo
47         ld  (_penCol),hl
48         ld  hl,txt_about        ;display "by Shiar (ICQ#43840958)"
49         call _vputs
50
51         ld  hl,$0705            ;located one row above bottom
52         ld  (_curRow),hl        ;go there
53         ld  hl,txt_1player      ;display "ONE PLAYER"
54         call _puts
55         ld  hl,$0706            ;below oneplayer text
56         ld  (_curRow),hl
57         ld  hl,txt_2players     ;display "TWO PLAYERS"
58         call _puts
59
60         call _getkey            ;wait for keypress
61         call New_level          ;prepare level
62
63 ;------------------------------------------------------------------------------
64 ;---------------------- game loop ---------------------------------------------
65 ;------------------------------------------------------------------------------
66
67 game_main_loop:
68         ld  hl,timer            ;update time
69         inc (hl)
70
71 Clear_screen:
72         xor a                   ;empty bitmask
73         ld  hl,GRAPH_MEM        ;screen location (top left)
74         ld  b,$E0               ;loop 0E0h = 224 times = 256-32 for score-bar)
75 clearloop:
76         ld  (hl),a              ;clear four times (total = 224*4 = 896 bytes)
77         inc hl
78         ld  (hl),a
79         inc hl
80         ld  (hl),a
81         inc hl
82         ld  (hl),a
83         inc hl
84         djnz clearloop          ;repeat 224x
85
86 check_exitkey:
87         ld  a,%00111111         ;<exit> pressed?
88         out (1),a
89         nop \ nop
90         in  a,(1)
91         bit 6,a                 ;test bit 6 = <EXIT>
92         jr  z,quit              ;yes: quit game
93
94 game_stuff:
95         call Level_event        ;insert enemies
96         call Handle_Ship        ;move you
97         call Fire_bullet        ;check for fire
98         call Handle_enemies     ;move enemies
99         call Handle_bullets     ;move your bullets
100         call Enemy_bullets      ;move enemy bullets
101         call Enemies_hit        ;check for collision with enemies
102
103         call Display_Screen     ;display all
104 ;       halt \ halt             ;delay
105         jr   game_main_loop     ;loop
106
107 ;--------------------------- exit ---------------------------------------------
108
109 quit:
110         ld  a,(CONTRAST)        ;load original contrast level
111         out (2),a               ;and set it back
112         ret                     ;quit Nemesis :(
113
114 ;--------------------------- display ------------------------------------------
115
116 Display_Screen:
117         ld  hl,GRAPH_MEM        ;from storage (top left)
118         ld  de,VIDEO_MEM        ;to screen (top left)
119         ld  a,56                ;display height = 64 bytes (minus 8 for bar)
120 displayloop:
121         ld  bc,16               ;display width = 16 bytes (16*8bits=256pixels)
122         ldir                    ;16x de >> hl
123         dec a                   ;next line
124         jr  nz,displayloop      ;loop 64x
125
126         ld  hl,$3946            ;Display Armor left
127         ld  (_penCol),hl        ;place @ armorIcon
128         ld  a,(your_armor)      ;load armor left
129         add a,'0'               ;make digit
130         call _vputmap           ;display char
131
132         ld  hl,$396b            ;Display Score
133         ld  (_penCol),hl        ;bottom right of screen
134         ld  hl,(timer)
135         ld  h,0
136
137 _D_HL_DECI:             ;------- display 5-digit value -------
138         ld   de,savestr+4       ;savenr saves number string
139         ld   b,5                ;five digits
140 ldhld:  call UNPACK_HL          ;one digit of hl
141         add  a,'0'              ;make number
142         ld   (de),a             ;save into savenr
143         dec  de                 ;point to next digit
144         djnz ldhld              ;repeat for all digits
145
146         ld   hl,savestr
147         call _vputs             ;display string
148         ret
149
150 savestr:
151         .db "SHIAR",0
152
153 ;------------------------- handle ship ----------------------------------------
154
155 Handle_Ship:
156         ld  a,(your_occ)
157         or  a
158         jr  z,ok                ;0 = normal stat
159
160         inc a                   ;next (explosion)frame
161         ld  (your_occ),a        ;save
162
163         cp  34                  ;last explosion frame?
164         jr  c,exploding_you     ;not yet: display explosion
165         cp  40                  ;delay finished?
166         jp  z,game_over         ;yes = game over
167         ret                     ;don't display anything
168
169 ok:
170         ld  a,%01111110
171         out (1),a
172         ld  hl,y
173         in  a,(1)
174         rra                     ;rotate right (put last bit in c)
175         ld  b,a                 ;we need a
176
177         jr  c,no_down
178         ld  a,(hl)
179         cp  49                  ;55-6 = bottom of screen
180         jr  z,no_down
181         inc a
182         ld  (hl),a
183 no_down:
184         dec hl
185         rr  b                   ;because we now use b, it's rr instead of rra
186         jr  c,no_left
187         ld  a,(hl)
188         sub 1                   ;<dec a> doesn't affect c-flag
189         jr  c,no_left           ;-1 = left side
190         ld  (hl),a
191 no_left:
192         rr  b   
193         jr  c,no_right
194         ld  a,(hl)
195         cp  121                 ;127-6 = right side
196         jr  z,no_right
197         inc a
198         ld  (hl),a
199 no_right:
200         ld  d,(hl)
201         inc hl
202         rr  b
203         jr  c,no_up
204         ld  a,(hl)
205         sub 1                   ;<dec a> doesn't affect carry-flag
206         jr  c,no_up             ;-1 = top of screen
207         ld  (hl),a              ;save new y
208
209 no_up:  ld  e,(hl)
210         ld  ix,spr_ship01       ;ship sprite
211         ld  hl,your_inv         ;invulnerable?
212         ld  a,(hl)              ;load time in a
213         or  a                   ;is it 0?
214         jp  z,putsprite         ;yes so ship = normal (display \ ret)
215
216         ld  b,a                 ;save inv-time
217         ld  a,(timer)           ;load frame nr.
218         and %00000011           ;a=0 once every four frames
219         jr  nz,not_time         ;a<>0 = not time to update counter
220         dec (hl)                ;decrease inv-time left
221 not_time:
222         and %00000010           ;a switches 0<->1 every 2 frames
223         jr  z,no_flicker        ;don't show normal sprite anyway
224         ld  a,b                 ;pop inv-time
225         and %11110000           ;inv-time <16 ticks left?
226         jp  z,putsprite         ;yes: display normal sprite
227
228 no_flicker:
229         ld  ix,spr_ship01i      ;display inv-ship (ld ix is faster than add ix)
230         jp  putsprite           ;ret
231
232 exploding_you:
233         srl a                   ;half the framerate
234         dec a                   ;first frame is 1>inc>srl>dec = 0
235         ld  hl,x-1
236
237 explosion_stuff:
238         rra
239         add a,a
240         add a,a
241         add a,a
242         ld  c,a
243         ld  b,0
244         ld  ix,spr_explosion
245         add ix,bc
246         inc hl
247         ld  d,(hl)
248         inc hl
249         ld  e,(hl)
250         jp  putsprite
251
252 damage_you:
253         ld  a,(your_inv)        ;invulnerability left?
254         or  a
255         ret nz                  ;return if inv>0
256         ld  hl,your_armor       ;armor left
257         ld  a,(hl)              ;check
258         dec a                   ;is it 0?
259         jp  m,no_armor          ;yes, 0hp left so explode
260         ld  (hl),a              ;no, so save decreased hp
261         ret                     ;and return
262 no_armor:
263         ld  a,%01               ;occ %xxxxxx01 = explode
264         ld  (your_occ),a        ;set to explode
265         ret
266
267 ;------------------------- fire bullet ----------------------------------------
268
269 Fire_bullet:
270         ld  a,(your_occ)        ;are you 100% OK?
271         or  a                   ;a=0??
272         ret nz                  ;return if not normal stat
273
274         ld  a,%00111111         ;function keys (F1-F5)
275         out (1),a               ;ask for them
276         ld  hl,just_fired       ;usefull delay 10 clocks (nop\nop is 8)
277         in  a,(1)               ;get zem!
278         bit 4,a                 ;test bit 4 = F1-key
279         jr  z,fire              ;fire pressed?
280         ld  (hl),0              ;no: reset just_fired
281         ret
282
283 fire:   ld  a,(hl)              ;just_fired
284         or  a                   ;zero when first time
285         ret nz                  ;return when already pressed
286         ld  (hl),1              ;set just_fired
287
288         ld  hl,ybullets
289         ld  de,3
290         ld  b,10
291 find_ybullet:
292         ld  a,(hl)
293         or  a
294         jr  z,found_ybullet     ;0 = no bullet here
295         add hl,de
296         djnz find_ybullet       ;look next bullet
297         ret
298
299 found_ybullet:
300         ld  (hl),1              ;use bullet
301         inc hl
302         ld  a,(x)
303         add a,5
304         ld  (hl),a              ;set x
305         ld  a,(y)
306         add a,2
307         inc hl
308         ld  (hl),a              ;set y
309         ret
310
311 ;------------------------ handle bullets --------------------------------------
312
313 remove_bullet:
314         dec hl
315         ld  (hl),0              ;dump this bullet!
316         ret
317
318 Handle_bullets:
319         ld  hl,ybullets
320         ld  b,10
321 scan_bullets:
322         push bc
323         push hl
324         ld  (temp1),hl
325         ld  a,(hl)
326         inc hl
327         dec a                   ;type 1?
328         call z,bullet_2left     ;yes: 2left
329         pop hl
330         pop bc
331         ld  de,3
332         add hl,de               ;3 x <inc hl>
333         djnz scan_bullets       ;next bullet (loop)
334         ret
335
336 bullet_2left:
337         ld  a,(hl)              ;d = X
338         inc a                   ;move right
339         cp  122                 ;off screen? (x=127-5) &&&
340         jr  z,remove_bullet
341         inc a                   ;move right
342         cp  122                 ;off screen?
343         jr  z,remove_bullet
344         ld  (hl),a              ;save new pos.
345         ld  d,a
346         inc hl                  ;to y-pos
347         ld  e,(hl)              ;e = Y
348         ld  ix,spr_bullet01
349         push de
350         call putsprite          ;display bullet
351         pop de
352         ld  b,nrenemies
353         ld  hl,enemies
354
355 hit_enemies:                    ;Hits with normal enemies
356         push hl
357
358         ld  a,(hl)
359         and %00000010
360         jr  z,nohit             ;no hit when enemy_occ <> 2/3
361
362         inc hl                  ;enemy type
363         ld  a,(hl)
364         or  a                   ;enemy #0 = pickup
365         jr  z,nohit             ;yes: don't destroy
366
367         inc hl
368         ld  a,(hl)              ;check x
369         sub d
370         add a,5
371         jp  m,nohit
372         cp  8
373         jr  nc,nohit
374
375         inc hl
376         ld  a,(hl)              ;check y
377         sub e
378         add a,5
379         jp  m,nohit
380         cp  10
381         jr  nc,nohit
382
383         xor a
384         push hl
385         ld  hl,(temp1)
386         ld  (hl),a              ;remove bullet
387         pop hl
388
389         dec hl
390         dec hl
391         dec hl
392         ld  a,(hl)              ;occ
393         ld  b,a                 ;push occ
394         and %11111100           ;occ/4 = HP left        ;<srl a\srl a
395         jr  nz,hpleft           ;not zero -> jump
396         ld  (hl),%01            ;set to explode
397
398         ld  a,(RanPos)          ;use random var
399         and %01011011           ;matches 0 100/2/2/2/2/2=3% of the time
400         jr  nz,pickupdone       ;otherwise just explode
401         ld  (hl),%00000110      ;change it into a pickup (with 2 HP)
402 pickupdone:
403         inc hl
404         ld  b,(hl)              ;save enemy type
405         ld  (hl),$00            ;explosionFrame 0
406
407         pop hl
408         ret
409
410 hpleft:
411         ld  a,b                 ;pop occ
412         sub %00000100           ;decrease HP by one
413         ld  (hl),a              ;save
414         pop hl
415         ret
416
417 nohit:
418         pop hl
419         inc hl
420         inc hl
421         inc hl
422         inc hl
423         djnz hit_enemies        ;check next enemy
424         ret
425
426 ;--------------------------- level events -------------------------------------
427
428 Level_event:
429         ld  hl,nextevent        ;time to next event     <ld  a,(nextevent)
430         dec (hl)                ;decrease counter       <dec a
431         ld  a,(hl)              ;look at counter        <ld  (nextevent),a
432         or  a                   ;has it reached zero?
433         ret nz                  ;nope: get outta here!
434
435         ld  a,(eventtime)       ;enemy frequency (lvl)
436         ld  (nextevent),a       ;set time to next event
437         ld  hl,eventleft
438         dec (hl)                ;update enemy-counter
439
440         ld  a,(hl)              ;look at counter
441         or  a                   ;has it reached 0?
442         jp  z,Next_level        ;yes: level finished
443         dec a                   ;has it reached 1?
444         jr  nz,do_event         ;nope: wait for enemies to leave
445         inc hl                  ;nextevent located behind eventleft
446         ld  (hl),119            ;set delay
447         ret                     ;don't place any more enemies
448
449 do_event:
450         ld  de,enemies-4
451 chk_noenemy:
452         inc de
453         inc de
454         inc de
455         inc de
456         ld  a,(de)
457         or  a                   ;0 = no enemy present
458         jr  nz,chk_noenemy
459
460 place_enemy:
461         ld  a,(eventenemy)      ;enemy type to place (lvl)
462         ld  hl,enemy00          ;enemy 1 specs
463         add a,a                 ;a=type*2
464         add a,a                 ;a=type*4
465         ld  c,a                 ;c=type
466         ld  b,0                 ;bc = enemy nr.
467         add hl,bc               ;hl = enemy specs
468         ld  a,(hl)              ;load hitpoints+occ of this enemy class
469         ld  (de),a              ;occ
470
471         inc hl                  ;next enemyInfo byte
472         inc de                  ;next byte of current enemy
473         ld  a,(hl)              ;load movement+type of this enemy class
474         ld  (de),a              ;enemy type
475
476         inc de                  ;set x-pos
477         ld  a,122               ;appear at right edge of screen (128-6)
478         ld  (de),a              ;= x-position
479
480         inc de                  ;set y-pos
481         inc hl                  ;where to place??
482         ld  a,(hl)              ;load placeInfo
483         dec a                   ;is it 1?
484         jr  z,random_enemy      ;yes: create random value <51 in a
485         dec a                   ;is it 2?
486         jr  z,lure_enemy        ;yes: create a 100% luring enemy
487                                 ;otherwise?
488 halflure_enemy:                 ;yes (of course it is): pick one (50% lure)
489         ld  a,(timer)           ;look at frame-number
490         and %00000001           ;make random if odd frame nr.
491         jr  nz,random_enemy     ;1st possibility: random enemy
492 lure_enemy:                     ;2nd possibility: luring enemy
493         ld  a,(y)               ;place at same y-pos as YOUR ship
494         jr  ypos_OK
495
496 random_enemy:
497         call Random             ;make a (in a) random value 0-255
498         cp  51                  ;y may not be more than 51
499         jr  c,ypos_OK           ;OK if a<51
500         and %00111111           ;a = 0..63
501         sub 13                  ;a = -13..50
502         jr  c,random_enemy      ;not OK if a<0
503
504 ypos_OK:                        ;random value successfully created
505         ld  (de),a              ;save y-position
506
507         ld  hl,add2enemy-3      ;offset to xtra enemy info
508         add hl,de               ;hl points to <xtra info: move>
509         ld  (hl),1              ;set move-counter to 1
510         inc hl                  ;hl to <xtra info: fire>
511         ld  (hl),1              ;set time-to-fire to 1 frame (fires directly)
512         ret                     ;return
513
514 Random:
515         ld  a,(RanPos)          ;a handy random-var.
516         ld  hl,x                ;add your x-coord for randomness
517         adc a,(hl)
518         ld  hl,y                ;add your y-coord for randomness
519         adc a,(hl)
520         ld  (RanPos),a          ;save altered random-var
521         ret                     ;RanPos also in #a
522
523 ;--------------------------- enemy fires --------------------------------------
524
525 Enemy_fires:                    ;de = x,y
526         dec d
527         dec d                   ;d = x-2
528         inc e                   ;e = y+1
529
530         ld  b,10
531         ld  hl,ebullets
532 find_ebullet:
533         ld  a,(hl)
534         or  a
535         jr  z,found_ebullet     ;0 = not used
536         inc hl \ inc hl \ inc hl
537         djnz find_ebullet       ;look next bullet
538         ret
539
540 found_ebullet:
541         ld  (hl),1              ;use bullet &&&
542         inc hl
543         ld  (hl),d              ;set x-pos
544         inc hl
545         ld  (hl),e              ;set y-pos
546         ret         
547
548 ;----------------------------- enemy bullets ----------------------------------
549
550 Enemy_bullets:
551         ld  hl,ebullets
552         ld  b,10
553 handle_bullet:
554         push bc
555         push hl
556         ld  a,(hl)              ;load bulletType in a
557         or  a                   ;is it 0?
558         jr  nz,enemy_bullet     ;no: handle bullet
559 next_bullet:
560         pop hl                  ;do not move the <pop hl>
561         pop bc
562         inc hl \ inc hl \ inc hl
563         djnz handle_bullet
564         ret
565
566 enemy_bullet:
567         ld  b,a                 ;save type
568         inc hl                  ;bullet x
569         ld  a,(hl)              ;check if it has reached the left side of scrn
570         and %11111110           ;it is <2 (0 or 1)?
571         jr  z,remove_ebullet    ;yes, remove bullet
572         dec (hl)                ;move one left
573         dec (hl)                ;and another one
574         ld  d,(hl)              ;d=x
575         inc hl                  ;@y
576
577         ld  a,b                 ;restore type
578         dec a                   ;type 1?
579         jr  z,ebullet_common    ;normal bullet
580
581 ebullet_down:
582         ld  a,(timer)
583         rra
584         jr  c,ebullet_common
585         inc (hl)
586
587 ebullet_common:
588         ld  e,(hl)              ;e=y
589         ld  ix,spr_bullet11     ;display enemy bullet
590         call putsprite
591
592 ebullet_hits:
593         ld  a,(your_occ)
594         or  a
595         jr  nz,next_bullet      ;0 = you're normal
596
597         pop hl
598         push hl
599         inc hl                  ;check x
600         ld  a,(x)
601         sub (hl)
602         add a,6
603         jp  m,next_bullet
604         cp  9
605         jr  nc,next_bullet
606
607         inc hl                  ;check y
608         ld  a,(y)
609         sub (hl)
610         add a,6
611         jp  m,next_bullet
612         cp  9
613         jr  nc,next_bullet
614
615         call damage_you         ;HIT!!
616 remove_ebullet:
617         pop hl                  ;hl could be destroyed by damage_you
618         ld  (hl),0              ;bullet > unused
619         jr  next_bullet+1       ;next bullet (SKIP THE <POP HL> = one byte)
620
621 ;--------------------------- handle enemies -----------------------------------
622
623 Handle_enemies:
624         ld  hl,enemies
625         ld  b,nrenemies         ;handle all enemies
626
627 handle_enemy:
628         push bc
629         push hl
630
631         ld  a,(hl)
632         and %00000011
633         jr  z,next_enemy        ;occ "no enemy" 0
634         dec a
635         jr  z,exploding_enemy   ;occ "exploding" 1
636         ld  b,a                 ;b=2 if moving, otherwise b=1
637
638 normal_enemy:                   ;occ "normal" 2 or "moving" 3
639         inc hl
640         push hl
641
642         ld  e,(hl)              ;e = enemy type
643         ld  d,0                 ;de = e
644         ld  hl,sprites          ;hl = @sprites offset-table
645         add hl,de               ;points to offset of current enemy offset
646         ld  e,(hl)              ;de = @enemy offset
647
648         ld  ix,spr_enemy00      ;first enemy sprite
649         add ix,de               ;add offset for current enemy
650         pop hl
651
652         inc hl
653         ld  a,(hl)              ;x
654         dec a                   ;move left
655         jr  c,remove_enemy      ;off screen
656         jr  z,remove_enemy      ;"
657         ld  d,a
658
659         inc hl
660         ld  e,(hl)              ;y
661         ld  a,b                 ;moving state was stored in b earlier
662         dec a                   ;is it 1?
663         call nz,moving_enemy    ;2 = moving enemy
664
665 ymove_done:
666         dec hl                  ;@x
667         ld  (hl),d              ;store new x
668
669  push hl
670         push de                 ;save registers for firing-use
671         call putsprite          ;display sprite @ix
672         pop  de                 ;restore (destroyed by putsprite)
673  pop hl
674
675 check_enemyfire:
676         ld  bc,add2enemy+1-2    ;offset of <xtra enemy info: fire>
677         add hl,bc               ;go there (@hl)
678         dec (hl)                ;decrease counter till next blast
679         ld  a,(hl)              ;load new counter
680         or  a                   ;has it reached zero?
681         jr  nz,next_enemy       ;finished if not
682
683         add a,64                ;re-set counter for next blast
684         ld  (hl),a              ;save
685         call Enemy_fires        ;fires bullet
686
687 next_enemy:
688         pop hl
689         ld  bc,$0004
690         add hl,bc
691         pop bc
692         djnz handle_enemy
693         ret
694
695 remove_enemy:
696         pop hl
697         ld  (hl),$0000          ;bye bye enemy
698         push hl
699         jr  next_enemy
700
701 exploding_enemy:
702         inc  hl
703         push hl
704         ld   a,(hl)
705         call explosion_stuff    ;display explosion
706         pop  hl
707
708         ld  a,(hl)
709         cp  15
710         jr  z,remove_enemy      ;remove when at last frame
711         inc a
712         ld  (hl),a              ;next frame
713         jr  next_enemy
714
715 ;--------------------------- moving enemies -----------------------------------
716
717 moving_enemy:
718 movetype_updown:                ;&&&
719         ld  bc,add2enemy
720         add hl,bc
721
722         ld  a,(hl)
723         dec a
724         jr  nz,move_updated
725         add a,128
726 move_updated:
727         ld  (hl),a
728
729         or  a                   ;reset carry flag
730         sbc hl,bc
731         and %00100000
732         jr  z,movedown
733
734 moveup:
735         ld  a,(hl)              ;load y-position
736         dec a                   ;decrease y-pos (=move up)
737         ret m                   ;don't move off the screen (y<0)
738         ld  (hl),a              ;save new y-pos
739         ret                     ;finish
740 movedown:
741         ld  a,(hl)              ;load current y
742         inc a                   ;increase y-pos
743         cp  55                  ;compare with bottom
744         ret nc                  ;return if it has passed that line (>40)
745         ld  (hl),a              ;otherwise save new position
746         ret                     ;and return
747
748 ;--------------------------- check collision ----------------------------------
749
750 Enemies_hit:
751         ld  a,(your_occ)
752         or  a                   ;0 = you're normal
753         ret nz
754
755         ld  de,(x)              ;e = X, d = Y
756         ld  hl,enemies
757         ld  b,nrenemies         ;check all 20 enemies
758 check_collision:
759         push hl
760         ld  a,(hl)
761         and %00000010
762         jr  z,check_next        ;2 or 3 = ok
763         inc hl
764
765 collide_enemy:
766 ;       push hl
767 ;       push bc
768 ;       ld  hl,enemy00          ;enemy 1 specs
769 ;       add a,a                 ;a=type*2
770 ;       add a,a                 ;a=type*4
771 ;       ld  c,a                 ;c=type
772 ;       ld  b,0                 ;bc = 4 * enemy nr.
773 ;       add hl,bc               ;hl = enemy specs
774 ;       ld  a,(hl)              ;load size byte
775 ;       pop bc
776 ;       pop hl
777 ;       ld  c,a                 ;save size in c
778
779         inc hl
780         ld  a,(hl)              ;check x match
781         sub e                   ;enemy position minus yours
782         add a,6
783         jp  m,check_next
784         cp  12
785         jr  nc,check_next
786
787         inc hl
788         ld  a,(hl)              ;check y match
789         sub d                   ;same as with x-check
790         add a,6
791         jp  m,check_next
792         cp  12
793         jr  nc,check_next
794         dec hl
795         dec hl
796
797 take_pickup:
798         ld  a,(hl)              ;load enemy type
799         or  a
800         jr  nz,collide          ;enemy when <>0
801
802         ld  a,(your_armor)
803         inc a
804         ld  (your_armor),a
805
806         dec hl                  ;to enemy occ
807         xor a                   ;set to 0 = gone
808         ld  (hl),a              ;remove
809         jr  check_next          ;all done, next..
810
811 collide:
812         xor a
813         ld  (hl),a              ;explosionFrame 0
814         dec hl
815         inc a
816         ld  (hl),a              ;set to explode
817         call damage_you         ;auch!
818
819 check_next:
820         pop hl
821         inc hl
822         inc hl
823         inc hl
824         inc hl
825         djnz check_collision
826         ret
827
828 ;--------------------------- game over ----------------------------------------
829
830 game_over:
831         call _clrLCD            ;clear screen
832         ld  hl,$0603
833         ld  (_curRow),hl        ;center
834         ld  hl,txt_gameover
835         call _puts              ;display "GAME OVER"
836
837         ld  hl,lives
838         dec (hl)                ;decrease lives
839
840         ld  b,$20
841 wait2:  halt \ halt
842         djnz wait2              ;delay
843         call _getkey            ;wait for keypress
844
845 ;--------------------------- new game -----------------------------------------
846
847 New_level:
848         xor a                   ;a=0
849  ld a,3
850         ld  (your_armor),a      ;no armor
851  xor a
852         ld  hl,x                ;begin position x=...
853         ld  (hl),a              ;...=a=0=left
854         inc hl                  ;y=...
855         ld  (hl),24             ;...=24=middle
856         ld  (level),a           ;reset level nr
857         ld  (score),a           ;reset score
858         ld  hl,level01-3        ;set level pointer to level#1
859         ld  (levelp),hl         ;reset level pointer
860
861 ;--------------------------- next level ---------------------------------------
862
863 Next_level:
864         ld  hl,level
865         inc (hl)                ;increase level nr.
866         ld  a,80
867         ld  (nextevent),a       ;time to first enemy appearance
868
869         ld  hl,(levelp)         ;level pointer
870         inc hl
871         inc hl
872         inc hl                  ;update to point to next level
873         ld  (levelp),hl         ;save
874
875         ld  a,(hl)              ;load new level-enemy type
876         ld  (eventenemy),a      ;set level-enemy
877         inc hl
878         ld  a,(hl)              ;load new appearance-time
879         ld  (eventtime),a       ;set
880         inc hl
881         ld  a,(hl)              ;load nr of enemies in this level
882         ld  (eventleft),a       ;set nr of events left
883
884         xor a
885         ld  (timer),a           ;reset time
886         ld  hl,your_occ         ;hl = your_occ
887         ld  (hl),a              ;reset your ship (not exploding)
888         inc hl                  ;hl = your_inv
889         ld  (hl),50             ;set 50 frames invulnerable
890
891 ;--------------------------- setup game ---------------------------------------
892
893 game_setup:
894         call _clrLCD            ;clear screen
895         ld a,%10111011
896         ld  hl,VIDEO_MEM        ;screen location (top left)
897         ld  b,0                 ;b = 0 (loop 0-1 = 0FFh = 256 times)
898 clearloop2:
899         inc a
900         ld  (hl),a              ;clear four times (total = 256*4 = 1024 bytes)
901         inc hl
902         ld  (hl),a
903         inc hl
904         xor $ff
905         ld  (hl),a
906         inc hl
907         ld  (hl),a
908         inc hl
909         xor $ff
910         djnz clearloop2         ;repeat 256x
911
912         ld  hl,$0703
913         ld  (_curRow),hl        ;center
914         ld  hl,txt_level
915         call _puts              ;display "LEVEL "
916
917         ld  a,(level)
918         ld  l,a
919         ld  h,$00
920
921         call UNPACK_HL
922         add a,'0'
923         ld  b,a
924         call UNPACK_HL
925         add a,'0'
926         call _putc              ;display second digit
927         ld  a,b
928         call _putmap            ;display first digit
929
930         ld  hl,$0904
931         ld  (_curRow),hl        ;display lives left below level nr
932         ld  hl,txt_lives        ;bar text: "Lx0"...
933         ld  a,(lives)           ;lives left
934         add a,'0'               ;make value
935         ld  (txt_lives+3),a     ;add to text
936         call _puts              ;display the string
937
938         ld  b,$20
939 wait:   halt \ halt
940         djnz wait               ;delay
941         call _getkey            ;wait for keypress
942
943         ld  ix,spr_icon00       ;empty icon
944         ld  de,$1a01            ;icon #1
945         call putwidesprite      ;display
946         ld  ix,spr_icon00       ;emptyIcon
947         ld  de,$2a01            ;icon #2
948         call putwidesprite
949 ;       ld  ix,spr_icon02       ;emptyIcon
950 ;       ld  de,$3a01            ;icon #3
951 ;       call putwidesprite
952         ld  ix,spr_icon00       ;emptyIcon
953         ld  de,$4a01            ;icon #4
954         call putwidesprite
955         ld  ix,spr_icon00       ;emptyIcon
956         ld  de,$5a01            ;icon #5
957         call putwidesprite
958
959         ld  ix,spr_icon02       ;armorIcon
960         ld  de,$3a01            ;bottom mid
961         call putwidesprite      ;display
962
963         ld  hl,GRAPH_MEM        ;from storage (top left)
964         ld  de,VIDEO_MEM+(56*16);to screen (top left)
965         ld  a,8                 ;display height = 64 bytes (minus 8 for bar)
966 displayloop3:
967         ld  bc,16               ;display width = 16 bytes (16*8bits=256pixels)
968         ldir                    ;16x de >> hl
969         dec a                   ;next line
970         jr  nz,displayloop3     ;loop 8x
971
972         ld  hl,$3900            ;display Lives
973         ld  (_penCol),hl        ;bottom left
974         ld  hl,savestr+2
975         ld  (hl),'L'
976         inc hl
977         ld  (hl),'x'
978         inc hl
979
980         ld  a,(lives)           ;nr of lives in a
981         add a,'0'               ;make digit
982         ld  (hl),a
983         dec hl \ dec hl
984         call _vputs             ;display on screen
985
986         ld  hl,VIDEO_MEM+(16*56);56 rows down = eight rows from bottom
987         ld  b,16                ;draw 16x (screen width)
988 drawline:
989         ld  a,%11111111         ;horizontal line mask
990         ld  (hl),a              ;draw one piece of the divider-line
991         inc hl                  ;move right (8 pixels = 1 byte)
992         djnz drawline           ;repeat (16bytes * 8pixels =128= screen width)
993         ret
994
995 ;--------------------------- putsprite ----------------------------------------
996 ;--------------------------- de =(X,Y) ----------------------------------------
997
998 offsets_table:
999         .db 128,64,32,%10000,%01000,%00100,%00010,%00001
1000 putsprite:
1001         ld  a,d                 ;a = X
1002         and %00000111           ;a = X mod 8 = bit nr. to mask
1003         ld  hl,offsets_table    ;pixel mask table
1004         ld  c,a                 ;bit nr.
1005         ld  b,0                 ;word
1006         add hl,bc               ;add to table
1007         ld  a,(hl)              ;a = pixel mask
1008         ld  (_smc1+1),a         ;alter pixel mask
1009
1010         ld  hl,GRAPH_MEM        ;save-location
1011         ld  a,e                 ;y-coord
1012         add a,a                 ;y*2
1013         add a,a                 ;y*4
1014         add a,a                 ;y*8
1015         rl  b                   ;b (=0) =b*2+overflow (if y>32 then bc=bc+256)
1016         add a,a                 ;y*16 (width of screen)
1017         rl  b                   ;b=b*2+overflow (if y>64 then bc=bc+512)
1018         srl d                   ;d/2
1019         srl d                   ;d/4
1020         srl d                   ;d/8 (8 bits in byte) ** c is set when overflow
1021         add a,d                 ;a = (Y*16+X/8) mod 256
1022         jr  nc,_n1              ;jump if no carry = no overflow = a<=255
1023         inc b                   ;a>255 so increase bc by 256
1024 _n1:    ld  c,a                 ;c = (Y*16+X/8) mod 256
1025         add hl,bc               ;bc = Y*16+X/8
1026           
1027         ld  d,(ix)
1028         ld  b,(ix+1)
1029 _oloop: push bc                 ;Save # of rows
1030         push hl                 ;Save screen address
1031         ld  b,d                 ;Load width
1032         ld  c,(ix+2)            ;Load one line of image
1033         inc ix
1034 _smc1:  ld  a,1                 ;Load pixel mask
1035 _iloop: sla c                   ;Test leftmost pixel
1036         jr  nc,_noplot          ;See if a plot is needed
1037         ld  e,a                 ;OR pixel with screen
1038         or  (hl)
1039         ld  (hl),a
1040         ld  a,e
1041 _noplot:rrca
1042         jr  nc,_notedge         ;Test if edge of byte reached
1043         inc hl                  ;Go to next byte
1044 _notedge:
1045         djnz _iloop
1046         pop hl                  ;Restore address
1047         ld  bc,16               ;Go to next line
1048         add hl,bc
1049         pop bc                  ;Restore data
1050         djnz _oloop
1051         ret
1052
1053 ;--------------------------- putbigsprite -------------------------------------
1054
1055 putwidesprite:
1056         ld       a,d
1057         and      7
1058         ld       hl,offsets_table
1059         ld       c,a
1060         ld       b,0
1061         add      hl,bc
1062         ld       a,(hl)
1063         ld       (wsmc1+1),a
1064         ld       (wsmc2+1),a
1065
1066         ld       hl,GRAPH_MEM
1067
1068         ld       a,e
1069         add      a,a
1070         add      a,a
1071         add      a,a
1072
1073         rl       b
1074         add      a,a
1075         rl       b
1076         srl      d
1077         srl      d
1078         srl      d
1079         add      a,d
1080         jr       nc,n1
1081         inc      b
1082 n1:     ld       c,a
1083         add      hl,bc                                    
1084           
1085         ld       d,(ix)       
1086         ld       b,(ix+1)        
1087 woloop: push     bc                         ;Save # of rows
1088         push     hl                         ;Save screen address
1089         ld       b,d                        ;Load width
1090         ld       c,(ix+2)                   ;Load one line of image
1091         inc      ix
1092 wsmc1:  ld       a,1                        ;Load pixel mask
1093 wiloop: sla      c                          ;Test leftmost pixel
1094         jr       nc,wnoplot                 ;See if a plot is needed
1095         ld       e,a                        ;OR pixel with screen
1096         or       (hl)
1097         ld       (hl),a
1098         ld       a,e
1099 wnoplot:
1100         rrca
1101         jr       nc,wnotedge                ;Test if edge of byte reached
1102         inc      hl                         ;Go to next byte
1103 wnotedge:
1104 wsmc2:  cp       1
1105         jr       z,wover_1
1106
1107         djnz     wiloop
1108         pop      hl                         ;Restore address
1109         ld       bc,16                      ;Go to next line
1110         add      hl,bc
1111         pop      bc                         ;Restore data
1112         djnz     woloop
1113         ret
1114 wover_1:
1115         ld       c,(ix+2)
1116         inc      ix
1117         djnz     wiloop
1118         dec      ix
1119         pop      hl
1120         ld       bc,16
1121         add      hl,bc
1122         pop      bc
1123         djnz     woloop
1124         ret
1125
1126 ;------------------------------------------------------------------------------
1127 ;------------------------------- sprites --------------------------------------
1128 ;------------------------------------------------------------------------------
1129
1130 spr_ship:
1131         .db 9,1         ;ship icon
1132         .db %11100000   ; ███
1133         .db %01111000   ;  ████
1134         .db %00111110   ;   █████
1135         .db %01111001   ;  ████  █
1136         .db %01111001   ;  ████  █
1137         .db %01111001   ;  ████  █
1138         .db %00111110   ;   █████
1139         .db %01111000   ;  ████
1140         .db %11100000   ; ███
1141
1142 spr_ship01:
1143         .db 7,7         ;ship alpha class
1144         .db %01111000   ;  ████
1145         .db %11100000   ; ███
1146         .db %11111100   ; ██████
1147         .db %11110010   ; ████  █
1148         .db %11111100   ; ██████
1149         .db %11100000   ; ███
1150         .db %01111000   ;  ████
1151 spr_ship01i:
1152         .db 7,7         ;ship alpha class
1153         .db %01010000   ;  █ █
1154         .db %10100000   ; █ █
1155         .db %01010100   ;  █ █ █
1156         .db %10100010   ; █ █   █
1157         .db %01010100   ;  █ █ █
1158         .db %10100000   ; █ █
1159         .db %01010000   ;  █ █
1160
1161 spr_ship02:
1162         .db 7,7         ;ship beta class
1163         .db %11000000   ; ██
1164         .db %11110000   ; ████
1165         .db %01111100   ;  █████
1166         .db %01110010   ;  ███  █
1167         .db %01111100   ;  █████
1168         .db %11110000   ; ████
1169         .db %11000000   ; ██
1170
1171 spr_bullet01:
1172         .db 5,3         ;your bullets
1173         .db %00110000   ;   ░▒▓█▒
1174         .db %11111000   ; ░▒▓████▒
1175         .db %00110000   ;   ░▒▓█▒
1176 spr_bullet02:
1177         .db 5,3
1178         .db %11110000   ; ░▒▓███▒
1179         .db %11111000   ; ░▒▓████▒
1180         .db %11110000   ; ░▒▓███▒
1181
1182 spr_bullet11:
1183         .db 3,3         ;enemy bullets
1184         .db %01000000   ;  ▒▓▒░
1185         .db %11100000   ; ▒██▓▒░
1186         .db %01000000   ;  ▒▓▒░
1187
1188 ;---------------------------------------- explosion -------------------------------------------
1189
1190 spr_explosion:                               
1191         .db 8,6         ;1
1192         .db %00000000
1193         .db %00011100   ;    ███
1194         .db %00111110   ;   █████
1195         .db %01010110   ;  █ █ ██
1196         .db %00111000   ;   ███
1197         .db %00000000
1198
1199         .db 8,6         ;2
1200         .db %00110000   ;   ██
1201         .db %01001110   ;  █ ▒███
1202         .db %10111110   ; █ █████
1203         .db %01001111   ;  █ ▒████
1204         .db %00111000   ;   ███
1205         .db %00011010   ;    ██ █
1206
1207         .db 8,6         ;3
1208         .db %10110000   ; █ ██
1209         .db %01001110   ;  █  ███
1210         .db %10110101   ; █ ██▒█▒█
1211         .db %01000101   ;  █  ▒█▒█
1212         .db %00111110   ;   █████
1213         .db %01011010   ;  █ ██ █
1214
1215         .db 8,6         ;4
1216         .db %00101010   ; ▒ █▒█ █
1217         .db %01000110   ;  █  ▒██
1218         .db %10110101   ; █ ██ █ █
1219         .db %01100110   ;  ██  ██▒
1220         .db %00111100   ;   ████▒
1221         .db %01011001   ;  █ ██ ▒█
1222
1223         .db 8,6         ;5
1224         .db %01000000   ;  █▒ ▒ ▒
1225         .db %00100101   ;  ▒█  █▒█
1226         .db %00010100   ; ▒ ▒█ █ ▒
1227         .db %01000100   ;  █▒  █
1228         .db %00010010   ;   ▒█▒▒█
1229         .db %10011010   ; █▒ ██ █▒
1230
1231         .db 8,6         ;6
1232         .db %01000100   ;  █   █
1233         .db %00100000   ;   ▒█ ▒ ▒
1234         .db %00000001   ;    ▒ ▒ █
1235         .db %01000100   ;  █   █
1236         .db %00100010   ;   █▒  █
1237         .db %01001000   ; ▒█ ▒█ ▒
1238
1239         .db 8,6         ;7
1240         .db %00001000   ;  ▒  █▒
1241         .db %11000010   ; ██ ▒  █
1242         .db %00000000   ;        ▒
1243         .db %00100000   ;  ▒█  ▒
1244         .db %00000001   ;   ▒   ▒█
1245         .db %00110000   ;  ▒██▒
1246
1247         .db 8,6         ;8
1248         .db %00000100   ;     ▒█
1249         .db %00000000   ; ▒▒    ▒
1250         .db %01000000   ;  █
1251         .db %00000000   ;   ▒
1252         .db %00000010   ;       █▒
1253         .db %00100100   ;   █▒ █
1254
1255 ;--------------------------------------- bar -----------------------------------
1256
1257 spr_icon00:
1258         .db 16,7        ;unused   .......:.......:
1259         .db %10101010,%10101010 ; █ █ █ █ █ █ █ █
1260         .db %11010101,%01010101 ; ██ █ █ █ █ █ █ █
1261         .db %10101010,%10101010 ; █ █ █ █ █ █ █ █
1262         .db %11010101,%01010101 ; ██ █ █ █ █ █ █ █
1263         .db %10101010,%10101010 ; █ █ █ █ █ █ █ █
1264         .db %11010101,%01010101 ; ██ █ █ █ █ █ █ █
1265         .db %10101010,%10101010 ; █ █ █ █ █ █ █ █
1266 spr_icon01:
1267         .db 16,7        ;invulnerable....:.......:
1268         .db %10000000,%01010100 ; █        O O O
1269         .db %10011110,%00101010 ; █  OOOO   O O O
1270         .db %10111000,%00010101 ; █ OOO      O O O
1271         .db %10111111,%10101010 ; █ OOOOOOO O O O
1272         .db %10111111,%00010101 ; █ OOOOOOO  O O O
1273         .db %10111000,%00101010 ; █ OOO     O O O
1274         .db %10011110,%01010100 ; █  OOOO  O O O
1275 spr_icon02:
1276         .db 16,7        ;armor  ; .......:.......:
1277         .db %10001111,%10000000 ; █   █████
1278         .db %10010000,%01000100 ; █  █     █  XXX
1279         .db %10101110,%00101010 ; █ █ ███   █ XXX
1280         .db %10100111,%10101010 ; █ █  ████ █ XXX
1281         .db %10101110,%00101010 ; █ █ ███   █ XXX
1282         .db %10010000,%01000100 ; █  █     █  XXX
1283         .db %10001111,%10000000 ; █   █████
1284
1285 ;---------------------------- texts -------------------------------------------
1286
1287 txt_about:      .db "v0.8.93 ","by Shiar  "
1288                 .db "(ICQ#43840958)",0
1289 txt_1player:    .db "1 PLAYER",0
1290 txt_2players:   .db "2 PLAYERS",0
1291 txt_level:      .db "LEVEL ",0
1292 txt_gameover:   .db "GAME OVER!",0
1293 txt_lives:      .db "Lx0?",0
1294
1295 ;---------------------------- save data ---------------------------------------
1296
1297 stored_data_start:
1298
1299 timer           .db $00                 ;frame counter
1300 level           .db $00                 ;level number
1301 levelp          .dw level01             ;pointer to level data
1302
1303 eventenemy      .db $02                 ;enemy type
1304 eventtime       .db $15                 ;enemy frequency
1305 eventleft       .db $00                 ;nr. of enemies still to come
1306 nextevent       .db $50                 ;time to next event
1307
1308 score           .dw $0000
1309
1310 your_occ        .db $00                 ;0=normal 1..16=exploding
1311 your_inv        .db $50                 ;invincibility left
1312 your_armor      .db $13                 ;HP left
1313 lives           .db $03                 ;
1314 x               .db $16                 ;x-pos
1315 y               .db $46                 ;think about it..
1316 hp              .db $00                 ;hitpoints left
1317
1318 ybullets        .dw 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0       ;10 x (state,x,y)
1319 ebullets        .dw 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0       ;10 x (state,x,y)
1320
1321 nrenemies       = 10
1322 enemies         .dw $0000,$0000,$0000,$0000,$0000,$0000,$0000,$0000,$0000,$0000
1323                 .dw $0000,$0000,$0000,$0000,$0000,$0000,$0000,$0000,$0000,$0000
1324                 .dw $0000,$0000,$0000,$0000,$0000,$0000,$0000,$0000,$0000,$0000
1325                 .dw $0000,$0000,$0000,$0000,$0000,$0000,$0000,$0000,$0000,$0000
1326
1327 enemiesxtra     .dw $0000,$0000,$0000,$0000,$0000,$0000,$0000,$0000,$0000,$0000
1328                 .dw $0000,$0000,$0000,$0000,$0000,$0000,$0000,$0000,$0000,$0000
1329                 .dw $0000,$0000,$0000,$0000,$0000,$0000,$0000,$0000,$0000,$0000
1330                 .dw $0000,$0000,$0000,$0000,$0000,$0000,$0000,$0000,$0000,$0000
1331 add2enemy       = 40
1332
1333 ; %111111 (HP left) 11 (00=no enemy 01=exploding 10=normal 11=moving)
1334 ; %11111111 (ship type or explosion frame)  %11111111 (x) %11111111 (y)
1335
1336 ;---------------------------- enemy data --------------------------------------
1337
1338 sprites:
1339         .db $00
1340         .db spr_enemy01-spr_enemy00
1341         .db spr_enemy02-spr_enemy00
1342         .db spr_enemy03-spr_enemy00
1343         .db spr_enemy04-spr_enemy00
1344         .db spr_enemy05-spr_enemy00
1345         .db spr_enemy06-spr_enemy00
1346         .db spr_enemy07-spr_enemy00
1347
1348 spr_enemy00:
1349         .db 6,5         ;pickup
1350         .db %11111100   ; ██████
1351         .db %10010100   ; █  █ █
1352         .db %11111100   ; ██████
1353         .db %10010100   ; █  █ █
1354         .db %11111100   ; ██████
1355 spr_enemy01:
1356         .db 6,6         ;enemy type one
1357         .db %00111100   ;   ████
1358         .db %01110000   ;  ███
1359         .db %11110000   ; ████
1360         .db %11110000   ; ████
1361         .db %01110000   ;  ███
1362         .db %00111100   ;   ████
1363 spr_enemy02:
1364         .db 8,6         ;enemy type two
1365         .db %00111111   ;    █████
1366         .db %01111000   ;  ████
1367         .db %11111100   ; ██████
1368         .db %11111100   ; ██████
1369         .db %01111000   ;  ████
1370         .db %00111111   ;    █████
1371 spr_enemy03:
1372         .db 6,6         ;enemy type three
1373         .db %01111100   ;  █████
1374         .db %11110000   ; ████
1375         .db %11111000   ; █████
1376         .db %11111000   ; █████
1377         .db %11110000   ; ████
1378         .db %01111100   ;  █████
1379 spr_enemy04:
1380         .db 6,6         ;enemy type four
1381         .db %00111000   ;   ███
1382         .db %01111100   ;  █████
1383         .db %11111000   ; █████
1384         .db %11111000   ; █████
1385         .db %01111100   ;  █████
1386         .db %00111000   ;   ███
1387 spr_enemy05:
1388         .db 7,6         ;enemy type four
1389         .db %00011110   ;    ████
1390         .db %01111110   ;  ██████
1391         .db %11111100   ; ██████
1392         .db %11111100   ; ██████
1393         .db %01111110   ;  ██████
1394         .db %00011110   ;    ████
1395 spr_enemy06:
1396         .db 7,6         ;enemy type four
1397         .db %00011100   ;    ███
1398         .db %01111110   ;  ██████
1399         .db %10111000   ; █ ███
1400         .db %10111000   ; █ ███
1401         .db %01111110   ;  ██████
1402         .db %00011100   ;    ███
1403 spr_enemy07:
1404         .db 8,6         ;enemy type four
1405         .db %00011110   ;    ████
1406         .db %01111111   ;  ███████
1407 enemy00:.db %10011100   ; █  ███
1408         .db %10011100   ; █  ███
1409         .db %01111111   ;  ███████
1410         .db %00011110   ;    ████
1411
1412         ;enemyInfo:     %000000:HP %10:occ $00:type $00:app $00:unused
1413 enemy01:                        ;#1     HP:1    app:random
1414         .db %00000010,1,1,0
1415 enemy02:                        ;#2     HP:1    app:halflure
1416         .db %00000010,2,3,0
1417 enemy03:                        ;#3     HP:1    app:random      moving
1418         .db %00000011,3,1,0
1419 enemy04:                        ;#4     HP:2    app:lure
1420         .db %00000110,4,2,0
1421 enemy05:                        ;#5     HP:2    app:random      moving
1422         .db %00000111,5,1,0
1423 enemy06:                        ;#6     HP:2    app:lure        moving
1424         .db %00000111,6,2,0
1425 enemy07:                        ;#7     HP:4    app:halflure    moving
1426         .db %00001111,7,3,0
1427
1428 ;----------------------------- level info -------------------------------------
1429
1430 level01:
1431         .db $01,$1b,$2f                 ;enemy nr ; enemy frequency ; next lvl
1432 level02:                                ;frequency must be odd if halfluring!
1433         .db $02,$11,$4b
1434 level03:
1435         .db $03,$1d,$3f
1436 level04:
1437         .db $04,$0d,$4f
1438 level05:
1439         .db $05,$2d,$3d
1440 level06:
1441         .db $06,$2b,$39
1442 level07:
1443         .db $07,$25,$f9
1444
1445 ;----------------------------- logo -------------------------------------------
1446
1447 logo_nemesis:
1448 .db %11111111,%11111111,%11111111,%11111110,%11111111,%11110111,%11111111,%11111110,%11111111,%111101111,%11111111,%00001011,%11111111,%11111111,%11111111,%11111000
1449 .db %01111111,%11111111,%11111111,%11111110,%11111111,%11110111,%11111111,%11111110,%11111111,%111101111,%11111111,%00011011,%11111111,%11111111,%11111111,%11110000
1450 .db %00111111,%11111111,%11111111,%11111110,%11111111,%11110111,%11111111,%11111110,%11111111,%111101111,%11111111,%00111011,%11111111,%11111111,%11111111,%11100000
1451 .db %00011111,%11111111,%11111111,%11111110,%11111111,%11110111,%11111111,%11111110,%11111111,%111101111,%11111111,%01111011,%11111111,%11111111,%11111111,%11000000
1452 .db %00000000,%00000000,%00000001,%00011110,%00010000,%00000000,%10000001,%00011110,%00010000,%000000001,%00000000,%00001000,%01000000,%00000000,%00000000,%00000000
1453 .db %00000000,%00000000,%00000011,%00011110,%00110000,%00000001,%10000011,%00011110,%00110000,%000000011,%00000000,%00011000,%11000000,%00000000,%00000000,%00000000
1454 .db %00000000,%00000000,%00000111,%00011110,%01110000,%00000011,%10000111,%00011110,%01110000,%000000111,%00000000,%00111001,%11000000,%00000000,%00000000,%00000000
1455 .db %00000000,%00000000,%00001111,%00011110,%11111111,%00000111,%10001111,%00011110,%11111111,%000001111,%11111111,%01111011,%11111111,%11000000,%00000000,%00000000
1456 .db %00000000,%00000000,%00001111,%00011110,%11111111,%00000111,%10001111,%00011110,%11111111,%000001111,%11111111,%01111011,%11111111,%11000000,%00000000,%00000000
1457 .db %00000000,%00000000,%00001111,%00011110,%11111111,%00000111,%10001111,%00011110,%11111111,%000001111,%11111111,%01111011,%11111111,%11000000,%00000000,%00000000
1458 .db %00000000,%00000000,%00001111,%00011110,%11111111,%00000111,%10001111,%00011110,%11111111,%000001111,%11111111,%01111011,%11111111,%11000000,%00000000,%00000000
1459 .db %00000000,%00000000,%00001111,%00011110,%11110000,%00000111,%10001111,%00011110,%11110000,%000000000,%00001111,%01111000,%00000011,%11000000,%00000000,%00000000
1460 .db %00000000,%00000000,%00001111,%00011110,%11110000,%00000111,%10001111,%00011110,%11110000,%000000000,%00001111,%01111000,%00000011,%11000000,%00000000,%00000000
1461 .db %00000000,%00000000,%00001111,%00011110,%11110000,%00000111,%10001111,%00011110,%11110000,%000000000,%00001111,%01111000,%00000011,%11000000,%00000000,%00000000
1462 .db %00000000,%00000000,%00001111,%00011110,%11110000,%00000111,%10001111,%00011110,%11110000,%000000000,%00001111,%01111000,%00000011,%11000000,%00000000,%00000000
1463 .db %00000000,%00000000,%00001111,%00011110,%11111111,%11110111,%10001111,%00011110,%11111111,%111101111,%11111111,%01111011,%11111111,%11000000,%00000111,%11010001
1464 .db %00000000,%00000000,%00001111,%00011110,%11111111,%11110111,%10001111,%00011110,%11111111,%111101111,%11111111,%01111011,%11111111,%11000000,%00000001,%00011011
1465 .db %00000000,%00000000,%00001111,%00011110,%11111111,%11110111,%10001111,%00011110,%11111111,%111101111,%11111111,%01111011,%11111111,%11000000,%00000001,%00010101
1466 .db %00000000,%00000000,%00001111,%00011110,%11111111,%11110111,%10001111,%00011110,%11111111,%111101111,%11111111,%01111011,%11111111,%11000000,%00000001,%00010001
1467
1468 ;----------------------------- end --------------------------------------------
1469
1470         .end
1471 .end
1472
1473 ;----------------------------- NEMESIS'86 by Shiar ----------------------------
1474
1475 ;Game · · · · · · · · · · · · · · · · · · · · · · · · · · · · · · · · · NEMESIS
1476 ;Version  · · · · · · · · · · · · · · · · · · · · · · · · · · · · · · ·  0.8.93
1477 ;Latest modification  · · · · · · · · · · · · · · · · · · · · · · · · · 3.IX.99
1478 ;Calc · · · · · · · · · · · · · · · · · · · · · · · · · · · · · · ·  TI-86 only
1479 ;Size · · · · · · · · · · · · · · · · · · · · · · · · · · ·  2417 bytes on calc
1480
1481 ;Author · · · · · · · · · · · · · · · · · · · · · · · · · · · · · · · · · SHIAR
1482 ;ICQ · · · · · · · · · · · · · · · · · · · · · · · · · · · · · · · ·  #43840958
1483 ;E-mail · · · · · · · · · · · · · · · · · · · · · · · · · ·  shiar0@hotmail.com
1484 ;Homepage · · · · · · · · · · · · · · · · · · coming soon (www.wish.net/~shiar)
1485
1486 ;Notes:
1487 ;  <*> This game is not yet finished (BETA) and there may still be some bugs.
1488 ;  <*> Source will be released when the game has been finished.
1489 ;  <*> Have fun, and have even more fun with the completed version of NEMESIS!
1490
1491 ;----------------------------- version history --------------------------------
1492
1493 ;0.01.717 -- 17.VII.99 -- size 909
1494 ;
1495 ;       + used "Galaxian"-game engine (drawings, movement, enemy-routines)
1496 ;       + movement of ship over 3/4 screen (96 pixels; 32 pixels for score)
1497 ;       + enemies moving from right to left, appearing right at specified times
1498 ;
1499 ; 0.1.718 -- 18.VII.99 -- size 832
1500 ;
1501 ;       # no crash when level restarts for the third time
1502 ;       * exit-procedure updated, unnecessary stuff/keychecks removed
1503 ;       - alot of unused code removed
1504 ;       + different types of enemies (just look different)
1505 ;       + collision detection!! enemy ships disappear when you hit them
1506 ;
1507 ; 0.2.718 -- 18.VII.99 -- size 1078
1508 ;
1509 ;       + ability to fire bullets (F1). Enemies disappear on impact
1510 ;       * enemies explode instead of disappearing
1511 ;
1512 ; 0.3.719 -- 19.VII.99 -- size 1326
1513 ;
1514 ;       * bullets appear correctly (not INSIDE your ship)
1515 ;       + some enemies can take multiple hits (differs per class)
1516 ;       + all enemies fire bullets at random
1517 ;       + if you're hit by bullet/enemy, you'll lose one hitpoint
1518 ;
1519 ; 0.4.720 -- 20.VII.99 -- size 1406
1520 ;
1521 ;       # collision detection fixed and optimized (much faster now!)
1522 ;       + shell-icon added (YAS type)
1523 ;       * code optimizations, some data "compression"
1524 ;       * explosion looks better, and some vars removed/smaller
1525 ;       # enemies are removed when at left side (instead of becoming invisible)
1526 ;       + displays level number before each level begins
1527 ;
1528 ; 0.5.725 -- 25.VII.99 -- size 1703
1529 ;
1530 ;       * waits a sec at level display (in case of accidental keypress)
1531 ;       * moving enemies (move up+down)
1532 ;       # bullets removed correctly so they can be used again later
1533 ;       * first level made
1534 ;       # enemy weaponfire is fired from correct positions
1535 ;       + your ship explodes on impact with ships/bullets
1536 ;       * game over screen will be displayed just *after* your ship's gone
1537 ;       + frame counter onscreen
1538 ;
1539 ; 0.6.820 -- 20.IIX.99 -- size 2077
1540 ;
1541 ;       * play field increased to full screen instead of 3/4
1542 ;       + bottom eight lines used for score (etc) display
1543 ;       - no more solid levels, enemies are placed at random
1544 ;       + enemies appear every x turns (depends on level)
1545 ;       # fixed bullets so they don't disappear at 3/4 of the screen
1546 ;       * A LOT of optimizations both in speed and size!!
1547 ;       + enemy type, frequency, and number specified per level
1548 ;       + bottom score bar displays score, lives and icons (to be used later)
1549 ;       * smarter enemy handling (so enemies have different sizes)
1550 ;       + bottom bar divided from playing field by a horizontal line
1551 ;       + five levels (and five enemies) made
1552 ;       # game vars reset at start and game over
1553 ;       + NEMESIS LOGO displayed at startup!! (also, program grew 350bytes ):
1554 ;       + version/credits string displayed below logo: v0.6.820 by shiar (ICQ#)
1555 ;
1556 ; 0.6.825 -- 25.IIX.99 -- size 2085
1557 ;
1558 ;       # pointer to fifth ship corrected (ships in level 5 weren't displayed)
1559 ;       # calc doesn't crash anymore when game is continued after game over!!
1560 ;       + lives are decreased when ship is destroyed
1561 ;       # last eight pixels of divider line are shown correctly now
1562 ;
1563 ;  0.7.92 -- 02.IX .99 -- size 2303
1564 ;
1565 ;       + contrast is increased one level at startup (and restored on exit)
1566 ;       + invulnerable for a sec when you enter the game (inv-pickup later)
1567 ;       + when in invulnerable-mode, your ship look different!
1568 ;       + at the beginning you get three *hitpoints* so you can be hit 3 times
1569 ;       * bottomline icons are now 16 pixels wide and 7 pixels high!
1570 ;       + hitpoint icon added: displays nr. of hps left next to a nice picture
1571 ;       * maximum invulnerability-time is increased (can last upto 1024 frames)
1572 ;       + when invulnerable-mode has nearly expired, your ship flashes!
1573 ;       * again a lot of optimizations esp. in size ('bout 100 bytes)
1574 ;       + pickups! 10% chance a destroyed enemy changes into an armor-pickup
1575 ;       # code optimization caused some bullets to reappear as "fake" bullets
1576 ;       * pickups can't be destroyed by bullets (they pass right through it)
1577 ;
1578 ;  0.8.93 -- 03.IX .99 -- size 2433
1579 ;
1580 ;       + enemies move individually, not all at the same time!! Looks very nice
1581 ;       # titlescreen background is cleared (looked weird in Rascall and TI-OS)
1582 ;       + enemies fire at a ### rate instead of firing at will (too random)
1583 ;       # moving enemies don't move off the screen top/bottom (they wait there)
1584 ;       + seven playable levels going easy to hard (including moving enemies)
1585 ;       # xtraInfo data wasn't reset when a moving enemy entered the game
1586 ;       * longer delay when level is completed (NextLevel screen came too soon)
1587
1588 ;To FIX: pickups fire bullets!?!
1589
1590
1591 ;        + added        - removed       * changed       # bug fixed