Kernel 0.93+

This commit is contained in:
Rémy GIBERT 2019-09-27 16:53:44 +02:00
parent 55ddec10bd
commit 1431388c45
7 changed files with 133 additions and 112 deletions

Binary file not shown.

View File

@ -6,11 +6,13 @@ REPMAX .EQ 16
STRINGMAX .EQ 16 STRINGMAX .EQ 16
WSIZE .EQ 4096 WSIZE .EQ 4096
*-------------------------------------- *--------------------------------------
PAK.B.SHORT3 .EQ %0 PAK.B.STOREn .EQ %0
PAK.B.SHORT4 .EQ %10 PAK.B.BYTE8 .EQ %0
PAK.B.REPn .EQ %110 PAK.B.TOP8 .EQ %10
PAK.B.BACKLINK .EQ %1110 PAK.B.TOP16 .EQ %110
PAK.B.STOREn .EQ %1111 PAK.B.TOP24 .EQ %1110
PAK.B.REPn .EQ %1111
PAK.B.BACKLINK .EQ %1
*-------------------------------------- *--------------------------------------
* STRINGn : 0 xxxx (1-16) * STRINGn : 0 xxxx (1-16)
* { * {
@ -27,13 +29,15 @@ PAK.B.STOREn .EQ %1111
* !!! USED TO STOP UNPACK,NO EOF TOKEN!!! * !!! USED TO STOP UNPACK,NO EOF TOKEN!!!
*-------------------------------------- *--------------------------------------
S.PAKSHNK.ULEN .EQ 0 Uncompressed length S.PAKSHNK.ULEN .EQ 0 Uncompressed length
S.PAKSHNK.TOPLEN .EQ 2 S.PAKSHNK.TOPCNT .EQ 2
S.PAKSHNK.TOPBYTES .EQ 3
* TOP Bytes .... * TOP Bytes ....
* DATA * DATA
S.PAKSHNK .EQ 2+1+24 Max
*-------------------------------------- *--------------------------------------
S.PAKSTAT.PASS1 .EQ 0 S.PAKSTAT.PASS1 .EQ 0
S.PAKSTAT.PASS2 .EQ 2 S.PAKSTAT.PASS2 .EQ 2
S.PAKSTAT.STR .EQ 4 S.PAKSTAT.BYTE8 .EQ 4
S.PAKSTAT.TOP8 .EQ 6 S.PAKSTAT.TOP8 .EQ 6
S.PAKSTAT.TOP16 .EQ 8 S.PAKSTAT.TOP16 .EQ 8
S.PAKSTAT.TOP24 .EQ 10 S.PAKSTAT.TOP24 .EQ 10

View File

@ -83,9 +83,9 @@ Pak.Out.PutByte inc Pak.DstCnt
bne .2 bne .2
inc ZPDstPtr+1 inc ZPDstPtr+1
.7 inc Pak.Stat+S.PAKSTAT.PASS1,x .7 inc Pak.Stat+S.PAKSTAT.PASS2,x
bne .8 bne .8
inc Pak.Stat+S.PAKSTAT.PASS1+1,x inc Pak.Stat+S.PAKSTAT.PASS2+1,x
.8 clc .8 clc
rts rts

View File

@ -12,7 +12,7 @@ NEW
ZPSrcPtr .EQ ZPLIB ZPSrcPtr .EQ ZPLIB
ZPSrcWPtr .EQ ZPLIB+2 ZPSrcWPtr .EQ ZPLIB+2
ZPCnt .EQ ZPLIB+4 ZPCnt .EQ ZPLIB+4
ZPHdrPtr .EQ ZPLIB+14
ZPDstPtr .EQ ZPLIB+16 ZPDstPtr .EQ ZPLIB+16
ZPStatPtr .EQ ZPLIB+18 ZPStatPtr .EQ ZPLIB+18
*-------------------------------------- *--------------------------------------
@ -61,7 +61,7 @@ Pak >PULLW Pak.SrcPtr
inx inx
bne .1 bne .1
* PASS #1 : REP & BL, no store, update byte counters * PASS #1 : no store, update byte counters
stz Pak.bPass2 stz Pak.bPass2
@ -70,9 +70,9 @@ Pak >PULLW Pak.SrcPtr
jsr Pak.Run jsr Pak.Run
bcs .9 bcs .9
jsr Pak.BuildShortTable jsr Pak.BuildTOPTable
* PASS #2 : REP & BL, store with S3,S4 * PASS #2 : store with TOP bytes
dec Pak.bPass2 dec Pak.bPass2
@ -80,7 +80,7 @@ Pak >PULLW Pak.SrcPtr
jsr Pak.Out.Init Initialize properly for first "PutBit" Call jsr Pak.Out.Init Initialize properly for first "PutBit" Call
stz Pak.StoreCnt stz Pak.StringLen
jsr Pak.Run jsr Pak.Run
bcs .9 bcs .9
@ -88,7 +88,7 @@ Pak >PULLW Pak.SrcPtr
ldy #S.PAKSHNK-1 ldy #S.PAKSHNK-1
.2 lda Pak.Shnk,y .2 lda Pak.Shnk,y
sta (ZPHdrPtr),y
dey dey
bpl .2 bpl .2
@ -118,10 +118,15 @@ Pak.InitPass >LDYA Pak.SrcPtr
eor #$ff eor #$ff
sta Pak.SrcCnt+1 sta Pak.SrcCnt+1
lda #$ff RepChar invalid stz Pak.RepCnt
sta Pak.RepCnt stz Pak.LastByte
ldx #S.PAKSTAT.PASS2 ldx #S.PAKSTAT.PASS1
bit Pak.bPass2
bpl .1
inx
inx
.1 stz Pak.Stat,x Reset Stats .1 stz Pak.Stat,x Reset Stats
inx inx
@ -294,19 +299,28 @@ Pak.ScanBL stx Pak.WStrLen
.9 sec .9 sec
rts rts
*-------------------------------------- *--------------------------------------
Pak.BuildShortTable Pak.BuildTOPTable
ldy #0 ldy #0
.6 stz Pak.Cnt Init best score to 0 .1 stz Pak.Cnt Init best score to 0
stz Pak.Cnt+1 stz Pak.Cnt+1
sec
ror Pak.bStop
ldx #0 ldx #0
.7 lda Pak.Cnt .2 lda Pak.Cnt
ora Pak.Cnt+1
beq .3
stz Pak.bStop
lda Pak.Cnt
cmp Pak.CntL,x is it better at X cmp Pak.CntL,x is it better at X
lda Pak.Cnt+1 lda Pak.Cnt+1
sbc Pak.CntH,x sbc Pak.CntH,x
bcs .8 not better or equal... bcs .3 not better or equal...
stx Pak.In.Byte save new score index... stx Pak.In.Byte save new score index...
@ -315,17 +329,22 @@ Pak.BuildShortTable
lda Pak.CntH,x lda Pak.CntH,x
sta Pak.Cnt+1 sta Pak.Cnt+1
.8 inx .3 inx
bne .7 bne .2
bit Pak.bStop
bmi .8
lda Pak.In.Byte lda Pak.In.Byte
sta Pak.Shnk+S.PAKSHNK.SHORT3,y sta Pak.Shnk+S.PAKSHNK.TOPBYTES,y
tax tax
stz Pak.CntL,x Discard this entry stz Pak.CntL,x Discard this entry
stz Pak.CntH,x stz Pak.CntH,x
iny iny
cpy #24 cpy #24
bne .6 bne .1
.8 sty Pak.TopCnt
rts rts
*-------------------------------------- *--------------------------------------
@ -347,7 +366,7 @@ Pak.PutA bit Pak.RepCnt
jsr Pak.PutA.1 jsr Pak.PutA.1
bcs .9 bcs .9
ldx #S.PAKSTAT.REP ldx #S.PAKSTAT.REPN
jsr Pak.UpdateStats jsr Pak.UpdateStats
stz Pak.RepCnt stz Pak.RepCnt
@ -367,7 +386,7 @@ Pak.PutA bit Pak.RepCnt
lda #1 lda #1
sta Pak.RepCnt sta Pak.RepCnt
ldx #S.PAKSTAT.REP ldx #S.PAKSTAT.REPN
jsr Pak.UpdateStats jsr Pak.UpdateStats
.8 clc .8 clc
@ -389,53 +408,37 @@ Pak.PutA.1 bit Pak.bPass2
* Pak.PutA.1 PASS #2 * Pak.PutA.1 PASS #2
.10 ldy #7 .10 ldy #S.PAKSHNK.TOPCNT
.1 cmp Pak.Shnk+S.PAKSHNK.SHORT3,y .1 cmp Pak.Shnk+S.PAKSHNK.TOPBYTES-1,y
beq .3 beq .3
dey dey
bpl .1 bpl .1
ldy #15 ldx #S.PAKSTAT.BYTE8
jsr Pak.UpdateStats
.2 cmp Pak.Shnk+S.PAKSHNK.SHORT4,y
beq .4
dey
bpl .2
bra .7
.3 tya
asl
asl
asl
asl
ora #PAK.B.SHORT3
ldy #4
ldx #S.PAKSTAT.S3
bra .8
.4 tya
asl
asl
ora #PAK.B.SHORT4
ldy #6
ldx #S.PAKSTAT.S4
bra .8
.7 ldx Pak.StoreCnt
sta Pak.StoreBuf,x
inx
cpx #STOREMAX
beq Pak.Flush
stx Pak.StoreCnt
clc clc
rts jmp Pak.Out.PutCA
.8 jsr Pak.UpdateStats .3 tya Range 0-23
lsr
lsr
lsr
tax
tya
and #7
ora TOP.Bits,x
ldy TOP.BitCnt,x
pha
lda TOP.Stat,x
tax
pla
jsr Pak.UpdateStats
jmp Pak.Out.PutYBits jmp Pak.Out.PutYBits
*-------------------------------------- *--------------------------------------
Pak.Flush ldx Pak.StoreCnt Pak.Flush ldx Pak.StringLen
beq .8 beq .8
lda #PAK.B.STOREn lda #PAK.B.STOREn
@ -445,18 +448,18 @@ Pak.Flush ldx Pak.StoreCnt
ldx #0 ldx #0
.1 lda Pak.StoreBuf,x .1 lda Pak.StringBuf,x
sta Pak.LastByte update last byte for REP sta Pak.LastByte update last byte for REP
ldy #8 ldy #8
jsr Pak.Out.PutYBits jsr Pak.Out.PutYBits
bcs .9 bcs .9
inc Pak.Stat+S.PAKSTAT.STORE inc Pak.Stat+S.PAKSTAT.BYTE8
bne .2 bne .2
inc Pak.Stat+S.PAKSTAT.STORE+1 inc Pak.Stat+S.PAKSTAT.BYTE8+1
.2 inx .2 inx
dec Pak.StoreCnt dec Pak.StringLen
bne .1 bne .1
stz Pak.RepCnt Don't forget to set last byte valid stz Pak.RepCnt Don't forget to set last byte valid
@ -473,6 +476,11 @@ Pak.UpdateStats inc Pak.Stat,x
.INB USR/SRC/LIB/LIBPAK.S.OUT .INB USR/SRC/LIB/LIBPAK.S.OUT
*-------------------------------------- *--------------------------------------
CS.END CS.END
*--------------------------------------
TOP.Bits .DA #%10000,#%110000,#%1110000
TOP.BitCnt .DA #5,#6,#7
TOP.Stat .DA #S.PAKSTAT.TOP8,S.PAKSTAT.TOP16,S.PAKSTAT.TOP24
*--------------------------------------
Pak.SrcPtr .BS 2 Pak.SrcPtr .BS 2
Pak.SrcLen .BS 2 Pak.SrcLen .BS 2
@ -482,11 +490,12 @@ Pak.DstCnt .BS 2
Pak.RepCnt .BS 1 Pak.RepCnt .BS 1
Pak.LastByte .BS 1 Pak.LastByte .BS 1
Pak.StoreCnt .BS 1 Pak.StringLen .BS 1
Pak.StoreBuf .BS STOREMAX Pak.StringBuf .BS STRINGMAX
Pak.TopCnt .BS 1
Pak.Cnt .BS 2 Pak.Cnt .BS 2
Pak.bStop .BS 1
Pak.bPass2 .BS 1 Pak.bPass2 .BS 1
Pak.MaxReadAhead .BS 1 Pak.MaxReadAhead .BS 1

View File

@ -10,8 +10,13 @@ AUTO 4,1
.INB INC/MLI.I .INB INC/MLI.I
.INB INC/A2OSX.I .INB INC/A2OSX.I
*-------------------------------------- *--------------------------------------
ZPCfgPtr .EQ ZPBIN .DUMMY
ZPTmp1 .EQ ZPBIN+2 .OR ZPBIN
ZS.START
ZPCfgPtr .BS 2
ZPTmp1 .BS 2
hFileBuf .BS 1
ZS.END .ED
*-------------------------------------- *--------------------------------------
* File Header (16 Bytes) * File Header (16 Bytes)
*-------------------------------------- *--------------------------------------
@ -19,11 +24,12 @@ CS.START cld
jmp (.1,x) jmp (.1,x)
.DA #$61 6502,Level 1 (65c02) .DA #$61 6502,Level 1 (65c02)
.DA #1 BIN Layout Version 1 .DA #1 BIN Layout Version 1
.DA 0 .DA #S.PS.F.EVENT
.DA CS.END-CS.START CS .DA #0
.DA DS.END-DS.START DS .DA CS.END-CS.START Code Size (without Constants)
.DA #16 SS .DA DS.END-DS.START Data Segment Size
.DA #4 ZP .DA #64 Stack Size
.DA #ZS.END-ZS.START Zero Page Size
.DA 0 .DA 0
*-------------------------------------- *--------------------------------------
* Relocation Table * Relocation Table
@ -47,6 +53,8 @@ L.MSG.DISABLED .DA MSG.DISABLED
L.MSG.ENABLED .DA MSG.ENABLED L.MSG.ENABLED .DA MSG.ENABLED
L.MSG.SLOT .DA MSG.SLOT L.MSG.SLOT .DA MSG.SLOT
L.MSG.QUIT .DA MSG.QUIT L.MSG.QUIT .DA MSG.QUIT
L.MSG.QUIT.SAVED
.DA MSG.QUIT.SAVED
L.MSG.QUIT.ERR .DA MSG.QUIT.ERR L.MSG.QUIT.ERR .DA MSG.QUIT.ERR
T.MSG.SLOT.DESC .DA MSG.SLOT.NODEV T.MSG.SLOT.DESC .DA MSG.SLOT.NODEV
.DA MSG.SLOT.Z80 .DA MSG.SLOT.Z80
@ -107,12 +115,17 @@ CS.RUN.Loop >SYSCALL GetChar
bne .1 bne .1
jsr CS.RUN.Save jsr CS.RUN.Save
bcc .8 bcc .10
>PUSHA >PUSHA
>PUSHBI 1 >PUSHBI 1
>LDYA L.MSG.QUIT.ERR >LDYA L.MSG.QUIT.ERR
bra .9 bra .9
.10 >PUSHBI 1
>LDYA L.MSG.QUIT.SAVED
bra .9
.99 rts .99 rts
.1 cmp #20 Ctrl-T .1 cmp #20 Ctrl-T
@ -149,7 +162,7 @@ CS.RUN.Loop >SYSCALL GetChar
and #3 and #3
inc inc
sta (ZPCfgPtr),y sta (ZPCfgPtr),y
bra CS.RUN.REPaint jmp CS.RUN.REPaint
.5 cmp #'1' .5 cmp #'1'
bcc CS.RUN.Loop bcc CS.RUN.Loop
@ -201,9 +214,9 @@ CS.RUN.Load >PUSHEA.G StatBuf
>LDYA L.FILENAME >LDYA L.FILENAME
>SYSCALL LoadFile >SYSCALL LoadFile
bcs .99 bcs .99
txa
>STA.G hFileBuf stx hFileBuf
txa
>SYSCALL GetMemPtr >SYSCALL GetMemPtr
>STYA ZPCfgPtr >STYA ZPCfgPtr
* clc * clc
@ -214,8 +227,7 @@ CS.RUN.Load >PUSHEA.G StatBuf
>STYA ZPCfgPtr >STYA ZPCfgPtr
txa stx hFileBuf
>STA.G hFileBuf
ldy #15 ldy #15
@ -342,7 +354,7 @@ CS.RUN.DumpConfYA
CS.DOEVENT sec do not discard TIMER event CS.DOEVENT sec do not discard TIMER event
rts rts
*-------------------------------------- *--------------------------------------
CS.QUIT >LDA.G hFileBuf CS.QUIT lda hFileBuf
beq .8 beq .8
>SYSCALL FreeMem >SYSCALL FreeMem
.8 clc .8 clc
@ -391,12 +403,12 @@ MSG.SLOT.CLK .AZ "Clock Card"
MSG.SLOT.DIS .AZ "<Disabled>" MSG.SLOT.DIS .AZ "<Disabled>"
MSG.PROMPT .AZ "\e[24;80H" MSG.PROMPT .AZ "\e[24;80H"
MSG.QUIT .AZ "\ec" MSG.QUIT .AZ "\ec"
MSG.QUIT.ERR .AZ "\ecError [$%h] While Writing KCONFIG File.\r\n\r\n" MSG.QUIT.SAVED .AZ "\ecA2osX.KCONFIG file saved.\r\n\r\n"
MSG.QUIT.ERR .AZ "\ecError [$%h] while writing A2osX.KCONFIG file.\r\n\r\n"
*-------------------------------------- *--------------------------------------
.DUMMY .DUMMY
.OR 0 .OR 0
DS.START DS.START
hFileBuf .BS 1
StatBuf .BS S.STAT StatBuf .BS S.STAT
DS.END .ED DS.END .ED
MAN MAN

View File

@ -204,7 +204,7 @@ CORE.GetEvents lda #Evt.Table
sta IRQ.Mode sta IRQ.Mode
ldx A2osX.ASCREEN ldx A2osX.ASCREEN
dex devID 1 is /DEV/CONSOLE cpx #3 devID 3 is /DEV/CONSOLE
bne .22 bne .22
sta SYS.BASL0+38 sta SYS.BASL0+38

View File

@ -16,22 +16,16 @@ K.IrqHAuxLC.BRK jmp K.IrqHAuxLC.6
*-------------------------------------- *--------------------------------------
K.IrqHAuxLC cld K.IrqHAuxLC cld
sec
sta K.IrqHAuxLC.6+1 sta K.IrqHAuxLC.6+1
pla pla
pha pha
and #$10 BRK? and #$10 BRK?
* bne K.IrqHAuxLC.BRK * bne K.IrqHAuxLC.BRK
bne * bne *
stx K.IrqHAuxLC.5+1 stx K.IrqHAuxLC.5+1
sty K.IrqHAuxLC.4+1 sty K.IrqHAuxLC.4+1
* lda $fe Save 2 bytes in ZP
* pha
* lda $ff
* pha
lda RDPAGE2 lda RDPAGE2
pha pha
sta CLRPAGE2 sta CLRPAGE2
@ -65,8 +59,9 @@ K.IrqHAuxLC.JSR jsr K.IrqH.DEV SELF MODIFIED
sta K.IrqHAuxLC.2+2 sta K.IrqHAuxLC.2+2
and #$F0 and #$F0
eor #$C0 ....mmm...not looking link Cn.... eor #$C0 ....mmm...not looking like Cn....
bne K.IrqHAuxLC.3 bne K.IrqHAuxLC.3
sta $CFFF Release $C800 sta $CFFF Release $C800
K.IrqHAuxLC.2 lda $ff00 SELF MODIFIED K.IrqHAuxLC.2 lda $ff00 SELF MODIFIED
@ -86,22 +81,20 @@ K.IrqHAuxLC.3 pla Must keep Carry
sta SETPAGE2 sta SETPAGE2
.3 .3 bvc K.IrqHAuxLC.4 if V, skip task switching
* pla
* sta $ff
* pla
* sta $fe
bvc K.IrqHAuxLC.4 if V, skip task switching
bit IRQ.InLib
bmi K.IrqHAuxLC.4 we are in LIB, no switching
tsx tsx
txa lda $103,x
eor #$FC Only LO,HI & P on stack and #$C0
eor #$C0
beq K.IrqHAuxLC.4 we are in kernel CORE.Run beq K.IrqHAuxLC.4 we are in kernel CORE.Run
* tsx
* txa
* eor #$FC Only LO,HI & P on stack
* beq K.IrqHAuxLC.4 we are in kernel CORE.Run
* >DEBUG
php php
php make room for 2 additional bytes php make room for 2 additional bytes
@ -121,7 +114,7 @@ K.IrqHAuxLC.3 pla Must keep Carry
lda /A2osX.SLEEP with RTS=PC IRQ-1 lda /A2osX.SLEEP with RTS=PC IRQ-1
sta $103,x sta $103,x
lda #$A0+'S .5 lda #$80+'S'
eor SYS.BASL0+39 eor SYS.BASL0+39
sta SYS.BASL0+39 sta SYS.BASL0+39
@ -198,6 +191,9 @@ K.IrqH.Switch inc IRQ.Tick
eor #PS.DOEVENT Dont switch while DOEVENT eor #PS.DOEVENT Dont switch while DOEVENT
bne .9 bne .9
lda IRQ.InLib
bmi .9 we are in LIB, no switching
.8 clc exit with V flag set .8 clc exit with V flag set
rts rts
*-------------------------------------- *--------------------------------------