X-Git-Url: http://git.shiar.nl/wormy.git/blobdiff_plain/7ec10d8466fbe267a3d0a8fe8fbfaed79adbf07f..18959d722238409d68bd3a979624cc80c7d5b3d9:/worm.z80 diff --git a/worm.z80 b/worm.z80 index a5cdab9..af6b84a 100644 --- a/worm.z80 +++ b/worm.z80 @@ -1,33 +1,36 @@ ; Title : Worm -; Version : 91% -; Release Date : may 2000 +; Version : 92% +; Release Date : june 2000 ; Filename : worm.86p (5kb) ; Author(s) : Shiar -; Email Address : shiar@mailroom.com +; Email Address : shiar0@hotmail.com ; ICQ UIN : #43840958 -; Web Page : www.games3.net/shiar -; Description : ruling multiplayer game for 86 (most like Nibbles) -; Where to get this game : games3.net/shiar (home of Worm) -; Other games by author(s) : Shiar: Nemesis beta +; Web Page : www.shiar.org +; Description : ruling Nibbles-like game 1-4 players +; Where to get this game : www.shiar.org (home of Worm) +; Other games by author(s) : Nemesis beta ; Additional Credits to : Matthew Shepcar (wrote original Peaworm, end'98) -; Jonah Cohen (wrote some parts of worm) +; Jonah Cohen (helped writing worm) ;----------------------------- ;----------- TO-DO ----------- ;----------------------------- -; 91% = DONE +; 92% = DONE +; * customizable keys +; * internal levels +; * check levels/gametype +; * enough hiscore saves! +; * complete readme +; 2% * misc (pollish, bugs, &&&) +; * LINK ; 2% * fix deaths linkplay and transmit game/level data ; 2% * make linkplay available for all gametypes (not just deathmatch) +; * CTF ; 1% * fix pea XOR problem in ctf (+dom?) ; * fix wormstop ; 1% * domination?: take control points by running over them and hold them -; * customizable keys -; * complete readme (+custom level info) -; 2% * ... (pollish, &&&) - -; 99% = beta release ;100% = bugs fixed + levels done @@ -78,6 +81,7 @@ _PTEMP_END = $D29A ;end of VAT _load_ram_ahl = $462F ;ahl->page+hl _writeb_inc_ahl = $5567 ;ld (ahl),c _jforce = $409C ;TI-OS stack restored +_EXLP = $4493 ;swap (hl),(de) b times ;----------------------------- ;------- data storage ------- @@ -107,7 +111,6 @@ peaspos = $AE01 ;--- temporary -templevels = $BC00 ;(3*strings) @init namelength = $BC00 ;(1) @menu #ifdef buffer DispBuffer = $BC00 ;(10x57d) @game @@ -121,7 +124,8 @@ DispBuffer = $FC70 .org _asm_exec_ram -WormVersion = 091 +wormVhost = 092 +wormVclient = 192 start: nop @@ -131,7 +135,7 @@ start: .dw WormIcon WormMsg: - .db "WORM by SHIAR -- pre-beta 91%",0 + .db "WORM by SHIAR -- alpha 92%",0 WormIcon: .db 9,2 .db %10010110,%01101111 @@ -145,13 +149,43 @@ WormIcon: .db %11000011,%10000000 levelhead = 'w' -levelhead2 = 91 ;worm levels header = "91" +levelhead2 = 92 ;worm levels header = "92" + +int_handler: + ex af,af' + in a,($03) + bit 3,a + jp z,$0039 + res 0,a + out ($03),a + jp $0039 +int_end: Start: ld (SpSave),sp cal _runindicoff cal _flushallmenus + im 1 + ld a,$D4 + ld h,a + ld l,0 ;ld hl,$D400 + ld d,a + ld e,1 ;ld de,$D401 + ld b,e + ld c,l ;ld bc,$0100 + dec a ;ld a,$D3 + ld (hl),a + ldir + ld hl,int_handler + ld d,a + ld e,a ;ld de,$D3D3 + ld bc,int_end-int_handler + ldir + inc a ;ld a,$D4 + ld i,a + im 2 + cal _RAM_PAGE_7 ld hl,$BFFF ;VAT start ld bc,templevels @@ -236,12 +270,7 @@ searchcomplete: cal _RAM_PAGE_1 ld a,255 ld (bc),a ;end mark - ld hl,templevels - psh hl - or a - sbc hl,bc - pop hl - jp z,_clrWindow ;no ext files: exit + ld hl,templevels-3 dispnextlevel: cal _RAM_PAGE_1 psh hl @@ -254,9 +283,9 @@ dispnextlevel: ld (_curRow),hl pop hl ld a,(hl) - cp 255 + cp 255 ;&& jr nz,displevel - ld hl,templevels + ld hl,templevels-3 ld a,(hl) displevel: inc hl @@ -294,6 +323,9 @@ levselect: loadlevel: ld a,c + or a ;levelfile on page 0 (=internal) + jr z,levelloaded + ex de,hl ;ahl=cde inc b ;b=titlesize+1 skiptitle: @@ -310,21 +342,26 @@ skiptitle: ld d,4 cal loadgametype - cal _SET_ABS_SRC_ADDR + cal _SET_ABS_SRC_ADDR ;levelsstart xor a ld hl,leveldata - cal _SET_ABS_DEST_ADDR - xor a + cal _SET_ABS_DEST_ADDR ;store in mem. ld hl,0 leveldataSize =$-2 cal _SET_MM_NUM_BYTES cal _mm_ldir cal _LOAD_ABS_SRC_ADDR ;->ahl -levelloaded: ld (hiscrposa),a ld (hiscrposhl),hl - cal _RAM_PAGE_1 ;&&& + cal _RAM_PAGE_1 + + ld hl,leveldata + ld de,defsprsize + ldi ;(de),(hl)\inc hl + ld (defsprite),hl +levelloaded: + cal _RAM_PAGE_1 res 2,(iy+13) ;appAutoScroll ld a,r @@ -363,6 +400,9 @@ NegativeSineWave: ld a,1 ld (curlevel),a + +;--- draw menu --- + DisplayMenu: cal _clrWindow ld de,$FC42 ;(10,2) @@ -377,17 +417,17 @@ disptitleloop: ex de,hl dec a jr nz,disptitleloop - ld hl,txtMenu ld de,$0D5A ld (_penCol),de cal _vputs ;by Shiar + ld de,$0207 ld (_curRow),de - cal _puts ;--- + cal _puts ;Level <00> dec e ;$0206 ld (_curRow),de - cal _puts ;Level <00> + cal _puts ;Limit <00> dec e ;$0205 ld (_curRow),de cal _puts ;Worms <2> @@ -399,12 +439,15 @@ disptitleloop: xor a cal menudraw jr howmanyworms + +;--- menu loop --- + mainMenu: cal menucall jr nz,notselect -select: +select: ;2nd/enter ld a,b - dec a ;2nd item + dec a ;2nd item jp z,changeworms jp LetsGetThisPartyOn ;1/3/4 notselect @@ -415,12 +458,14 @@ notselect cp K_RIGHT ld a,b jr nz,mainMenu + +selright: or a jr z,changegame dec a jr z,changenrworms dec a - jp nz,LetsGetThisPartyOn + jp z,changelives changelevel: ld hl,Gametype @@ -438,23 +483,25 @@ curlevel =$+1 changedlevel: ld (curlevel),a _dispcurlevel: - ld hl,$0906 + ld hl,$0807 ld (_curRow),hl cal showA -_mainMenu: - jr mainMenu + jp displives ;mainMenu selleft: ld a,b dec a jr z,bchangenrworms dec a + jp z,bchangelives + dec a jr nz,mainMenu bchangelevel: ld a,(curlevel) dec a jr nz,changedlevel +_mainMenu: jr mainMenu changegame: @@ -488,6 +535,7 @@ changenrworms: ld a,(Gametype) cp 2 ;&& jr c,_mainMenu ;type 0/1 + ld hl,nrworms ld a,(hl) inc a @@ -497,22 +545,62 @@ changednrworms: ld (hl),a dispnrworms: ld a,(hl) ;hl=nrworms - ld hl,$0905 + ld hl,$0805 ld (_curRow),hl add a,'0' cal _putc -dispcurlevel +dispcurlevel: ld a,(curlevel) jr _dispcurlevel ;mainMenu bchangenrworms: ld hl,nrworms ld a,(hl) - dec a - cp 2 ;2-4 - jr nc,changednrworms + dec a ;1-3 + jr nz,changednrworms jr dispcurlevel + +changelives: + cal changelivesInit + inc a + cp 100 + jr nc,displives +changedlives: + ld (hl),a +displives: + cal loadgamecar + ld hl,$0806 + ld (_curRow),hl + cal showA ;liveslimit + sub '0' ;original A + ld l,a + ld a,c + and _datascore + ld a,' ' + jr z,limitok + ld a,'0' +limitok: + cal _putc ;x10 + jp mainMenu +bchangelives: + cal changelivesInit + dec a + jr z,displives + jr changedlives + +changelivesInit: + cal loadgamecar ;c=(gameCar) +;a=(hl)=(Gametype+1)=(wormbeglives) + ld a,(Gametype) ;&&& + cp 3 + ld a,(hl) + ret nc ;change lives + pop hl ;restore stack + jr displives + +;--- handle menukeys --- + menucall: psh bc menuwaitkey: @@ -529,7 +617,6 @@ menuwaitkey: ret z cp K_SECOND ret ;z=select - menupos: ld a,b add a,4 @@ -557,6 +644,10 @@ menudraw: ld a,'*' jp _putc ;a=K_STO +;--- change name --- +; of worm#(nrworms) +;or #1 if Gametype<2 + changeworms: cal _clrWindow ld hl,txtName @@ -644,15 +735,9 @@ continue: ld (ix),a cal _putc inc ix - cal waitnokeypressed + cal releasekeys jr enternameloop -waitnokeypressed: - halt - cal GET_KEY - or a - jr nz,waitnokeypressed - ret chartable: .db 0,".<>!",0,0,0,0 ;down,L,R,up @@ -679,8 +764,8 @@ skipsprite: inc b inc b ;skip 6 ld a,c - and _datasingl - jr nz,skipworms + cp _datasp + jr z,skipworms inc b ;multiplayer lvl inc b inc b ;skip other 3 worms (9 bytes) @@ -703,17 +788,35 @@ skipflags: inc hl noflagstoskip: - cal skiplines ;lines -skiplines: ;boxes - ld a,(hl) ;lines/boxes - add a,a +skipobjects: + ld a,(hl) + inc hl + or a + ret z ;0=end + inc hl + inc hl + inc hl + inc hl + jr skipobjects + +loadgamecar: +;in: (Gametype) +;out: Gametype+1=hl +;build: c=(gameCar)=(hl-1) +; a=(wormbeglives)=(hl) +;destr: acdehl + ld hl,datasingle + ld a,(Gametype) add a,a - inc a - ld b,a ;4x(hl)+1 - -skiplb + ld e,a + ld d,0 + add hl,de + ld a,(hl) + ld (gameCar),a + ld c,a inc hl - dnz skiplb + ld a,(hl) + ld (wormbeglives),a ret ;----------------------------- @@ -724,19 +827,17 @@ LetsGetThisPartyOn: ld a,$17 ;no exit ld (CheckExit),a ;set exit state - ld hl,gamesdata - ld a,(Gametype) - ld e,a - ld d,0 - add hl,de - ld a,(hl) - ld (gameCar),a + cal loadgamecar + ld l,a + ld h,0 ;hl=a + cal _HLTIMES10 ;hl=10*(hl) + ld (scorelimit),hl ;set limit - add hl,de - ld e,8 ;=de - add hl,de + cal loadgamecar ;nc + ld e,24+1 ;=de + sbc hl,de ;datalevels - ld c,a + ld a,c ;(gameCar) and _datasingl jr z,notsingle ld a,1 @@ -744,11 +845,10 @@ LetsGetThisPartyOn: notsingle: ld a,c and _datascore - ld de,$FF64 ;virt.infinate - jr z,setscorelimit - ld d,0 ;de=100 -setscorelimit: - ld (scorelimit),de + jr nz,scorelimitset + dec a ;ld a,$FF ;=no_limit + ld (scorelimit),a +scorelimitset: cal _ldHLind ;ld hl,(hl) ld a,(curlevel) @@ -768,18 +868,21 @@ levelsskipped: linkmatch: cal _clrWindow - ld a,WormVersion - cal send - jr nc,client ;2nd - -host: + ld c,wormVhost + cal Qsend ld hl,txtWaiting cal _puts - cal receive - cp WormVersion - jp nz,linkiniterror - cal send + cal Crecv +; ld a,c + cp wormVclient + jr z,client + cp wormVhost + jr nz,linkiniterror +host: + ld c,wormVclient + cal Qsend + ld a,$18 jr multiplayer linkiniterror: @@ -789,14 +892,10 @@ linkiniterror: client: ld hl,txtReceive cal _puts - cal Qreceive - jp c,linkiniterror - cp WormVersion - jp nz,linkiniterror - ld hl,SwapPos - ld (hl),$f6 + ld a,$f6 multiplayer: + ld (SwapPos),a ld a,2 ld (nrworms),a @@ -806,36 +905,30 @@ multiplayer: GameOver: cal _clrLCD - ld hl,0 - ld (worm1+died),hl -;+died=0 \ +score1=0 - ld (worm2+died),hl - ld (worm3+died),hl - ld (worm4+died),hl - inc h - ld (worm1+score+1),hl -;+score2=0 \ +delay=1 - ld (worm2+score+1),hl - ld (worm3+score+1),hl - ld (worm4+score+1),hl ld hl,worm1set - ld de,worm1+head + ld de,worm1 ld a,4 ;4x (all worms) createwormsloop: - ld bc,19 - ldir ;copy 19 bytes ex de,hl - ld bc,head + ld bc,died add hl,bc - ex de,hl ;de=wormX+head - dec a ;loop + ld (hl),0 ;died=0 + inc hl + ld (hl),0 ;score=0 + inc hl + ld (hl),0 ;score+1=0 + inc hl + ld (hl),2 ;delay=2 + inc hl + ld (hl),3 ;lives=x +wormbeglives =$-1 + inc hl + ex de,hl ;de=wormX+head + ld bc,18 + ldir ;copy 18 bytes + dec a ;loop jr nz,createwormsloop - ld a,(Gametype) - cp 1 ;=peaworm - jr nz,worminitdone - ld (worm1+lives),a -worminitdone: pop hl ;begin of current level StartLevel: @@ -845,10 +938,7 @@ StartLevel: jp nz,nextlevel psh hl - ld b,150 -waitsomemore: - halt - dnz waitsomemore + cal releasekeys cal _clrWindow pop hl ;show end msg or smtn @@ -881,9 +971,11 @@ nextlevel: add hl,bc ;hl=behind sprite jr setsprite defaultsprite: - ld a,defsprsize - ld de,peasprite -setsprite: + ld a,defspritesz +defsprsize =$-1 +defsprite =$+1 + ld de,defspriteimg +setsprite: ;de=@sprite ;a=sprsize ld (sprsize),a ld (spritepos),de @@ -908,9 +1000,9 @@ toobad_noballs: ld hl,worm1 ld a,(gameCar) - and _datanextl + cp _datasp ld b,1 - jr nz,worminit + jr z,worminit ld b,4 worminit: psh bc ; >> 1 @@ -1017,52 +1109,7 @@ NoVertShift: pop hl noctf: -;-draw lines- - - ld a,(hl) - inc hl - or a - jr z,NoLines -DrawLines: - psh af ; >> 1 - cal loaddrawdata - psh hl ; >> 2 - ld l,(hl) - ld h,a - cal Line - inc d - inc h - cal Line - inc e - inc l - cal Line - dec d - dec h - cal Line - pop hl ; << 1 - inc hl - pop af ; << 0k - dec a - jr nz,DrawLines -NoLines: - - ld a,(hl) - inc hl - or a - jr z,noboxes -drawboxes: - psh af - cal loaddrawdata - psh hl - ld l,(hl) - ld h,a - cal drawbox - pop hl - inc hl - pop af - dec a - jr nz,drawboxes -noboxes: + cal drawstuff ;----------------------------- @@ -1112,26 +1159,26 @@ maskline: ld a,0 gameCar =$-1 and _datalink - jr z,SwapPos ;no link + jr z,initfinished ;no link + xor a - ld (worm2+input),a + ld (worm2+input),a ;worm 2 via link ld (worm2+left),a - ld (Speed),a - + ld (Speed),a ;max.speed SwapPos: ;$18 xx -> $F6 xx + ; jr xx -> or xx jr initfinished inc a - ld (worm2+left),a - ld hl,(worm1+pos) - ld de,(worm2+pos) - ld (worm2+pos),hl - ld (worm1+pos),de - ld a,(worm1+heading) - ld b,a - ld a,(worm2+heading) - ld (worm1+heading),a - ld a,b - ld (worm2+heading),a + ld (worm2+left),a ;1 + ld hl,worm1 + ld de,worm2 + ld b,4 ;+heading +pos + cal _EXLP ;swap positions +;&&& over link + ld hl,worm1+name + ld de,worm2+name + ld b,maxnamelength + cal _EXLP ;swap positions initfinished: ld b,startdelay @@ -1249,6 +1296,8 @@ thislevel =$+1 Exit: ld sp,0 ;pop all SpSave = $-2 + ld a,D0HD1H + out (7),a cal _clrWindow ld hl,txtGO cal _puts @@ -1278,11 +1327,11 @@ displayWormStats: xor a cp (hl) ;input=0 = link jr nz,NoLinkIndic - ld b,7 + ld b,7 ;{DOWN} inc hl ;+left cp (hl) jr z,hostLinkIndic - dec b + dec b ;{UP} hostLinkIndic: ld a,8 ld (_curCol),a @@ -1330,13 +1379,14 @@ checkhilevel: ld c,a ld a,0 hilvlposa =$-1 - ld hl,0 + ld hl,nrlevels hilvlposhl =$-2 ;save external cal _writeb_inc_ahl ;ld (ahl),c hilevelcheckdone: ld a,(gameCar) and _datasingl + jr z,hiscorecheckdone checkhiscore: cal loadhiscoreposinahl @@ -1396,35 +1446,53 @@ ExitNoStats: ld hl,_asapvar rst 20h ;_ABS_MOV10TOOP1 rst 10h ;_FINDSYM - ld hl,4 + ld hl,savestart-_asm_exec_ram+4 xor a add hl,de adc a,b ;ahl=bde+4 cal _SET_ABS_DEST_ADDR xor a - ld hl,_asm_exec_ram + ld hl,savestart cal _SET_ABS_SRC_ADDR - ld hl,end-_asm_exec_ram + ld hl,saveend-savestart cal _SET_MM_NUM_BYTES cal _mm_ldir cal releasekeys res 4,(iy+9) set 2,(iy+13) + im 1 ;remove keyfix jp _clrWindow loadhiscoreposinahl: ld a,(Level) ld b,a + + ld h,0 ;hl= + ld a,(nrlevels+1) ;# peaworm lvls + add a,a + ld l,a + ld a,(Gametype) - or a -externalhiscoresavepos: - ld a,0 -hiscrposa =$-1 - ld hl,0 + dec a + ld c,a + dec a ;z=(Gametype)=2 + jr z,tronhi + ld l,h ;hl=0 +tronhi: + + xor a ;ahl=0(+x) + psh bc + ld bc,defhiscrpos hiscrposhl =$-2 - ret z ;(Gametype)=0 + add hl,bc + pop bc + adc a,0 +hiscrposa =$-1 ;ahl=saveloc + + inc c + ret z ;(Gametype)=0 addlevelposition: cal _AHL_PLUS_2_PG3 dnz addlevelposition @@ -1469,7 +1537,6 @@ safewormsizedone: ;de=ix+head ld (ix+tail+1),d ld (ix+tail),e ;head=tail/size=0 - jr norespawn ret unnamedlabel: @@ -1479,16 +1546,19 @@ unnamedlabel: respawndue: ld l,a cal inputcall + ld (sendbyte),a ld a,h ;previous cp l ;changed? ret z + ld (ix+delay),a ;=0 + ret saverespawncounter: ld (ix+delay),a -norespawn: - ld a,(gameCar) - and _datalink - jr nz,inlink - ret + jr inputcall +; ld a,(ix+input) +; or a +; jr z,inlink +; ret inkeys: ;use jp not call! out (1),a ;nop\nop @@ -1514,22 +1584,26 @@ inputcall: jr nz,inkeys inlink: - ld a,0 -sendbyte =$-1 ld b,(ix+left) dec b jr z,receivefirst - cal send - cal receive - ld l,a + psh hl + ld c,0 +sendbyte =$-1 + cal Csend + cal Crecv + pop hl + ld l,c ret receivefirst: - psh af - cal receive - ld l,a - pop af psh hl - cal send + cal Crecv + pop hl + ld l,c + psh hl + ld a,(sendbyte) + ld c,a + cal Csend pop hl ret @@ -1540,6 +1614,13 @@ HandleWorm: dec a jp nz,respawncheck + ld a,(Gametype) + cp gametron + jr nz,notron + ld de,1 + cal IncScore +notron: + ld l,(ix+heading) cal inputcall donediddelydone: @@ -1671,6 +1752,7 @@ peagrowth =$-1 pop hl ; << call pop hl ; << call pop hl ; << levelp new + ld (ix+delay),2 jp StartLevel chkpeahit: ;hl=peapos @@ -1832,9 +1914,16 @@ Drawworm: ld b,(ix+pos+1) ld a,(Gametype) + ld d,a cp gamerace cal z,checkhitlapline + cal set4pixels + dec c + ld a,d + cp gametron + ret z ;keep tail in "Tron" + ld l,(ix+head) ld h,(ix+head+1) ld (hl),c @@ -1845,8 +1934,6 @@ Drawworm: ld (ix+head),l ld (ix+head+1),h - cal set4pixels - ld a,(ix+grow) dec a jr z,removetail @@ -2042,7 +2129,7 @@ chkloopx: DrawPea: ;hl=(PeaY) ld b,h ld c,l - ld de,peasprite + ld de,0 spritepos =$-2 jp PutSprite ;||-ed @@ -2080,6 +2167,9 @@ scorecommon: ld (ix+score),l ld de,0 scorelimit =$-2 + inc e + jr z,showstats ;de=$FF??=no limit + dec e cal _cphlde jp nc,Exit @@ -2110,14 +2200,18 @@ showstatloop: showstat: ld a,(gameCar) - and _datalivel - jr nz,showlives + and _datascore + jr z,showlives showscore: ld h,(ix+score+1) ld l,(ix+score) cal _D_HL_DECI jr __vputs showlives: + ld a,(Gametype) + cp gametron + jr z,showscore + ld a,(ix+lives) add a,'0' __vputmap: @@ -2498,7 +2592,8 @@ PutSprite: ;||@(b,c) cal FindPixel putspr: ld (beginbit),a - ld a,(sprsize) + ld a,0 +sprsize =$-1 ld b,a ;rows sprloopy: psh bc ;rows @@ -2531,21 +2626,61 @@ nextbitok: dnz sprloopy ret -;--- line --- +;--- objects --- + +drawstuff: + ld a,(hl) + inc hl + or a ;0 = + ret z ;no more -loaddrawdata: ld d,(hl) inc hl ld e,(hl) inc hl - ld a,(hl) + ld b,(hl) inc hl + psh hl + ld l,(hl) + ld h,b + + dec a ;1 = line + cal z,drawline + dec a ;2 = fatline + cal z,drawfatline + dec a ;3 = box + cal z,drawbox + + pop hl + inc hl + jr drawstuff + +drawbox: ;(d,e)-(h,l) + ld b,l ;Delta-y + ld l,e +boxloop: + cal drawline + inc l + inc e + dnz boxloop ret +drawfatline: + cal drawline + inc d + inc h + cal drawline + inc e + inc l + cal drawline + dec d + dec h + jp drawline + ;LINE (d,e)-(h,l) ;destroyes a -Line: +drawline: psh bc psh hl psh de @@ -2646,141 +2781,119 @@ line4sm: dnz LineLoopSteep jr DoneLine -drawbox: ;(d,e)-(h,l) - ld b,l ;Delta-y - ld l,e -boxloop: - cal Line - inc l - inc e - dnz boxloop - ret - ;----------------------------- ;----------- link ------------ ;----------------------------- -TIMEOUT = $1000 +timeout = $800 -LinkBreak: - pop hl - ld a,D0HD1H - out (7),a - jp Exit +checklink: + dec de + ld a,d + or e + jr z,linkerror + ld a,$BF + out (1),a + in a,(1) + bit 6,a + jp z,Exit -receive: - cal GET_KEY - cp K_EXIT - jp z,LinkBreak in a,(7) and %11 - cp %11 - jr z,receive - in a,(7) - and %11 - cp %11 - jr z,receive - ld b,8 - cal ReceiveCont - jr c,receive ret -Qreceive: - ld b,8 -receiveloop: - ld de,TIMEOUT -WaitRecBit: - cal CheckLink - jr z,LinkFailed - cp %11 - jr z,WaitRecBit -ReceiveCont: - sub %10 - ld a,%10 - ld d,D0LD1H - jr c,ReceiveLow - rra - ld d,D0HD1L -ReceiveLow: - rr c - ld (AckBit),a - ld a,d - out (7),a - ld de,TIMEOUT -WaitAckRec: - cal CheckLink - cp 0 -AckBit =$-1 - jr nz,WaitAckRec - ld a,D0HD1H - out (7),a - ld d,4 -WaitReadyRec: - dec d - jr z,ReadyRec - in a,(7) - cp %11 - jr nz,WaitReadyRec -ReadyRec: - dnz receiveloop - ld a,c +linkerror: + scf + ld a,%11 + pop hl ret -send: +;-------------- +;---- SEND ---- +;-------------- + +Csend: ;--- send 8 bits in A --- destr:abcdehl --- ld c,a - ld b,8+1 - jr SendAcked +Csendloop: + cal Qsend + ret nc ;NC = all ok + ld a,D0HD1H + out (7),a ;both high + jr Csendloop ;CF = error +Qsend: ;--- try to send 8 bits in C; CF=error --- destr:abcdehl --- + ld de,timeout + cal checklink + cp %11 ;are they? + scf + ret nz ;nope, wait + ld b,8 ;bits to send sendloop: - rr c - ld a,D0LD1H - jr nc,SendLow - ld a,D0HD1L -SendLow: + ld de,timeout + rl c ;bit to send in cf + ld a,D0LD1H ;0: lower white + jr nc,sendbit + ld a,D0HD1L ;1: lower red +sendbit: + out (7),a ;lower one (send bit) +sendwaitack: + cal checklink ;other calc must lower other wire + jr nz,sendwaitack + ld a,D0HD1H ;raise one, ok to raise other out (7),a - ld de,TIMEOUT -WaitAckSend: - cal CheckLink - jr nz,WaitAckSend -SendAcked: +sendfinish: + cal checklink + cp %11 ;both raised (by other calc) + jr nz,sendfinish + nop \ nop + dnz sendloop ;repeat for all bits + xor a ;nc... + ret ;=ok + +;-------------- +;---- RECV ---- +;-------------- + +Crecv: ;--- receive 8 bits into A/C --- destr:abcdehl --- + cal Qrecv + ret nc ;return if all went ok ld a,D0HD1H - out (7),a - ld de,TIMEOUT -WaitReadySend: - cal CheckLink + out (7),a ;raise both on error + jr Crecv ;and try again + +Qrecv: ;--- receive 8 bits into A/C; CF=error --- destr:abcdehl --- + ld de,timeout + cal checklink + jp z,Exit ;both low = error, quit cp %11 - jr nz,WaitReadySend - dnz sendloop -LinkSuccess: - .db $F6 ;or NN (skip scf) -LinkFailed: scf - ld a,c + ret z ;both high = nothing yet, wait + ld b,8 ;bits to receive +recvloop: + ld de,timeout +recvwait: + cal checklink + cp %11 + jr z,recvwait ;both high = nothing sent (yet) + rra ;received bit in cf + ld a,D0LD1H + jr c,received ;lower white wire as well + ld a,D0HD1L ;lower red +received: + rl c ;save bit in c + out (7),a ;both wires low +recvwaitack: + cal checklink + jr z,recvwaitack ;same wire will be raised again by other calc + ld a,D0HD1H + out (7),a ;raise both +recvfinish: + dnz recvloop ;repeat for all bits + xor a ;nc=no error + ld a,c ;result in a ret -CheckLink: - pop hl - dec de - ld a,d - or e - jr z,LinkFailed - - ld a,$BF - out (1),a -; nop \ nop - in a,(1) - psh af - ld a,%11111111 - out (1),a - pop af - bit 6,a - jr z,LinkFailed - - in a,(7) - and %11 - jp (hl) - ;----------------------------- ;---------- levels ----------- ;----------------------------- @@ -2789,16 +2902,29 @@ LevelDef: .db 5,4,15,15,0,0 ;peas,speed,growth,begin_size,sprite,balls .db 0,2,63 ;start d, y, x .db 128,57 ;field width (128-255), height (57-255) - .db 0,0 ;no additional lines, boxes + .db 0 ;no additional lines, boxes .db 255 ret LevelDefM: - .db 8,0,15,15,0,0 + .db 8,4,15,15,0,0 .db $40,30,2,$C0,30,125, $00,2,64,$80,54,64 .db 128,57 - .db 0,0 + .db 0 + + .db 8,0,18,12,5 + .db %1110000,%10001000,%10001000,%10001000,%1110000,0 + .db $40,30,2,$C0,30,125, $00,2,64,$80,54,64 + .db 128,57 + .db 0 + +LevelDefT: + .db 8,4,18,12,5 + .db %1110000,%10001000,%10001000,%10001000,%1110000,0 + .db $40,30,64,$C0,30,64, $00,30,64,$80,30,64 + .db 128,57 + .db 0 ;----------------------------- ;---------- data ------------- @@ -2823,17 +2949,18 @@ wtPicture: .db %00001111,%10000011,%11100000,%00011111,%00000011,%00000001,%10000000,%00011000 txtMenu: .db "by Shiar",0 - .db "Have fun!",0 ;4th menu item - .db "Level ",$CF,"??",5,0 ;3rd - .db "Worms ",$CF,"?",5,0 ;2nd + .db "Level 00",0 ;4th menu item + .db "Limit 00 ",0 ;3rd + .db "Worms 0",0 ;2nd txtGame: .db "Singleplayer",0 ;0 (1st) txtGame2: .db "Peaworm ",0 ;1 (next 1st) - .db "Deathmatch",0 ;2 - .db "Foodmatch ",0 ;3 - .db "LinkMatch",0 ;4 - .db "Race ",0 ;5 - .db "CTF ",0 ;6 - .db "Domination",0 ;7 + .db "Tron ",0 ;2 + .db "Deathmatch",0 ;3 + .db "Foodmatch ",0 ;4 + .db "LinkMatch",0 ;5 + .db "Race ",0 ;6 + .db "CTF ",0 ;7 +; .db "Domination",0 ;8 txtLevsel: .db $CF," Select levels: ",5,0 txtName: .db "Enter name player ",0 txtWaiting: .db "Waiting...",0 @@ -2860,63 +2987,62 @@ txtReady: .db "Prepare!",0 txtposReady = 7 txtGO: .db "----- GAME OVER -----",0 -gamesdata: - _datalink = %00000001 ;linkplay _datalivel = %00000010 ;lives=0 limit _datafoodl = %00000100 ;left=0 limit _datanextl = %00001000 ;next level if left=0 _datasingl = %00001000 ;singleplayer=1 + ;1=hiscore+keep_length _datafood = %00010000 ;food present -_________ = %00100000 ; _datadie = %01000000 ;worm dies on impact _datascore = %10000000 ;score>=100 limit _datamultpeas = %00100000 +_datasp = %01011110 -gamesingle = 0 -datasingle: .db %01011110 -gamepeas = 1 -datapeas: .db %01011010 -gamedeathm = 2 -datadeathm: .db %01000010 -gamefoodm = 3 -datafoodm: .db %11010000 -gamelinkm = 4 -datalinkm: .db %01000011 -gamerace = 5 -datarace: .db %10000000 -gamectf = 6 -datactf: .db %11100000 -gamedomin = 7 -datadomin: .db %01000000 ;==(8 modes) - -datalevels: .dw LevelDef, LevelDef +datalevels: .dw LevelDef, LevelDefM + .dw LevelDefT,LevelDefM .dw LevelDefM,LevelDefM .dw LevelDefM,LevelDefM - .dw LevelDefM,LevelDefM -nrlevels: .db 2,2,2,2,2,2,2,2 +nrlevels: .db 1,2,2,2,2,2,2,1 ;=defaults + +savestart: + +gamesingle = 0 +datasingle: .db %01011110,3 ;3 lives ( + .db %11110111,%00,%01111110,%10,%100 ;< > worm1name: .db "worm #01",0 worm2set: .dw worm2p,worm2p - .db %11111011,3,%11,%00111111,%10000,%1000 ;f1 f2 + .db %11111011,%11,%00111111,%10000,%1000 ;f1 f2 worm2name: .db "worm #02",0 worm3set: .dw worm3p,worm3p - .db %11111011,3,0,%01011111,%10,%100 ;sto , + .db %11111011,0,%01011111,%10,%100 ;sto , worm3name: .db "worm #03",0 worm4set: .dw worm4p,worm4p - .db %11111011,3,0,%01111101,%10,%1 ;enter + + .db %11111011,0,%01111101,%10,%1 ;enter + worm4name: .db "worm #04",0 -end: +defhiscrpos: + .dw 0,0,0,0,0 -defsprsize = 4 -sprsize: .db 4 -peasprite: .db %01100000 - .db %11110000 - .db %11110000 - .db %01100000 +saveend: ;set: heading = 0 ;level* @@ -2927,10 +3053,10 @@ died = 8 ;game score = 9 ;game delay = 11 ;game ;19B @game -head = 12 ;4B (head=tail) -tail = 14 ;also@next level -storepos = 16 -lives = 17 +lives = 12 +head = 13 ;4B (head=tail) +tail = 15 ;also@next level +storepos = 17 reserv = 18 ;loop ;race:lap ;ctf:pea @@ -2944,6 +3070,29 @@ startdelay = 30 respawndelay = 30 maxnamelength = 8+1 +.db "WWW.SHIAR.ORG WWW.SHIAR.ORG " +.db "WWW.SHIAR.ORG WWW.SHIAR.ORG " +.db "WWW.SHIAR.ORG WWW.SHIAR.ORG " +.db "WWW.SHIAR.ORG WWW.SHIAR.ORG " +.db "WWW.SHIAR.ORG WWW.SHIAR.ORG " +.db "WWW.SHIAR.ORG WWW.SHIAR.ORG " +.db "WWW.SHIAR.ORG WWW.SHIAR.ORG " +.db "WWW.SHIAR.ORG WWW.SHIAR.ORG " +.db "WWW.SHIAR.ORG WWW.SHIAR.ORG " +.db " shiar0@hotmail.com",0 + +defspritesz = 4 +defspriteimg: .db %01100000 + .db %11110000 + .db %11110000 + .db %01100000 + +deflevels: + .db 15,"Internal Levels" + + .db 0,deflevels/256,deflevels&255 +templevels: + ;----------------------------- ;----------- end ------------- ;-----------------------------