Login

Subversion Repositories NedoOS

Rev

Rev 882 | Rev 1916 | Go to most recent revision | Blame | Compare with Previous | Last modification | View Log | Download | RSS feed

atm=1

ID_DOOR=0+(22*2);127

;ZX data:
;music=0;1

debug=0
demorec=0
demoplay=0;1

;control:
doublespeed=0;1
doublerotate=1
autostrafe=1
kempston=0;1
mouse=1
mindist=118 ;max=111 ;111 излом ;120 застрял в дверях

colour=7
ceilingcolour=0
floorcolour=colour*9

showfps=0
showscans=0
crosshair=0

sprites=1;0

scale64=3;1

;render:
scrwid=32 ;chr$
scrtopx=(32-scrwid)/2
        if atm
scrhgt=200;128 ;pixels
scrhgtpix=scrhgt
Ycenter=100
Ytop=Ycenter-(scrhgt/2)
Ybottom=Ycenter+(scrhgt/2)
scrbase=0x4000+4
scrtop=Ytop*40+scrbase
        else
scrhgt=16;24 ;chr$ (10,12,...,24)
scrhgtpix=scrhgt*8
scrtop=(24-scrhgt)*16+#4000+scrtopx
attrtop=(scrtop/8)&0x300+(0xff&scrtop)+0x5800
lowscrtop=#4800+scrtopx
lowattrtop=(lowscrtop/8)&0x300+(0xff&lowscrtop)+0x5800
lowscrhgt=8 ;chr$
lowscrhgtpix=lowscrhgt*8
        endif

        IF scale64
maxscale=63
 IF scale64-3 == 0
lowmaxscale=28 ;fit in low screen
 ELSE
lowmaxscale=19 ;fit in low screen
 ENDIF
        ELSE
maxscale=127
lowmaxscale=25 ;fit in low screen
        ENDIF
mapdifbit=5;7
lores=0
        IF atm == 0
optres=1&(1-lores) ;+22t на мелких, выигрыш на крупных
        ELSE
lores=1
optres=0
        ENDIF
optfast=0
loresspr=0|atm
optresspr=1&(1-loresspr) ;выигрыш на крупных
loresspr_hires=loresspr&(1-lores)
pixperchr=8>>lores
corr_coord=1
interpolate=4;16;0

        if lores
SCRWIDPIX=scrwid*4
        else
SCRWIDPIX=scrwid*8
        endif

doublescr=1

        align 256
distbuf;=#BA00 ;#300 ;ID,texx,dist
        ds 0x300
scrbuf=#6040
        if atm == 0
lowscrbuf=(scrhgtpix-lowscrhgtpix)/2+scrbuf
        endif
scrbufflag=scrbuf&#FF00+32
dropline=scrhgt*8+(0xff&scrbuf) ;Y=192
map=scrbuf-#3F ;+0 занят dropline, +32 занят флагом высоких
mapend=map+#2000
invmap=1

        if atm == 0
tscale=#C000 ;128x64, множители 0 и 63 выдают константы 0 и 3
             ;64x64 при scale64=1
        endif

timer
        dw 0

      IF atm
       MACRO setpgfast pg
        LD A,pg
        setpgafast
       ENDM
       MACRO setpgafast
        ;LD (curpg),A
        ;LD BC,#FFF7
        ;OUT (C),A
        SETPGC000
       ENDM
      ELSE ;~atm
       MACRO setpg pg
        LD A,pg
        setpgA
       ENDM
       MACRO setpgA
        CALL SETPGA
       ENDM
       MACRO setpgfast pg
        LD A,pg
        setpgafast
       ENDM
       MACRO setpgafast
        LD (curpg),A
        LD BC,#7FFD
        OUT (C),A
       ENDM
      ENDIF ;~atm
     


wascorrlogd
        INCBIN "corlogd_"
        ORG $-256
       DUP 256
        DB {$+(scrtopx*8)}&0xff
       EDUP
       IF lores
        ORG $-256
_=$
       DUP 128
        DB {_}&0xff
_=_+2
       EDUP
        DS 128
       ENDIF
wasda
        INCBIN "da"
        ORG $-256
       DUP 256
        DB 0xff&({$}+128)
       EDUP
        ORG $-256
       DUP 256
        DB 0xff&({$+(scrtopx*8)})
       EDUP
       IF lores
        ORG $-256
_=$
       DUP 128
        DB {_}&0xff
_=_+2
       EDUP
        DS 128
       ENDIF

       IF showfps
PRDIG
        LD L,15
        INC L
        SUB C
        jr NC,$-2
        ADD A,C
        PUSH AF
        LD A,L
        ADD A,A
        ADD A,A
        ADD A,A
        INC A
        LD L,A
        LD H,#3D
        PUSH DE
        LD B,6
        LD A,(HL)
        ld (DE),A
        INC L,D
        DJNZ $-4
        POP DE
        POP AF
        INC E
        RET
       ENDIF

TEXCODEGO
       IF atm == 0
        LD HL,0;-2
        ADD HL,SP
        LD (clscrbufsp),HL
        LD (eorfillsp),HL
       endif

       IF atm
        call setpgmap4000
       ENDIF
        CALL RECMAP

        LD HL,tcos
REtcos0
       DUP 2;4
        SRA (HL)
       EDUP
        INC L
        jr NZ,REtcos0

ZXLOOP
       if atm
       call changescrpg
;        ld a,1
;curscreen=$+1
;        xor 1
;        ld (curscreen),a
;         add a,a
;         add a,a
;         add a,a
;         ld (imer_curscreen_value),a
        ld hl,(timer)
        ld (endoflastredrawtimer),hl
       endif

       IF atm == 0
        LD A,pgscale
        CALL SETPG
       ENDIF

;------------------------
       IF atm
        call setpgmap4000
       ENDIF
        LD HL,(timer)
oldtimer=$+1
        LD BC,0
        LD (oldtimer),HL
        OR A
        SBC HL,BC
        jr Z,nONTIMER
         ld bc,8
         or a
         sbc hl,bc
         add hl,bc
         jr c,ONTIMER0
         ld h,b
         ld l,c ;hl<=8
ONTIMER0
        PUSH HL
        CALL CONTROL ;там же логика
        POP HL
        DEC HL
        LD A,H
        OR L
        jr NZ,ONTIMER0
nONTIMER
       IF atm == 0
       IF doublescr
        LD A,#10
        CALL SETPG
       ENDIF
       ENDIF
       ;HALT
        CALL SCAN

       IF doublescr
;ждать флаг ожидания готовности экрана (включается по прерыванию)
;иначе будет так:
;фрейм 1:
;видим экран0, рисуем экран1
;фрейм 2:
;видим экран0, закончили рисовать экран1, [вот тут нужно ожидание], начали рисовать экран0 (хотя его видим)
;фрейм 3:
;видим экран1
;готовность - это когда текущий таймер != таймер конца прошлой отрисовки
;проверяем оба таймера, а то могло случиться системное прерывание
EmulatePPU_waitforscreenready0
        ld hl,(timer)
endoflastredrawtimer=$+1
        ld de,0
        or a
        sbc hl,de
        jr z,EmulatePPU_waitforscreenready0
       ENDIF

       IF atm
pgscalersnum=$+1
        LD A,0
        setpgafast
       
;        LD A,2
;setpgs_scr_xor=$+1
;        XOR 2
;        LD ($-1),A
;setpgs_scr_low=$+1
;        XOR 0xff-1;#7F-pgattr1
;        ld (curscrpg_low),a
;       PUSH AF
;        SETPG4000
       call getuser_scr_low
       SETPG4000
        CALL DWCLSALL
        xor a;LD A,0
        CALL DRAWWALLS
       call getuser_scr_high
       SETPG4000
;       POP AF
;setpgs_scr_high_xor_low=$+1
;        XOR 4;pgattr1^pgpix1
;        SETPG4000
       
        CALL DWCLSALL
        LD A,1
        CALL DRAWWALLS
       IF sprites
       CALL SCANMONS
       CALL DRAWSPRITES
       ENDIF

       ELSE ;~atm

        CALL CLSCRBUF
        CALL DRAWWALLS
        CALL CHECKHEIGHTS
       IF sprites
       CALL SCANMONS
       CALL DRAWSPRITES
       ENDIF
       IF crosshair
        CALL CROSSHAIR
       ENDIF
       IF doublescr
        LD A,(curscr)
newscr=$+1
        CP 0
        jr Z,nohalt
        HALT ;if CPU is too fast
nohalt
        LD A,#17
        CALL SETPG
       ENDIF
        CALL EORFILL
       IF doublescr
        LD A,(newscr)
        XOR 8
        LD (newscr),A
       ENDIF
       ENDIF
;-----------------------
       IF showfps
        LD HL,IMfps
        INC (HL)
       ENDIF
       
curkey=$+1
        ld a,0
        cp key_esc
        jr z,ZXLOOPQUIT
        cp key_redraw
        call z,redraw
       
       ;LD A,0xfe
       ;IN A,(0xFE)
       ;rra ;caps shift
       ;JP c,ZXLOOP
       ;LD A,0x7F
       ;IN A,(0xFE)
       ;RRA ;space
       ;JP NC,ZXLOOPQUIT
       
        jr ZXLOOP
ZXLOOPQUIT
        ret

redraw
        xor a
        ld (curkey),a ;чтобы redraw не повторялся
        call redraw_cls
        ld a,1
redraw_cls
        ;ld (curscrnum),a ;for interrupt
        ld e,a
        OS_SETSCREEN
        ld e,0
        OS_CLS
        ret

        INCLUDE "WSCAN10.asm"
        INCLUDE "WREND.asm"
        INCLUDE "WCTRL.asm"

;переменные рендера (обновляются в начале рендера)
curXx
curx    DB #80
curX    DB #0
curYy
cury    DB #80
curY    DB #0
curxy   DW 0
curyx   DW 0
curYX   DW 0
curangle
        DW tsin
demobegin
       IF demoplay
        INCBIN "demorec9"
       ELSE
        DB %00111111 ;all keys released
       ENDIF

        ;DISPLAY "PROG END=",$

        align 256 ;DS .(-$)
tables
wastables
shift=tables-$
tlogd2sca=$+shift
       IF scale64
       IF scale64 == 3
        INCBIN "logd2sc3"
       ELSE
        INCBIN "logd2sc2"
       ENDIF
       ELSE
        INCBIN "logd2sc_"
       ENDIF
tsqr2=$+shift
        INCBIN "sqr2int"
tlogd=$+shift
        INCBIN "logd"
tcorrlogd=$+shift
       DUP 256
        DB {wascorrlogd+$-tcorrlogd}&0xff
       EDUP
tcos=$+shift
        INCBIN "cos"
tlogcos=$+shift
        INCBIN "pluslcos"
tda=$+shift
       DUP 256
        DB {wasda+$-tda}&0xff
       EDUP
tctg=$+shift
        INCBIN "plusctg"
tsin=$+shift
        INCBIN "sin"
tscaljps=$+shift
        ds 256;INCBIN "scaljps"
tID=$+shift
        MACRO WALL pgnum,num2
        DB pgnum,num2;-pgnum,num2
        ENDM
       DUP 64+16 ;skip and 0..15
        WALL 0,#02
       EDUP
        MACRO PGWALL pgnum
        WALL pgnum,#02
        WALL pgnum,#42
        WALL pgnum,#82
        WALL pgnum,#C2
        ENDM
        PGWALL 0
        PGWALL 1
        PGWALL 2
        PGWALL 3
        PGWALL 4
       DUP 64-16-20 ;?..63
        WALL 0,#02
       EDUP
cursprites=$+shift
        DS 256
ltables=$-wastables

RECMAP
        LD HL,WASMAP
        LD DE,0x4000
       PUSH DE
        LD BC,szMAP
        LDIR
       POP HL
        LD DE,level
        LD BC,endlev-level
        LDIR
       
          ld de,MONSTRS
       
       if atm
       LD A,(YX+1) ;Y
       SUB 0xA0
       SUB map/256+31
       CPL
       LD (IMcurYy+1),A
       LD A,(YX) ;X
       INC A
       LD (IMcurXx+1),A
       endif
INImons LD A,(HL)
        LDI
        AND (HL)
        LDI
        INC A
        JR Z,INImonsQ
        LD BC,6
        LDIR
        JR INImons
INImonsQ ;
       EXD
       if atm
        LD H,map/256+31
       else
        LD H,map/256
       endif
       IF invmap
       LD L,map&0xff
       LD C,1
       JR GETMAPL
       ENDIF
GETMAP0
       IF invmap
        LD L,0xff&(map+32)
       ELSE
        LD L,map&0xff
       ENDIF
        LD C,2
GETMAPL LD B,32;33
GETMAP1 LD A,(DE)
        INC DE
        LD (HL),0
        CP 13
        JR Z,GETMCR
       IF atm
       jr NC,GMNRLE
        LD A,(DE)
        INC DE
       DEC A
GMRLE
        INC L
        LD (HL),0
        DEC B
        DEC A
        jr NZ,GMRLE
        LD A,32
GMNRLE
       ENDIF
        CP 32
        JR Z,GETMAPE
       IF atm
      CP 64    ;
      jr NC,$+4  ;
      ADD A,64 ;todo kill
       ADD A,128-64
         ;cp 128+ID_DOOR;(22*2)
         ;jr nz,$+4
         ;res 7,a ;ld a,ID_DOOR
       ELSE
       SUB "1";+128
      CPL
      ADD A,A
     CP -20
     jr NC,$+4
     LD A,-20
       ENDIF
       LD (HL),A
GETMAPE INC L
        DJNZ GETMAP1
        JR GETMOK
GETMCR  LD (HL),0
        INC L
        DJNZ GETMCR
GETMOK
       IF invmap
       LD L,map&0xff
       ENDIF
        DEC C
        jr NZ,GETMAPL
       if atm
        LD A,H
        DEC H
        CP map/256
        JR NZ,GETMAP0
       else
        INC H
        BIT 6,H
        JR Z,GETMAP0
       endif

        if invmap
        LD HL,MONSTRS+1 ;1+начало табл.монстров/предметов
remons0
        LD A,(HL) ;X
         inc (hl)
        INC A
       jr Z,remonsq
        ;ld a,0xff&(map+32+map+0)
        ;sub (hl)
        ;ld (hl),a ;???
        INC L
        inc L
        LD A,(HL) ;Y
       SUB 0xA0
       SUB map/256+31
       CPL
        ld (hl),a
        LD A,L
        ADD A,6
        LD L,A
        JP NC,remons0
        INC H
        JP remons0
remonsq
        endif

       IF atm == 0
        LD HL,#4000
        CALL INICLS
       IF doublescr
        LD A,#17
        CALL SETPG
        LD HL,#C000
        CALL INICLS
       ENDIF        
        XOR A
        LD H,scrbuf/256
        LD C,scrwid
PRECLS  LD L,scrbuf&0xff
        LD B,scrhgtpix
        LD (HL),A
        INC L
        DJNZ $-2
        INC H
        DEC C
        jr NZ,PRECLS
       ENDIF

        LD BC,#FBDF
        IN A,(C)
        LD (mouseoldx),A
        RET
       
       if atm==0
INICLS
        LD D,H
        ld E,1
        LD BC,#1800
        LD (HL),L
        LDIR
        LD BC,767
        LD (HL),colour
        LDIR
        RET
       endif