; Juddpeg -- A jpeg decoder for the C64 ; ; SLJ 9/17/99 ; ; MCM-lace version 10/1/99 ; Generic version 10/7/99 ; Last update: 12/18/99 ;; ;; Atari 8-bit port: Raphael Espino ;; started 16-Oct-00 ;; last updated 13-Sep-02 ;; ;; to assemble: ;; ca65 jpy1223a8.asm ;; then link with one of the viewers ;; ;; ;; decoder memory map: ;; ;; --- zero page --- ;; $0080 - $00BF decoder zero page addresses ;; $00C0 - $00FF available for viewer ;; ;; $0480 - $057F input buffer ;; ;; --- page 6 --- ;; $0600 - $061F decoder interface variables ;; $0620 - $062F viewer jump vectors ;; $0630 - $06FF available for viewer ;; ;; --- main RAM --- ;; $2000 - $2EFF code ;; $2F00 - $4BFF data tables ;; $4C00 - $4DFF decoding buffers ;; $4E00 - $6BFF output buffer ;; $6C00 - $78FF Huffman buffer ;; ;; $7900 - $FFFF is guaranteed free for renderer and screen RAM while ;; decoder is running ;; HuffTop-$7900 is also free for renderer and screen RAM while ;; decoder is decoding. HuffTop available in $60C ;; $4C00 - $8BFF is free for viewer after decoding has finished ;; (when RENDEND vector is called) but not before! ;; ;; ---------------- renderer interface addresses ----------------------- DISPCOLS = $600 ; (# of columns to display)/8 must be <= 40 DISPROWS = $601 ; (# of rows to display)/8 coloff = $602 ; Column offset (left edge of output image) rowoff = $603 ; Row offset (top edge of output image) numcols = $604 ; image width (pixels/8) numrows = $605 ; image height (pixels/8) IOCBNUM = $606 ; IOCB to read jpeg data from STACKPT = $607 ; stack pointer at program start ERROR = $608 ; non 0 if error ocurred decoding jpeg ; error codes are as shown below RERUN = $609 ; 2 bytes - restart address VERSION = $60B ; decoder version number HuffTop = $60C ; End of output buffer, above this is free for viewer width = $60E ; Width of image in pixels (2 bytes) SkipErr = $610 ; Error in an image with restart markers ; decoder will continue decoding and set this to non 0 ;; version 1 uses $0480 - $057F as input buffer and added ABORT code ;; version 2 added HuffTop ;; version 3 made width available to viewer ;; version 4 fixed DRI with restart interval = 0 bug ;; version 5 ignores HUFFMAN err if restart markers are being used ;; uses jpz HUFFMAN code to reduce buffer size ;; added SkipErr ;; fixed repeated columns at end of image when coloff > 0 ;; renderer jump vectors RENDINIT = $620 ; renderer init vector RENDSTART = RENDINIT+3 ; renderer, image data about to start RENDDRAW = RENDINIT+6 ; renderer, draw 8 lines of image RENDEND = RENDINIT+9 ; renderer, image finished RENDUNUSED = RENDINIT+12 ; unused for now, point at an rts ;; Rest of page 6 from $630 - $6FF is available to renderer ;; ------------ end of renderer interface addresses ---------------- NOTJPG = 1 ; Error codes READERR = 2 BADQT = 3 ; bad data in DQT segment BADHT = 4 ; bad data in DHT segment HUFFERR = 5 PROGJPG = 6 ; progressive jpeg not supported ABORT = 128 ; abort decoding YBuf = 0 ; ; Atari addresses ; ; ; O.S. ROM ; CIOV = 58454 ; ; O.S. RAM ; COLOR4 = 712 ICCOM = 834 ICSTA = 835 ICBAL = 836 ICBAH = 837 ICBLL = 840 ICBLH = 841 ICAX1 = 842 ICAX2 = 843 ; ; PRESETS ; OPEN = 3 ; open channel GETBUF = 7 ; get buffer PUTBUF = 11 ; put buffer CLOSE = 12 ; close channel ;; decoder also uses empty space at 1152 to buffer input data INBUFFSZ = $FF ; input buffer size, must be <= 255 INBUFF = $0480 ; input buffer ;; ;; page 0 addresses used by decoder ;; mult1lo = 128 ; data tables mult1hi = 130 mult2lo = 132 mult2hi = 134 point = 136 ; image buffer pointer temp = 138 quantp = 140 ; Quant table huff = 142 ; Huffman pointers temp2 = 144 ; 1 byte count = 145 ; Used by GetBits, 1 byte ; and AddNode Bitslo = 146 ; and Dequantize Bitshi = 147 ; dest = 148 index = 150 ; 1 byte t1 = 151 t2 = 153 t3 = 155 DCT = 157 ; 16 bytes worth here Coeff = 173 ; 16 bytes worth here ;; ;; page 0 addresses from 192 upwards are available to renderer ;; ;; ;; data table addresses, the data is included at the end of this file ;; Negmlo = $2F00 Posmlo = Negmlo+$100 Negmhi = Posmlo+$200 Posmhi = Negmhi+$100 ; 2 pages a1lo = Posmhi+$200 ; cos(2a), a=pi/8 a1hi = a1lo+$100 a2lo = a1hi+$100 ; cos(a)-cos(3a) a2hi = a2lo+$100 a3lo = a1lo ; cos(2a) a3hi = a1hi a4lo = a2hi+$100 ; cos(a)+cos(3a) a4hi = a4lo+$100 a4gh = a4hi+$100 a5lo = a4gh+$100 ; cos(3a) a5hi = a5lo+$100 sec1 = a5hi+$100 sec2 = sec1+$200 sec3 = sec2+$200 sec4 = sec3+$200 sec5 = sec4+$200 sec6 = sec5+$200 sec7 = sec6+$200 ; - 2 pages worth a1216 = 46341 ;a1*2^16 a2216 = 35468 ;a2*2^16 a3216 = a1216 a4216 = 20091 ;... a5216 = 25080 ;; ;; decoding buffer addresses, these can be reused by viewer ;; when decoding has finished, but not until! ;; trans = sec7+$200 ; Transform Veclo = trans+$80 ; Vec to be quantized Vechi = Veclo+$40 QT0 = Vechi+$40 ; Quantization tables QT1 = QT0+$40 QT2 = QT1+$40 QT3 = QT2+$40 ImgBuf = QT3+$40 ; Image data output buffer ($4E00) ; Renderer gets its decoded image data from here BUFLEN = $A00 ; buffer size ImgBufSize = BUFLEN*3 ; have 3 buffers available for image Huffmem = ImgBuf+ImgBufSize ; Huffman trees, $D00 worth .ADDR segstart .ADDR segend-1 .ORG $2000 segstart: Start: tsx stx STACKPT lda #RunAgain sta RERUN+1 lda #5 ; version 5 of Atari port of decoder sta VERSION RunAgain: ldx STACKPT ; make sure stack pointer is reset txs ; if we are re-running ;; default to 40*8 (320) columns wide and 24*8 (192) lines high lda #40 sta DISPCOLS lda #24 sta DISPROWS LDA #0 STA ERROR ; no error STA SkipErr STA AtEOF ; not and end of file STA SkipFF STA lastchar ; reset last character printed sta inbytecnt ; no data in input buffer yet STA reslen ; restart interval length STA reslen+1 sta nbits LDA #$FF STA filepos ; initialise current file pos STA filepos+1 STA filepos+2 LDA #>Posmlo ; set up positions in RAM for mult tables STA mult1lo+1 LDA #>Negmlo STA mult2lo+1 LDA #>Posmhi STA mult1hi+1 LDA #>Negmhi STA mult2hi+1 jsr OPNGR ; make sure screen open for gr.0 ; lda #0 ; sta nbits JSR strout ; display title info .BYTE 125, 155,"based on juddpeg, slj 11/11",155,0 jsr RENDINIT ; let renderer initialise jsr GETIN ; check JPEG SOI cmp #$ff ; marker = $FFD8 bne @err1 jsr GETIN cmp #$d8 bne @err1 ;; clear buffers here in case renderer uses them for something else jsr InitHuff ; set up pointer to huff memory jsr InitBuff ; set up pointer to image buffer and init it jsr GetAPP0 @loop: lda ERROR ; exit on error bne @err lda AtEOF ; exit if end of file reached bne @done2 jsr DoMarker ; decode next segment jmp @loop @err1: LDA #NOTJPG ; not a jpeg image error sta ERROR @err: ; Acc = err no cmp #ABORT ; did user abort? beq @done2 PHA jsr OPNGR ; switch to GR.0 JSR strout ; display error message .BYTE 155 .BYTE "error at pos=$",0 LDA filepos+2 ; display file position JSR HexOut LDA filepos+1 JSR HexOut LDA filepos JSR HexOut JSR PRINTNL PLA ASL TAX LDA ERRTAB-2,X TAY LDA ERRTAB-1,X TAX jsr findlen jsr putbuf @done2: jsr RENDEND ; tell renderer we are about to finish ;; return to environment jmp OPNGR ; make sure we're in GR.0 before returning ; rts AtEOF: .BYTE 0 ; has end of file been reached? ERRTAB: ; error messages table .ADDR @notjpg .ADDR @readerr .ADDR @dqt .ADDR @dht .ADDR @huff .ADDR @prgerr @notjpg: .BYTE "Not a jpg file",0 @readerr:.BYTE "Error reading file",0 @dqt: .BYTE "Quantization table error",0 @dht: .BYTE "Huffman table error",0 @huff: .BYTE "Huffman error",0 @prgerr: .BYTE "Unsupported jpg",0 ; Bit patterns (masks) BITP: .BYTE $0 .BYTE $01, $02, $04, $08, $10, $20, $40, $80 .BYTE $01, $02, $04, $08, $10, $20, $40, $80 ; Zero out image output buffer InitBuff: LDA #ImgBuf STA point+1 LDX #>ImgBufSize LDA #0 TAY ; now initialise image buffer @loop: STA (point),Y DEY BNE @loop INC point+1 DEX BNE @loop RTS ; ; DoMarker -- Read Marker and call ; appropriate routine. ; Unknown: jsr strout .BYTE "unknown header:ff",0 lda Header jsr HexOut jsr anyway jsr Ignore ; ignore this segment DoMarker: lda AtEOF ; if we are at end of file, then return beq @c1 rts @c1: jsr GetHeader ; find next bcs DoMarker Do2: ; Handle diffent segments lda Header cmp #$fe beq @com cmp #$dd beq @dri cmp #$db beq @dqt cmp #$c4 beq @dht cmp #$c0 beq @sof cmp #$c2 ; check for a progressive jpeg bne @notprg lda #PROGJPG sta ERROR rts @notprg: cmp #$da bne Unknown ; unknown segment start, just skip it @sos: jmp SOS ; start of scan - this is the image data @com: jmp Comment ; comment @dri: jmp DRI ; define restart interval marker @dqt: jmp DQT ; define quantization table @dht: jmp DHT ; define huffman table @sof: jmp SOF ; start of frame ; ; display trying anyway message ; anyway: jsr strout .BYTE " trying anyway" .BYTE 155,0 rts ; ; GetAPP0 -- Read JFIF header ; GetAPP0: jsr GetHeader bcs @jmp lda Header cmp #$e0 ;APP0 marker beq Ignore jsr strout .BYTE "not jfif format!" jsr anyway jmp Do2 @jmp: jmp DoMarker ; Ignore rest of segment Ignore: JSR GetByte ; exit if error reading next byte BCS @rts LDA AtEOF ; exit if end of file reached BNE @rts JSR DecLen BNE Ignore ; skip bytes until end of segment reached @rts: RTS ; ; GetHeader -- Read in header bytes. ; On exit: ; C set -> error ; Z set -> end of file ; Header: .BYTE 0 Length: .WORD 0 ;lo,hi GetHeader: LDA #0 STA Header jsr GetByte bcs @rts cmp #$ff bne @sec jsr GetByte sta Header cmp #$d8 ;Start of JPEG beq @clc ;lame Photoshop cmp #$d9 ;End of file bne @c2 sta AtEOF beq @clc @c2: jsr GetByte bcs @rts sta Length+1 jsr GetByte bcs @rts sec sbc #2 ; 2 bytes of length info included in count sta Length bcs @c3 dec Length+1 @c3: ora Length+1 ;Empty segment beq GetHeader @clc: clc rts @sec: sec @rts: rts ; ; GetByte ; SkipFF: .BYTE 0 ;Flag GetByte: LDA COLOR4 ; flash backgroud as image is being decoded clc adc #16 sta COLOR4 jsr GETIN cmp #$ff bne @rts ldx SkipFF beq @rts ; we're not skipping $FF's so return byte jsr GETIN sta Header tay ; $ff00 -> $ff bne @rts lda #$ff @rts: ; at end of file? ldx AtEOF cpx #1 ; set carry bit as appropriate rts ; C set -> error ;; get one byte from file and return it in acc, updating file position GETIN: INC filepos BNE @c1 INC filepos+1 BNE @c1 INC filepos+2 @c1: ;; READ IN 1 BYTE FROM OPEN FILE ;; this uses an open IOCB to read in a buffer full of data from the ;; jpeg file and then returns a byte at a time from the buffer ;; if you don't want to use the IOCB, then replace this with something ;; else. This routine should return the next byte to decode in the ;; Accumulator. Return with carry clear for success, and carry set ;; for error lda inbytecnt bne @retbyte ;; no more data left in buffer, so go get another buffer full LDX IOCBNUM LDA #INBUFFSZ ; read in a buffer's worth of data, STA ICBLL,X LDA #0 ; should be faster than calling CIO for STA ICBLH,X ; just 1 byte at a time LDA #INBUFF sta ICBAH,X LDA #GETBUF STA ICCOM,X JSR CIOV lda ICBLL,X bne @noteof ; not reached eof yet inc AtEOF sec ; eof reached, set C flag rts @noteof: sta inbytecnt lda #0 sta @nextbyte @retbyte: ; return next byte available in buffer ldx @nextbyte lda INBUFF,x inc @nextbyte dec inbytecnt clc ; clear C flag RTS ; C flag set on error @nextbyte: .BYTE 0 ; pointer to next byte inbytecnt: .BYTE 0 ; number of bytes currently in buffer ; ; GetBit -- get next bit! ; nbits: .BYTE 0 ;# of bits left byte: .BYTE 0 GetBit: dec nbits bpl @get lda #7 sta nbits jsr GetByte sta byte @get: asl byte @rts: rts ; ; OPEN SCREEN FOR GR.0 ; OPNGR: LDX #0 LDA #CLOSE STA ICCOM jsr CIOV LDA #E STA ICBAH LDA #12 STA ICAX1 STX ICAX2 ; open for gr.0 LDA #OPEN STA ICCOM JMP CIOV E: .BYTE "E:" ; display embeded string on screen ; string data should follow strout call and be terminated ; with a 0 strout: PLA ; get string address from stack TAY PLA TAX INY BNE @NIN2 INX @NIN2: jsr findlen tay txa pha ; modify return address to tya ; return immediately after pha ; terminating 0 putbuf: LDA #PUTBUF ; found end of string STA ICCOM LDX #0 JMP CIOV ; let CIO display it findlen: STY ICBAL ; point at start of string STY @loop+1 STX @loop+2 STX ICBAH LDY #0 ; no data yet STY ICBLH @loop: lda $c000,y ; - this address gets modified beq @exit ; continue until we find terminating 0 iny bne @loop ; forced branch @exit: TYA STA ICBLL clc adc @loop+1 bcc @noinx inx @noinx: rts ;; print a newline PRINTNL: LDA #155 ; print a return char ;; use CIO to put 1 byte on screen PRINT1BYTE: LDX #PUTBUF STX ICCOM LDX #0 ; use CIO's put one byte routine STX ICBLL STX ICBLH JMP CIOV ; Print hex number on screen HexOut: PHA ; save original value LSR ; move hi hex digit to bottom nibble LSR LSR LSR JSR @print ; display hi hex digit PLA ; restore original value AND #$0F ; and get lo hex digit @print: cmp #10 ; if digit is > 9, then convert it to A BCC @c1 ADC #6 @c1: ADC #48 JMP PRINT1BYTE ;******************************* ; ; Main header processing routines ; ;******************************* DecLen: LDA Length BNE @c1 ORA Length+1 BEQ @rts DEC Length+1 @c1: DEC Length LDA Length ORA Length+1 @rts: RTS ;; handle a comment segment by displaying text on the screen Comment: JSR GetByte BCS @rts ldx lastchar ; get last character printed sta lastchar ; remember last char before converting CMP #$0D ; CR BEQ @oops2 CMP #$0A ; LF BNE @c0 cpx #$0D beq @skip ; if CR/LF only display one return char @c0: CMP #32 ; only want printing chars BCC @oops CMP #125 BCC @c1 @oops: LDA #'@' ; display @ instead of non printing char .BYTE $2C @oops2: LDA #155 ; CR or LF to 155 @c1: JSR PRINT1BYTE ; display character on screen @skip: JSR DecLen BNE Comment @rts: JMP PRINTNL ; display final newline lastchar: .BYTE 0 ; last character displayed ; Lame restart markers reslen: .WORD 0 cres: .WORD 0 ;; define restart interval marker DRI: JSR GETIN ; remember restart interval length STA reslen+1 STA cres+1 JSR GETIN STA reslen STA cres RTS ;; check if we have reached restart interval DecRes: LDA reslen+1 ; check if restart interval defined ora reslen beq @rts ; no restart interval, don't decrement it DEC cres BNE @rts LDA cres+1 BEQ @restart DEC cres+1 @rts: RTS @restart: STA nbits ;Skip bits - set nbits to 0 JSR GetByte ;Read $FFxx LDA reslen STA cres LDA reslen+1 STA cres+1 Restart: LDX #5 @l2: STA DClo,X STA DChi,X DEX BPL @l2 RTS ; Define Quantization table DQT: JSR DecLen BEQ @rts JSR GetByte BCS @err TAY AND #$0F ;number of QT BNE @c1 LDX #QT0 BNE @ok @c1: CMP #1 BNE @c2 LDX #QT1 BNE @ok @c2: CMP #2 BNE @c3 LDX #QT2 BNE @ok @c3: CMP #3 BNE @err LDX #QT3 @ok: STX point ;QT addr STA point+1 TYA AND #$F0 BNE @err ;0 = 8-bit LDY #0 @loop: STY temp ;Counter LDA Length ORA Length+1 BEQ @err JSR GetByte BCS @err LDY temp STA (point),Y JSR DecLen INY CPY #64 BNE @loop JMP DQT ;Multiple QT's allowed @err: LDA #BADQT ;Only 0-3 allowed STA ERROR @rts: RTS ; Define Huffman table hufflen: .BYTE 0 DHT: JSR DecLen BEQ @jerr @getb: JSR GetByte BCC @cont @jerr: JMP @err @cont: TAY ;Info byte AND #$0F CMP #$04 ; table number must be < 4 BCS @jerr ASL TAX ;table num 0-3 TYA AND #$F0 BEQ @ok ;DC table CMP #$10 BNE @jerr TXA ;AC table ORA #$08 ;+8 TAX @ok: LDA HuffTop STA DCHuff0,X STA huff LDA HuffTop+1 STA DCHuff0+1,X STA huff+1 STX temp2 LDY #1 ; start with a right node JSR NewNode ;Root node LDX #1 @l1: STX temp LDA Length ORA Length+1 BEQ @err ; ran out of data to read JSR GetByte BCS @err LDX temp STA symbols-1,X JSR DecLen ; byte has been read INX CPX #17 ; read in 16 bytes BNE @l1 LDA #$FF STA huffbits STA huffbits+1 LDA #1 STA hufflen @loop: INC huffbits+1 ;hi,lo! BNE @c1 INC huffbits @c1: @l2: LDX hufflen DEC symbols-1,X BPL @c2 CPX #16 BEQ @next ASL huffbits+1 ROL huffbits INC hufflen BNE @l2 @c2: LDX temp2 LDA DCHuff0,X STA huff LDA DCHuff0+1,X STA huff+1 JSR GetByte BCS @err LDX hufflen JSR AddNode JSR DecLen JMP @loop @next: JSR DecLen BEQ @rts JMP @getb ;Multiple HTs @err: LDA #BADHT STA ERROR @rts: RTS ; Start of Frame height: .WORD 0 ; image height (pixels) - low byte ncomps: .BYTE 0 ; Num components SOF: LDX #5 LDA #0 @l1: STA csampv,X STA csamph,X DEX BPL @l1 JSR @get CMP #8 BEQ @ok LDA #BADQT STA ERROR RTS @ok: JSR @get STA height+1 JSR @get STA height ; get image height SEC SBC #1 STA numrows ; then convert it to number of row LDA height+1 SBC #0 LSR ROR numrows ; 1 row = 8 pixels LSR ROR numrows LSR ROR numrows INC numrows JSR @get STA width+1 ; set up image width JSR @get STA width SEC SBC #1 ; 0..7 instead of 1..8 STA numcols ; then covert it to number of columns LDA width+1 SBC #0 LSR ROR numcols ; 1 column = 8 pixels LSR ROR numcols LSR ROR numcols INC numcols ; 0..7 => 1 col, etc. JSR @get STA ncomps STA temp @loop: JSR @get STA temp+1 ;ID JSR @get LDX temp+1 PHA AND #$0F STA csampv,X PLA LSR LSR LSR LSR STA csamph,X JSR @get LDX temp+1 STA cquant,X DEC temp BNE @loop LDX #5 ;Find max sample LDA #0 @l2: CMP csamph,X BCS @c2 LDA csamph,X @c2: DEX BNE @l2 STA csamph ;Store in +0 LDX #5 LDA #0 @l3: CMP csampv,X BCS @c3 LDA csampv,X @c3: DEX BNE @l3 STA csampv RTS @get: Get: LDA Length ORA Length+1 BEQ @err2 JSR DecLen JSR GetByte BCC @rts @err2: PLA PLA @err: LDA #READERR STA ERROR @rts: RTS ; And finally -- start of scan! row: .BYTE 0 col: .BYTE 0 SOS: DEC SkipFF ; Skip $FF bytes JSR RENDSTART ; tell renderer we're about to start image JSR Get STA temp ; # of components STA ncomps @l1: JSR Get STA temp+1 ; Component ID JSR Get LDX temp+1 PHA AND #$0F STA ACHuff,X PLA LSR LSR LSR LSR STA DCHuff,X DEC temp BNE @l1 JSR Get ;Scan parameters JSR Get ;(progressive) JSR Get ;(ignore) ; Image data begins here LDA #0 STA row STA col JSR Restart ReadY: ;Intensity LDX #1 ;Component LDY #0 ;Render flag - 0 = render JSR ReadDU ReadCb: ;Chrominance LDX ncomps DEX BEQ ReadDone LDX #2 LDY #1 ; don't render Cb component JSR ReadDU ReadCr: ;Chrominance LDX ncomps DEX BEQ ReadDone LDX #3 LDY #1 ; don't render Cr component JSR ReadDU ReadDone: JSR DecRes ;decrement byte count till Restart marker expected LDA AtEOF ; exit at end of file ORA ERROR ; check for ABORT code from renderer bne @done LDA csamph ;Max sample CLC ADC col STA col CMP numcols BCC ReadY LDA #0 STA col LDA #ImgBuf LDX csampv STX temp2 @rend: STA temp STY temp+1 LDX row CPX rowoff BCC @norend ; ignore anything before starting row ;; we've got 8 lines of image data, so call renderer JSR RENDDRAW ;unto Ceaser @norend: INC row LDA row CMP numrows BCS @done ; has last row in image been reached? SEC SBC rowoff BCC @c2 CMP DISPROWS ; max lines to display BCS @done @c2: LDA temp+1 CLC ; looks like this clc is not needed ADC #>BUFLEN ; we're assuming low byte of buffer length TAY ; will always be 0, LDA temp DEC temp2 BNE @rend @jmp: JMP ReadY @done: INC AtEOF RTS curcomp: .BYTE 0 curbuf: .BYTE 0 rend: .BYTE 0 curcol: .BYTE 0 RendFlag: .BYTE 0 ; ; Read in a data unit ; ReadDU: STY rend ; 0 if rendering this DU, 1 if not STX curcomp LDA #YBuf ; only greyscale supported in this version STA curbuf LDA csampv,X ;Vert samp STA temp @loopy: LDX curcomp LDA csamph,X ;Horiz sampling STA temp+1 LDA col SEC SBC coloff STA curcol @loopx: LDA rend STA RendFlag JSR Fetch LDA ERROR ORA AtEOF BNE rtsdu INC curcol ; we're doing the next column DEC temp+1 BNE @loopx ; have we run out of columns? INC curbuf ; use the next buffer for the other lines DEC temp BNE @loopy ; have we reached last line? rtsdu: RTS ; ; Fetch the data ; Fetch: LDA curcol ; -ve for cols < col offset CMP DISPCOLS ; catches neg too ROL RendFlag ; C set? bne @decode ; don't store image data in output buffer asl ; multipy column number by 8 asl ; to get starting offset into asl ; output buffer tax lda #0 rol sta dest+1 ; do hi byte too LDA curbuf ; get offset into output buffer table ASL TAY txa ADC buftab,Y ; add current output buffer address STA dest ; to offset into buffer LDA dest+1 ADC buftab+1,Y STA dest+1 ; Data storage @decode: JSR DecodeDC LDA ERROR BNE rtsdu JSR DecodeAC LDA ERROR ORA RendFlag BNE rtsdu JSR Dequantize JMP IDCT2D ; @c1: RTS buftab: ;Buffer offsets, change these if you change .ADDR ImgBuf ; output buffer size (# of pixels that will .ADDR ImgBuf+BUFLEN ; fit in ouput buffer) .ADDR ImgBuf+BUFLEN*2 ;------------------------------- ; DEBUG * DEBUG ; PrintDU: ; LDY #0 ; @loop: LDA trans+1,Y ; JSR HexOut ; LDA trans,Y ; JSR HexOut ; LDA #32 ; JSR PRINT1BYTE ; INY ; INY ; CPY #128 ; BCC @loop ; lda #155 ; jmp PRINT1BYTE ;------------------------------- ; ; Decode DC coeff. ; DecodeDC: LDX curcomp ;Set Huffman LDA DCHuff,X ASL TAX LDA DCHuff0,X STA huff LDA DCHuff0+1,X STA huff+1 JSR GetHuff ;Get category LDX ERROR ; Error? BNE @rts JSR GetBits ;Get the bits LDX curcomp LDA Bitslo CLC ADC DClo,X STA DClo,X STA Veclo LDA DChi,X ADC Bitshi STA DChi,X STA Vechi @rts: RTS ; ; Decode AC coeffs ; tmphuf: .BYTE 0 DecodeAC: LDX curcomp ;Set Huffman LDA ACHuff,X ASL TAX STX tmphuf LDY #1 @loop: STY temp2 ;Index LDX tmphuf LDA ACHuff0,X STA huff LDA ACHuff0+1,X STA huff+1 JSR GetHuff ;Get RLE len BEQ @fill LDX ERROR BNE @done STA count ;temp LSR LSR LSR LSR ;# of zeros BEQ @skip @fill: TAX LDA #0 LDY temp2 @lout: STA Veclo,Y STA Vechi,Y INY CPY #64 BCS @done DEX BNE @lout STY temp2 @skip: LDA count AND #$0F ;category JSR GetBits LDY temp2 LDA Bitslo STA Veclo,Y LDA Bitshi STA Vechi,Y INY CPY #64 BCC @loop @done: RTS ; ; Dequantize the vector Vec ; ; Mult is 16 bit signed x 8 bit unsigned ; with 16-bit result, so sign etc. are ; taken care of automatically. ; ; result -> trans ; quanttab: .ADDR QT0 .ADDR QT1 .ADDR QT2 .ADDR QT3 ; Table to un-zigzag coeffs; multiples ; of 2, since 2 byte result. zigzag: .BYTE 0,2,16,32,18,4,6,20 .BYTE 34,48,64,50,36,22,8,10 .BYTE 24,38,52,66,80,96,82,68 .BYTE 54,40,26,12,14,28,42,56 .BYTE 70,84,98,112,114,100,86,72 .BYTE 58,44,30,46,60,74,88,102 .BYTE 116,118,104,90,76,62,78,92 .BYTE 106,120,122,108,94,110,124,126 Dequantize: LDX curcomp LDA cquant,X ASL TAX LDA quanttab,X STA quantp LDA quanttab+1,X STA quantp+1 LDX #63 @loop: TXA TAY LDA (quantp),Y STA mult1lo STA mult1hi EOR #$FF CLC ADC #1 STA mult2lo STA mult2hi LDY Veclo,X BNE @c1 STY Bitslo STY Bitshi BEQ @high @c1: LDA (mult1lo),Y SEC SBC (mult2lo),Y STA Bitslo LDA (mult1hi),Y SBC (mult2hi),Y STA Bitshi @high: LDY Vechi,X LDA (mult1lo),Y SEC SBC (mult2lo),Y CLC ADC Bitshi LDY zigzag,X ;Un-zigzag INY STA trans,Y DEY LDA Bitslo STA trans,Y DEX BPL @loop RTS ; ; Retrieve .A bits and convert ; to signed number in (Bitslo, Bitshi) ; sign: .BYTE 0 GetBits: STA count TAX BEQ @zero JSR GetBit LDA #0 BCS @c1 LDA #$FF ;0-> negative @c1: STA Bitshi ROL STA Bitslo STA sign DEC count BEQ @done @loop: JSR GetBit ROL Bitslo ROL Bitshi DEC count BNE @loop @done: LDA sign BPL @rts INC Bitslo ;Make 2's comp BNE @rts INC Bitshi @rts: RTS @zero: STA Bitslo STA Bitshi RTS ; ; Huffman tree routines. ; ; The Huffman tree is implemented as ; a series of 2-byte nodes. Left ; nodes are at huff+2, right nodes ; are at (huff) if link < $8000. ; Link = $80xx means xx=leaf value, ; link = $FFxx means no right link, ; link+2 = HuffTop -> no left link. ; DCHuff0: .ADDR 0 ;Addresses DCHuff1: .ADDR 0 DCHuff2: .ADDR 0 DCHuff3: .ADDR 0 ACHuff0: .ADDR 0 ACHuff1: .ADDR 0 ACHuff2: .ADDR 0 ACHuff3: .ADDR 0 ; ty: .BYTE 0 ; tx: .BYTE 0 InitHuff: LDA #Huffmem ; in Huff buffer STA HuffTop+1 RTS ; Create new node and make current node ; point to it. ; ; On entry: .Y = 0 -> right node, ; otherwise left node NewNode: ; STY ty ; STX tx ; this routine doesn't touch X register, so don't need this TYA BNE @skip ; Y!=0 is a left node LDA HuffTop ; Y = 0, this is a right node SEC ; point previous node at new one SBC huff ; new node will be at HuffTop STA (huff),Y ; so find offset from previous node to INY ; new one, and store that value in previous LDA HuffTop+1 ; node's pointer SBC huff+1 STA (huff),Y @skip: LDA HuffTop ; move HuffTop to take account of the new STA point ; node CLC ADC #2 ; each node is 2 bytes worth STA HuffTop LDA HuffTop+1 STA point+1 ADC #0 STA HuffTop+1 LDY #01 LDA #$FF STA (point),Y ;Init new node ; LDY ty ; LDX tx RTS ; Add a new node; .X = length ; (huff) -> tree root huffbits: .WORD 0 ;hi,lo huffval: .BYTE 0 AddNode: STA huffval @loop: LDY #1 CPX #9 BCC @c1 DEY @c1: LDA BITP,X AND huffbits,Y BNE @right @left: LDA huff ;Check if at end CLC ADC #2 PHA TAY LDA huff+1 ADC #0 PHA CPY HuffTop SBC HuffTop+1 BCC @skip1 ;Not a new node LDY #$80 ;Create left node JSR NewNode @skip1: PLA STA huff+1 PLA STA huff JMP @dex @right: LDY #1 LDA (huff),Y ;Check for rt ptr BPL @skip2 DEY ;.Y=0 -> rt node JSR NewNode @skip2: LDY #0 LDA (huff),Y CLC ADC huff PHA INY LDA (huff),Y ADC huff+1 STA huff+1 PLA STA huff @dex: DEX BNE @loop LDA #$80 LDY #01 STA (huff),Y ;Store value LDA huffval DEY STA (huff),Y ;$80xx RTS ; ; GetHuff -- Get valid Huffman code ; from (huff) ; GetHuff: lda #16 sta bitcnt LDY #01 LDA (huff),Y CMP #$80 BEQ @found dec bitcnt JSR GetBit BCS @right LDA huff ADC #2 ; C is already clear TAX LDA huff+1 ADC #0 TAY CPX HuffTop SBC HuffTop+1 BCS @err STY huff+1 STX huff BCC GetHuff @right: LDY #01 LDA (huff),Y BMI @err PHA DEY LDA (huff),Y CLC ADC huff STA huff PLA ADC huff+1 STA huff+1 BNE GetHuff @found: DEY LDA (huff),Y RTS @err: @ckcnt: dec bitcnt bmi @bitend jsr GetBit jmp @ckcnt @bitend: LDA reslen+1 ; if there are restart markers in ora reslen ; the file, then ignore the error sta SkipErr bne @rts ; and let the image re-sync at next ; restart marker LDA #HUFFERR ; if no restart markers, then give an error STA ERROR @rts: lda #0 RTS bitcnt: .byte 0 ;******************************* ; ; IDCT routines ; ;******************************* IDCT2D: ; First the columns ; cols: LDX #0 @l0: STX index LDY #0 @l1: LDA trans,X STA DCT,Y LDA trans+1,X STA DCT+1,Y TXA CLC ADC #16 TAX INY INY CPY #16 BNE @l1 JSR IDCT LDY #0 LDX index @l1b: LDA Coeff,Y STA trans,X LDA Coeff+1,Y STA trans+1,X TXA CLC ADC #16 TAX INY INY CPY #16 BNE @l1b LDX index INX INX CPX #16 BCC @l0 ;; this copies an 8x8 block of decoded pixels into the output ;; buffer. Change this to modify the layout of the data in the ;; output buffer. ; Then the rows rows: lda curcol sec ; Acc = curcol + coloff + 1 adc coloff ; take skipped columns into account cmp numcols ; is current column >= to image max column? bcc @notlast ; is less than, continue as normal beq @lstcol ; is equal to, check how many pixels to do rts ; is greater than, so skip them @lstcol: lda width ; check if width is not a multiple of 8 and #%00000111 asl ; data is 2 bytes worth for each pixel bne @skp16 ; not a multiple, so do less than 8 lines @notlast: lda #16 @skp16: sta @endcol ldx row inx cpx numrows bne @notlastr lda height and #%00000111 asl asl asl asl bne @skp128 @notlastr: lda #128 @skp128: sta @endrow LDX #0 STX index @l0: LDY #0 ; copy 16 bytes from trans to DCT @l1: LDA trans,X STA DCT,Y LDA trans+1,X STA DCT+1,Y INX INX INY INY CPY #16 BNE @l1 STX index JSR IDCT LDY #0 LDX #0 @l1b: LDA Coeff,X STA Bitslo LDA Coeff+1,X CMP #$80 ROR ROR Bitslo CMP #$80 ROR ROR Bitslo STA Bitshi LDA Bitslo ADC #128 ;C determines rounding STA (dest),Y LDA Bitshi ;Range check ADC #0 BEQ @cont BPL @pos ; if hi byte > 0 then store $FF LDA #0 .BYTE $2C @pos: LDA #$FF STA (dest),Y @cont: iny INX INX cpx @endcol BNE @l1b @nxtlne: clc lda dest ; move down to next line adc #<320 ; change this if max # of pixels in sta dest ; a line changes lda dest+1 adc #>320 ; ditto sta dest+1 LDX index ; do 64 pixels (8x8) worth of data cpx @endrow ; unless we have less than 8 lines to draw bcc @l0 ; (2 bytes per pixel converted to 1 byte ; per pixel) cpx #128 ; we drew all 8 lines, then exit bcc @clrlines rts @clrlines: ; we drew less than 8 lines, so store 0 lda #0 ; in the rest ldy #7 ; we're doing 8 rows of data at a time @clrlp: sta (dest),y inx inx dey bpl @clrlp stx index bne @nxtlne ; forced branch @endcol: .BYTE 0 ; last column to copy, catches images ; that don't have a width of a multiple of 8 @endrow: .BYTE 0 ; last row to copy, catches images ; that don't have a height of a multiple of 8 F0 = DCT F1 = DCT+2 F2 = DCT+4 F3 = DCT+6 F4 = DCT+8 F5 = DCT+10 F6 = DCT+12 F7 = DCT+14 C0 = Coeff C1 = Coeff+2 C2 = Coeff+4 C3 = Coeff+6 C4 = Coeff+8 C5 = Coeff+10 C6 = Coeff+12 C7 = Coeff+14 ; ; Compute the inverse DCT (1D) ; ; Uses modified reversed flowgraph from ; Pennebaker & Mitchell, p. 52 ; ; Input: DCT coeffs contained in Flo/Fhi ; Output: Original coeffs in COEFFS ; IDCT: JSR PrepDat ;Shift and such ; Stage 1: F(5) <- F(5) - F(3) ; F(1) <- F(1) + F(7) ; F(7) <- F(1) - F(7) ; F(3) <- F(5) + F(3) LDA F5 SEC SBC F3 STA t1 LDA F5+1 SBC F3+1 STA t1+1 LDA F1 CLC ADC F7 STA t2 LDA F1+1 ADC F7+1 STA t2+1 LDA F1 SEC SBC F7 STA t3 LDA F1+1 SBC F7+1 STA t3+1 LDA F5 CLC ADC F3 STA F3 LDA F5+1 ADC F3+1 STA F3+1 LDA t3 STA F7 LDA t3+1 STA F7+1 LDA t2 STA F1 LDA t2+1 STA F1+1 LDA t1 STA F5 LDA t1+1 STA F5+1 ; Stage 2: F(2) <- F(2) - F(6) ; F(6) <- F(2) + F(6) ; F(1) <- F(1) - F(3) ; F(3) <- F(1) + F(3) LDA F2 SEC SBC F6 STA t1 LDA F2+1 SBC F6+1 STA t1+1 LDA F2 CLC ADC F6 STA F6 LDA F2+1 ADC F6+1 STA F6+1 LDA t1 STA F2 LDA t1+1 STA F2+1 LDA F1 SEC SBC F3 STA t1 LDA F1+1 SBC F3+1 STA t1+1 LDA F1 CLC ADC F3 STA F3 LDA F1+1 ADC F3+1 STA F3+1 LDA t1 STA F1 LDA t1+1 STA F1+1 ; Stage 3: F(2) <- a1*F(2) ; F(5) <- -a2*F(5) + t1 ; F(1) <- a3*F(1) ; F(7) <- a4*F(7) + t1 ; where t1 = -a5*(F(5) + F(7)) ; F(2) <- a1*F(2) LDX F2 ;Lo LDY F2+1 ;Hi LDA a1lo,Y CLC ADC a1hi,X STA Bitslo ;lo byte LDA a1hi,Y ADC #0 CPY #$80 BCC @pos1 STA Bitshi LDA Bitslo SBC #a1216 @pos1: STA F2+1 LDA Bitslo STA F2 ; F(1) = a3*F(1) LDX F1 ;Lo LDY F1+1 ;Hi LDA a3lo,Y CLC ADC a3hi,X STA Bitslo LDA a3hi,Y ADC #0 CPY #$80 BCC @pos1b STA Bitshi LDA Bitslo SBC #a3216 @pos1b: STA F1+1 LDA Bitslo STA F1 ; t1 = -a5*(F(5) + F(7)) LDA F5 CLC ADC F7 TAX ;Lo LDA F5+1 ADC F7+1 TAY ;Hi LDA a5lo,Y CLC ADC a5hi,X STA Bitslo LDA a5hi,Y ADC #0 STA Bitshi CPY #$80 BCC @pos2 LDA Bitslo SBC #a5216 STA Bitshi @pos2: LDA Bitslo EOR #$FF CLC ADC #1 STA t1 LDA Bitshi EOR #$FF ADC #0 STA t1+1 ; F(5) = t1 - a2*F(5) LDX F5 ;Lo LDY F5+1 ;Hi LDA a2lo,Y CLC ADC a2hi,X STA Bitslo LDA a2hi,Y ADC #0 CPY #$80 BCC @pos3 STA Bitshi LDA Bitslo SBC #a2216 @pos3: STA Bitshi LDA t1 SEC SBC Bitslo STA F5 LDA t1+1 SBC Bitshi STA F5+1 ; F(7) = a4*F(7) + t1 LDX F7 ;Lo LDY F7+1 ;Hi LDA a4lo,Y CLC ADC a4hi,X STA Bitslo LDA a4hi,Y ADC a4gh,X ;a4*.X can be >255 CPY #$80 BCC @pos4 STA Bitshi LDA Bitslo SBC #a4216 @pos4: STA Bitshi LDA Bitslo CLC ADC t1 STA F7 LDA Bitshi ADC t1+1 STA F7+1 ; Stage 4: ; F(0) <- F(0) + F(4) ; F(4) <- F(0) - F(4) ; F(6) <- F(2) + F(6) LDA F0 CLC ADC F4 STA t1 LDA F0+1 ADC F4+1 STA t1+1 LDA F0 SEC SBC F4 STA F4 LDA F0+1 SBC F4+1 STA F4+1 LDA t1 STA F0 LDA t1+1 STA F0+1 LDA F2 CLC ADC F6 STA F6 LDA F2+1 ADC F6+1 STA F6+1 ; Stage 5: ; F(0) <- F(0) + F(6) ; F(4) <- F(2) + F(4) ; F(2) <- F(4) - F(2) ; F(6) <- F(0) - F(6) ; F(3) <- F(3) + F(7) ; F(7) <- F(7) + F(1) ; F(1) <- F(1) - F(5) ; F(5) <- -F(5) LDA F0 CLC ADC F6 STA t1 LDA F0+1 ADC F6+1 STA t1+1 LDA F0 SEC SBC F6 STA F6 LDA F0+1 SBC F6+1 STA F6+1 LDA t1 STA F0 LDA t1+1 STA F0+1 LDA F4 CLC ADC F2 STA t1 LDA F4+1 ADC F2+1 STA t1+1 LDA F4 SEC SBC F2 STA F2 LDA F4+1 SBC F2+1 STA F2+1 LDA t1 STA F4 LDA t1+1 STA F4+1 LDA F3 CLC ADC F7 STA F3 LDA F3+1 ADC F7+1 STA F3+1 LDA F7 CLC ADC F1 STA F7 LDA F7+1 ADC F1+1 STA F7+1 LDA F1 SEC SBC F5 STA F1 LDA F1+1 SBC F5+1 STA F1+1 LDA #0 SEC SBC F5 STA F5 LDA #0 SBC F5+1 STA F5+1 ; Final stage: ; c(0) = F(0) + F(3) ; c(1) = F(4) + F(7) ; c(2) = F(2) + F(1) ; c(3) = F(6) + F(5) ; c(4) = F(6) - F(5) ; c(5) = F(2) - F(1) ; c(6) = F(4) - F(7) ; c(7) = F(0) - F(3) ; ; Note: values are offset -128 LDA F0 CLC ADC F3 STA C0 LDA F0+1 ADC F3+1 STA C0+1 LDA F4 CLC ADC F7 STA C1 LDA F4+1 ADC F7+1 STA C1+1 LDA F2 CLC ADC F1 STA C2 LDA F2+1 ADC F1+1 STA C2+1 LDA F6 CLC ADC F5 STA C3 LDA F6+1 ADC F5+1 STA C3+1 LDA F6 SEC SBC F5 STA C4 LDA F6+1 SBC F5+1 STA C4+1 LDA F2 SEC SBC F1 STA C5 LDA F2+1 SBC F1+1 STA C5+1 LDA F4 SEC SBC F7 STA C6 LDA F4+1 SBC F7+1 STA C6+1 LDA F0 SEC SBC F3 STA C7 LDA F0+1 SBC F3+1 STA C7+1 RTS ;Sheeew! ; ; Since the algorithm is really an ; FFT converted into a DCT, the ; coefficients need a little massaging ; before tranformation. ; ; Specifically, ; F(i) = S(i)/(2cos(i*pi/16)) i=0..7 ; with F(0)=F(0)*2/sqrt(2), which can ; be combined with the first step ; using the table for i=4. ; ; These multipliers can in part be ; incorporated in the quantization ; table, but for now they're out in ; the open. ; PrepDat: LDX #0 LDA #sec4 STA point+1 LDA F0 STA Bitslo LDA F0+1 JSR PMult STA F0+1 LDA Bitslo STA F0 LDX #0 LDA #sec1 STA point+1 LDA F1 STA Bitslo LDA F1+1 JSR PMult STA F1+1 LDA Bitslo STA F1 LDX #0 LDA #sec2 STA point+1 LDA F2 STA Bitslo LDA F2+1 JSR PMult STA F2+1 LDA Bitslo STA F2 LDX #0 LDA #sec3 STA point+1 LDA F3 STA Bitslo LDA F3+1 JSR PMult STA F3+1 LDA Bitslo STA F3 LDX #0 LDA #sec4 STA point+1 LDA F4 STA Bitslo LDA F4+1 JSR PMult STA F4+1 LDA Bitslo STA F4 LDX #0 LDA #sec5 STA point+1 LDA F5 STA Bitslo LDA F5+1 JSR PMult STA F5+1 LDA Bitslo STA F5 LDX #0 LDA #sec6 STA point+1 LDA F6 STA Bitslo LDA F6+1 JSR PMult STA F6+1 LDA Bitslo STA F6 LDX #0 LDA #sec7 STA point+1 LDA F7 STA Bitslo LDA F7+1 JSR PMult STA F7+1 LDA Bitslo STA F7 RTS PMult: ;exit .A = Bitshi BMI @neg BEQ @ok @l1: INX ;Shift count LSR ROR Bitslo CMP #0 BNE @l1 @ok: STA Bitshi LDA Bitslo ASL ROL Bitshi ADC point STA point LDA Bitshi ADC point+1 STA point+1 LDY #0 LDA (point),Y STA Bitslo INY LDA (point),Y DEX BMI @rts @l1b: ASL Bitslo ROL DEX BPL @l1b @rts: RTS @neg: STA Bitshi LDA #0 SEC SBC Bitslo STA Bitslo LDA #0 SBC Bitshi BEQ @ok2 @l2: INX ;Shift count LSR ROR Bitslo CMP #0 BNE @l2 @ok2: ASL Bitslo ROL STA Bitshi LDA Bitslo ADC point STA point LDA Bitshi ADC point+1 STA point+1 LDY #0 LDA (point),Y STA Bitslo INY LDA (point),Y DEX BMI @rts2 @l2b: ASL Bitslo ROL DEX BPL @l2b @rts2: STA Bitshi LDA #0 SEC SBC Bitslo STA Bitslo LDA #0 SBC Bitshi RTS filepos: ; .RES 3 ; 3 bytes for current file position symbols = filepos + 3 ; .RES 16 csampv = symbols + 16 ; .RES 6 ; Sampling factors csamph = csampv + 6 ; .RES 6 ; (horizontal) cquant = csamph + 6 ; .RES 6 ; Quantization table DClo = cquant + 6 ; .RES 6 ;DC coeffs DChi = DClo + 6 ; .RES 6 ACHuff = DChi + 6 ; .RES 6 ;AC table to use DCHuff = ACHuff + 6 ; .RES 6 ;DC table to use segend: .org DCHuff+6 ;; end of jpeg decoder .if (* >= $2F00) .out .concat("Error - Decoder code overrun into data area ", .string(*)) .else .out .concat("decoder code ends at ", .string(*)) .endif ;; data table segment .ADDR datastart .ADDR dataend-1 .ORG Negmlo datastart: ;; this is the table data ; Negmlo .BYTE $00,$80,$01,$82,$04,$86,$09,$8c,$10,$94,$19,$9e,$24,$aa,$31,$b8 .BYTE $40,$c8,$51,$da,$64,$ee,$79,$04,$90,$1c,$a9,$36,$c4,$52,$e1,$70 .BYTE $00,$90,$21,$b2,$44,$d6,$69,$fc,$90,$24,$b9,$4e,$e4,$7a,$11,$a8 .BYTE $40,$d8,$71,$0a,$a4,$3e,$d9,$74,$10,$ac,$49,$e6,$84,$22,$c1,$60 .BYTE $00,$a0,$41,$e2,$84,$26,$c9,$6c,$10,$b4,$59,$fe,$a4,$4a,$f1,$98 .BYTE $40,$e8,$91,$3a,$e4,$8e,$39,$e4,$90,$3c,$e9,$96,$44,$f2,$a1,$50 .BYTE $00,$b0,$61,$12,$c4,$76,$29,$dc,$90,$44,$f9,$ae,$64,$1a,$d1,$88 .BYTE $40,$f8,$b1,$6a,$24,$de,$99,$54,$10,$cc,$89,$46,$04,$c2,$81,$40 .BYTE $00,$c0,$81,$42,$04,$c6,$89,$4c,$10,$d4,$99,$5e,$24,$ea,$b1,$78 .BYTE $40,$08,$d1,$9a,$64,$2e,$f9,$c4,$90,$5c,$29,$f6,$c4,$92,$61,$30 .BYTE $00,$d0,$a1,$72,$44,$16,$e9,$bc,$90,$64,$39,$0e,$e4,$ba,$91,$68 .BYTE $40,$18,$f1,$ca,$a4,$7e,$59,$34,$10,$ec,$c9,$a6,$84,$62,$41,$20 .BYTE $00,$e0,$c1,$a2,$84,$66,$49,$2c,$10,$f4,$d9,$be,$a4,$8a,$71,$58 .BYTE $40,$28,$11,$fa,$e4,$ce,$b9,$a4,$90,$7c,$69,$56,$44,$32,$21,$10 .BYTE $00,$f0,$e1,$d2,$c4,$b6,$a9,$9c,$90,$84,$79,$6e,$64,$5a,$51,$48 .BYTE $40,$38,$31,$2a,$24,$1e,$19,$14,$10,$0c,$09,$06,$04,$02,$01,$00 ; Posmlo .BYTE $00,$00,$01,$02,$04,$06,$09,$0c,$10,$14,$19,$1e,$24,$2a,$31,$38 .BYTE $40,$48,$51,$5a,$64,$6e,$79,$84,$90,$9c,$a9,$b6,$c4,$d2,$e1,$f0 .BYTE $00,$10,$21,$32,$44,$56,$69,$7c,$90,$a4,$b9,$ce,$e4,$fa,$11,$28 .BYTE $40,$58,$71,$8a,$a4,$be,$d9,$f4,$10,$2c,$49,$66,$84,$a2,$c1,$e0 .BYTE $00,$20,$41,$62,$84,$a6,$c9,$ec,$10,$34,$59,$7e,$a4,$ca,$f1,$18 .BYTE $40,$68,$91,$ba,$e4,$0e,$39,$64,$90,$bc,$e9,$16,$44,$72,$a1,$d0 .BYTE $00,$30,$61,$92,$c4,$f6,$29,$5c,$90,$c4,$f9,$2e,$64,$9a,$d1,$08 .BYTE $40,$78,$b1,$ea,$24,$5e,$99,$d4,$10,$4c,$89,$c6,$04,$42,$81,$c0 .BYTE $00,$40,$81,$c2,$04,$46,$89,$cc,$10,$54,$99,$de,$24,$6a,$b1,$f8 .BYTE $40,$88,$d1,$1a,$64,$ae,$f9,$44,$90,$dc,$29,$76,$c4,$12,$61,$b0 .BYTE $00,$50,$a1,$f2,$44,$96,$e9,$3c,$90,$e4,$39,$8e,$e4,$3a,$91,$e8 .BYTE $40,$98,$f1,$4a,$a4,$fe,$59,$b4,$10,$6c,$c9,$26,$84,$e2,$41,$a0 .BYTE $00,$60,$c1,$22,$84,$e6,$49,$ac,$10,$74,$d9,$3e,$a4,$0a,$71,$d8 .BYTE $40,$a8,$11,$7a,$e4,$4e,$b9,$24,$90,$fc,$69,$d6,$44,$b2,$21,$90 .BYTE $00,$70,$e1,$52,$c4,$36,$a9,$1c,$90,$04,$79,$ee,$64,$da,$51,$c8 .BYTE $40,$b8,$31,$aa,$24,$9e,$19,$94,$10,$8c,$09,$86,$04,$82,$01,$80 .BYTE $00,$80,$01,$82,$04,$86,$09,$8c,$10,$94,$19,$9e,$24,$aa,$31,$b8 .BYTE $40,$c8,$51,$da,$64,$ee,$79,$04,$90,$1c,$a9,$36,$c4,$52,$e1,$70 .BYTE $00,$90,$21,$b2,$44,$d6,$69,$fc,$90,$24,$b9,$4e,$e4,$7a,$11,$a8 .BYTE $40,$d8,$71,$0a,$a4,$3e,$d9,$74,$10,$ac,$49,$e6,$84,$22,$c1,$60 .BYTE $00,$a0,$41,$e2,$84,$26,$c9,$6c,$10,$b4,$59,$fe,$a4,$4a,$f1,$98 .BYTE $40,$e8,$91,$3a,$e4,$8e,$39,$e4,$90,$3c,$e9,$96,$44,$f2,$a1,$50 .BYTE $00,$b0,$61,$12,$c4,$76,$29,$dc,$90,$44,$f9,$ae,$64,$1a,$d1,$88 .BYTE $40,$f8,$b1,$6a,$24,$de,$99,$54,$10,$cc,$89,$46,$04,$c2,$81,$40 .BYTE $00,$c0,$81,$42,$04,$c6,$89,$4c,$10,$d4,$99,$5e,$24,$ea,$b1,$78 .BYTE $40,$08,$d1,$9a,$64,$2e,$f9,$c4,$90,$5c,$29,$f6,$c4,$92,$61,$30 .BYTE $00,$d0,$a1,$72,$44,$16,$e9,$bc,$90,$64,$39,$0e,$e4,$ba,$91,$68 .BYTE $40,$18,$f1,$ca,$a4,$7e,$59,$34,$10,$ec,$c9,$a6,$84,$62,$41,$20 .BYTE $00,$e0,$c1,$a2,$84,$66,$49,$2c,$10,$f4,$d9,$be,$a4,$8a,$71,$58 .BYTE $40,$28,$11,$fa,$e4,$ce,$b9,$a4,$90,$7c,$69,$56,$44,$32,$21,$10 .BYTE $00,$f0,$e1,$d2,$c4,$b6,$a9,$9c,$90,$84,$79,$6e,$64,$5a,$51,$48 .BYTE $40,$38,$31,$2a,$24,$1e,$19,$14,$10,$0c,$09,$06,$04,$02,$01,$00 ; Negmhi .BYTE $40,$3f,$3f,$3e,$3e,$3d,$3d,$3c,$3c,$3b,$3b,$3a,$3a,$39,$39,$38 .BYTE $38,$37,$37,$36,$36,$35,$35,$35,$34,$34,$33,$33,$32,$32,$31,$31 .BYTE $31,$30,$30,$2f,$2f,$2e,$2e,$2d,$2d,$2d,$2c,$2c,$2b,$2b,$2b,$2a .BYTE $2a,$29,$29,$29,$28,$28,$27,$27,$27,$26,$26,$25,$25,$25,$24,$24 .BYTE $24,$23,$23,$22,$22,$22,$21,$21,$21,$20,$20,$1f,$1f,$1f,$1e,$1e .BYTE $1e,$1d,$1d,$1d,$1c,$1c,$1c,$1b,$1b,$1b,$1a,$1a,$1a,$19,$19,$19 .BYTE $19,$18,$18,$18,$17,$17,$17,$16,$16,$16,$15,$15,$15,$15,$14,$14 .BYTE $14,$13,$13,$13,$13,$12,$12,$12,$12,$11,$11,$11,$11,$10,$10,$10 .BYTE $10,$0f,$0f,$0f,$0f,$0e,$0e,$0e,$0e,$0d,$0d,$0d,$0d,$0c,$0c,$0c .BYTE $0c,$0c,$0b,$0b,$0b,$0b,$0a,$0a,$0a,$0a,$0a,$09,$09,$09,$09,$09 .BYTE $09,$08,$08,$08,$08,$08,$07,$07,$07,$07,$07,$07,$06,$06,$06,$06 .BYTE $06,$06,$05,$05,$05,$05,$05,$05,$05,$04,$04,$04,$04,$04,$04,$04 .BYTE $04,$03,$03,$03,$03,$03,$03,$03,$03,$02,$02,$02,$02,$02,$02,$02 .BYTE $02,$02,$02,$01,$01,$01,$01,$01,$01,$01,$01,$01,$01,$01,$01,$01 .BYTE $01,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00 .BYTE $00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00 ; Posmhi .BYTE $00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00 .BYTE $00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00 .BYTE $01,$01,$01,$01,$01,$01,$01,$01,$01,$01,$01,$01,$01,$01,$02,$02 .BYTE $02,$02,$02,$02,$02,$02,$02,$02,$03,$03,$03,$03,$03,$03,$03,$03 .BYTE $04,$04,$04,$04,$04,$04,$04,$04,$05,$05,$05,$05,$05,$05,$05,$06 .BYTE $06,$06,$06,$06,$06,$07,$07,$07,$07,$07,$07,$08,$08,$08,$08,$08 .BYTE $09,$09,$09,$09,$09,$09,$0a,$0a,$0a,$0a,$0a,$0b,$0b,$0b,$0b,$0c .BYTE $0c,$0c,$0c,$0c,$0d,$0d,$0d,$0d,$0e,$0e,$0e,$0e,$0f,$0f,$0f,$0f .BYTE $10,$10,$10,$10,$11,$11,$11,$11,$12,$12,$12,$12,$13,$13,$13,$13 .BYTE $14,$14,$14,$15,$15,$15,$15,$16,$16,$16,$17,$17,$17,$18,$18,$18 .BYTE $19,$19,$19,$19,$1a,$1a,$1a,$1b,$1b,$1b,$1c,$1c,$1c,$1d,$1d,$1d .BYTE $1e,$1e,$1e,$1f,$1f,$1f,$20,$20,$21,$21,$21,$22,$22,$22,$23,$23 .BYTE $24,$24,$24,$25,$25,$25,$26,$26,$27,$27,$27,$28,$28,$29,$29,$29 .BYTE $2a,$2a,$2b,$2b,$2b,$2c,$2c,$2d,$2d,$2d,$2e,$2e,$2f,$2f,$30,$30 .BYTE $31,$31,$31,$32,$32,$33,$33,$34,$34,$35,$35,$35,$36,$36,$37,$37 .BYTE $38,$38,$39,$39,$3a,$3a,$3b,$3b,$3c,$3c,$3d,$3d,$3e,$3e,$3f,$3f .BYTE $40,$40,$41,$41,$42,$42,$43,$43,$44,$44,$45,$45,$46,$46,$47,$47 .BYTE $48,$48,$49,$49,$4a,$4a,$4b,$4c,$4c,$4d,$4d,$4e,$4e,$4f,$4f,$50 .BYTE $51,$51,$52,$52,$53,$53,$54,$54,$55,$56,$56,$57,$57,$58,$59,$59 .BYTE $5a,$5a,$5b,$5c,$5c,$5d,$5d,$5e,$5f,$5f,$60,$60,$61,$62,$62,$63 .BYTE $64,$64,$65,$65,$66,$67,$67,$68,$69,$69,$6a,$6a,$6b,$6c,$6c,$6d .BYTE $6e,$6e,$6f,$70,$70,$71,$72,$72,$73,$74,$74,$75,$76,$76,$77,$78 .BYTE $79,$79,$7a,$7b,$7b,$7c,$7d,$7d,$7e,$7f,$7f,$80,$81,$82,$82,$83 .BYTE $84,$84,$85,$86,$87,$87,$88,$89,$8a,$8a,$8b,$8c,$8d,$8d,$8e,$8f .BYTE $90,$90,$91,$92,$93,$93,$94,$95,$96,$96,$97,$98,$99,$99,$9a,$9b .BYTE $9c,$9d,$9d,$9e,$9f,$a0,$a0,$a1,$a2,$a3,$a4,$a4,$a5,$a6,$a7,$a8 .BYTE $a9,$a9,$aa,$ab,$ac,$ad,$ad,$ae,$af,$b0,$b1,$b2,$b2,$b3,$b4,$b5 .BYTE $b6,$b7,$b7,$b8,$b9,$ba,$bb,$bc,$bd,$bd,$be,$bf,$c0,$c1,$c2,$c3 .BYTE $c4,$c4,$c5,$c6,$c7,$c8,$c9,$ca,$cb,$cb,$cc,$cd,$ce,$cf,$d0,$d1 .BYTE $d2,$d3,$d4,$d4,$d5,$d6,$d7,$d8,$d9,$da,$db,$dc,$dd,$de,$df,$e0 .BYTE $e1,$e1,$e2,$e3,$e4,$e5,$e6,$e7,$e8,$e9,$ea,$eb,$ec,$ed,$ee,$ef .BYTE $f0,$f1,$f2,$f3,$f4,$f5,$f6,$f7,$f8,$f9,$fa,$fb,$fc,$fd,$fe,$ff ; a1lo .BYTE $00,$b5,$6a,$1f,$d4,$89,$3e,$f3,$a8,$5d,$12,$c7,$7c,$31,$e6,$9b .BYTE $50,$05,$ba,$6f,$24,$d9,$8e,$43,$f8,$ad,$63,$18,$cd,$82,$37,$ec .BYTE $a1,$56,$0b,$c0,$75,$2a,$df,$94,$49,$fe,$b3,$68,$1d,$d2,$87,$3c .BYTE $f1,$a6,$5b,$10,$c5,$7a,$2f,$e4,$99,$4e,$03,$b8,$6d,$22,$d7,$8c .BYTE $41,$f6,$ab,$60,$15,$ca,$7f,$34,$e9,$9e,$53,$08,$bd,$72,$28,$dd .BYTE $92,$47,$fc,$b1,$66,$1b,$d0,$85,$3a,$ef,$a4,$59,$0e,$c3,$78,$2d .BYTE $e2,$97,$4c,$01,$b6,$6b,$20,$d5,$8a,$3f,$f4,$a9,$5e,$13,$c8,$7d .BYTE $32,$e7,$9c,$51,$06,$bb,$70,$25,$da,$8f,$44,$f9,$ae,$63,$18,$cd .BYTE $82,$37,$ed,$a2,$57,$0c,$c1,$76,$2b,$e0,$95,$4a,$ff,$b4,$69,$1e .BYTE $d3,$88,$3d,$f2,$a7,$5c,$11,$c6,$7b,$30,$e5,$9a,$4f,$04,$b9,$6e .BYTE $23,$d8,$8d,$42,$f7,$ac,$61,$16,$cb,$80,$35,$ea,$9f,$54,$09,$be .BYTE $73,$28,$dd,$92,$47,$fc,$b2,$67,$1c,$d1,$86,$3b,$f0,$a5,$5a,$0f .BYTE $c4,$79,$2e,$e3,$98,$4d,$02,$b7,$6c,$21,$d6,$8b,$40,$f5,$aa,$5f .BYTE $14,$c9,$7e,$33,$e8,$9d,$52,$07,$bc,$71,$26,$db,$90,$45,$fa,$af .BYTE $64,$19,$ce,$83,$38,$ed,$a2,$57,$0c,$c2,$77,$2c,$e1,$96,$4b,$00 .BYTE $b5,$6a,$1f,$d4,$89,$3e,$f3,$a8,$5d,$12,$c7,$7c,$31,$e6,$9b,$50 ; a1hi .BYTE $00,$00,$01,$02,$02,$03,$04,$04,$05,$06,$07,$07,$08,$09,$09,$0a .BYTE $0b,$0c,$0c,$0d,$0e,$0e,$0f,$10,$10,$11,$12,$13,$13,$14,$15,$15 .BYTE $16,$17,$18,$18,$19,$1a,$1a,$1b,$1c,$1c,$1d,$1e,$1f,$1f,$20,$21 .BYTE $21,$22,$23,$24,$24,$25,$26,$26,$27,$28,$29,$29,$2a,$2b,$2b,$2c .BYTE $2d,$2d,$2e,$2f,$30,$30,$31,$32,$32,$33,$34,$35,$35,$36,$37,$37 .BYTE $38,$39,$39,$3a,$3b,$3c,$3c,$3d,$3e,$3e,$3f,$40,$41,$41,$42,$43 .BYTE $43,$44,$45,$46,$46,$47,$48,$48,$49,$4a,$4a,$4b,$4c,$4d,$4d,$4e .BYTE $4f,$4f,$50,$51,$52,$52,$53,$54,$54,$55,$56,$56,$57,$58,$59,$59 .BYTE $5a,$5b,$5b,$5c,$5d,$5e,$5e,$5f,$60,$60,$61,$62,$62,$63,$64,$65 .BYTE $65,$66,$67,$67,$68,$69,$6a,$6a,$6b,$6c,$6c,$6d,$6e,$6f,$6f,$70 .BYTE $71,$71,$72,$73,$73,$74,$75,$76,$76,$77,$78,$78,$79,$7a,$7b,$7b .BYTE $7c,$7d,$7d,$7e,$7f,$7f,$80,$81,$82,$82,$83,$84,$84,$85,$86,$87 .BYTE $87,$88,$89,$89,$8a,$8b,$8c,$8c,$8d,$8e,$8e,$8f,$90,$90,$91,$92 .BYTE $93,$93,$94,$95,$95,$96,$97,$98,$98,$99,$9a,$9a,$9b,$9c,$9c,$9d .BYTE $9e,$9f,$9f,$a0,$a1,$a1,$a2,$a3,$a4,$a4,$a5,$a6,$a6,$a7,$a8,$a9 .BYTE $a9,$aa,$ab,$ab,$ac,$ad,$ad,$ae,$af,$b0,$b0,$b1,$b2,$b2,$b3,$b4 ; a2lo .BYTE $00,$8b,$15,$a0,$2a,$b5,$3f,$ca,$54,$df,$69,$f4,$7f,$09,$94,$1e .BYTE $a9,$33,$be,$48,$d3,$5d,$e8,$73,$fd,$88,$12,$9d,$27,$b2,$3c,$c7 .BYTE $51,$dc,$67,$f1,$7c,$06,$91,$1b,$a6,$30,$bb,$45,$d0,$5b,$e5,$70 .BYTE $fa,$85,$0f,$9a,$24,$af,$39,$c4,$4f,$d9,$64,$ee,$79,$03,$8e,$18 .BYTE $a3,$2e,$b8,$43,$cd,$58,$e2,$6d,$f7,$82,$0c,$97,$22,$ac,$37,$c1 .BYTE $4c,$d6,$61,$eb,$76,$00,$8b,$16,$a0,$2b,$b5,$40,$ca,$55,$df,$6a .BYTE $f4,$7f,$0a,$94,$1f,$a9,$34,$be,$49,$d3,$5e,$e8,$73,$fe,$88,$13 .BYTE $9d,$28,$b2,$3d,$c7,$52,$dc,$67,$f2,$7c,$07,$91,$1c,$a6,$31,$bb .BYTE $46,$d0,$5b,$e6,$70,$fb,$85,$10,$9a,$25,$af,$3a,$c4,$4f,$da,$64 .BYTE $ef,$79,$04,$8e,$19,$a3,$2e,$b8,$43,$ce,$58,$e3,$6d,$f8,$82,$0d .BYTE $97,$22,$ac,$37,$c2,$4c,$d7,$61,$ec,$76,$01,$8b,$16,$a0,$2b,$b6 .BYTE $40,$cb,$55,$e0,$6a,$f5,$7f,$0a,$95,$1f,$aa,$34,$bf,$49,$d4,$5e .BYTE $e9,$73,$fe,$89,$13,$9e,$28,$b3,$3d,$c8,$52,$dd,$67,$f2,$7d,$07 .BYTE $92,$1c,$a7,$31,$bc,$46,$d1,$5b,$e6,$71,$fb,$86,$10,$9b,$25,$b0 .BYTE $3a,$c5,$4f,$da,$65,$ef,$7a,$04,$8f,$19,$a4,$2e,$b9,$43,$ce,$59 .BYTE $e3,$6e,$f8,$83,$0d,$98,$22,$ad,$37,$c2,$4d,$d7,$62,$ec,$77,$01 ; a2hi .BYTE $00,$00,$01,$01,$02,$02,$03,$03,$04,$04,$05,$05,$06,$07,$07,$08 .BYTE $08,$09,$09,$0a,$0a,$0b,$0b,$0c,$0c,$0d,$0e,$0e,$0f,$0f,$10,$10 .BYTE $11,$11,$12,$12,$13,$14,$14,$15,$15,$16,$16,$17,$17,$18,$18,$19 .BYTE $19,$1a,$1b,$1b,$1c,$1c,$1d,$1d,$1e,$1e,$1f,$1f,$20,$21,$21,$22 .BYTE $22,$23,$23,$24,$24,$25,$25,$26,$26,$27,$28,$28,$29,$29,$2a,$2a .BYTE $2b,$2b,$2c,$2c,$2d,$2e,$2e,$2f,$2f,$30,$30,$31,$31,$32,$32,$33 .BYTE $33,$34,$35,$35,$36,$36,$37,$37,$38,$38,$39,$39,$3a,$3a,$3b,$3c .BYTE $3c,$3d,$3d,$3e,$3e,$3f,$3f,$40,$40,$41,$42,$42,$43,$43,$44,$44 .BYTE $45,$45,$46,$46,$47,$47,$48,$49,$49,$4a,$4a,$4b,$4b,$4c,$4c,$4d .BYTE $4d,$4e,$4f,$4f,$50,$50,$51,$51,$52,$52,$53,$53,$54,$54,$55,$56 .BYTE $56,$57,$57,$58,$58,$59,$59,$5a,$5a,$5b,$5c,$5c,$5d,$5d,$5e,$5e .BYTE $5f,$5f,$60,$60,$61,$61,$62,$63,$63,$64,$64,$65,$65,$66,$66,$67 .BYTE $67,$68,$68,$69,$6a,$6a,$6b,$6b,$6c,$6c,$6d,$6d,$6e,$6e,$6f,$70 .BYTE $70,$71,$71,$72,$72,$73,$73,$74,$74,$75,$75,$76,$77,$77,$78,$78 .BYTE $79,$79,$7a,$7a,$7b,$7b,$7c,$7d,$7d,$7e,$7e,$7f,$7f,$80,$80,$81 .BYTE $81,$82,$82,$83,$84,$84,$85,$85,$86,$86,$87,$87,$88,$88,$89,$8a ; a4lo .BYTE $00,$4e,$9d,$eb,$3a,$88,$d7,$25,$74,$c2,$11,$5f,$ae,$fc,$4b,$99 .BYTE $e8,$36,$85,$d3,$22,$70,$bf,$0d,$5c,$aa,$f8,$47,$95,$e4,$32,$81 .BYTE $cf,$1e,$6c,$bb,$09,$58,$a6,$f5,$43,$92,$e0,$2f,$7d,$cc,$1a,$69 .BYTE $b7,$06,$54,$a2,$f1,$3f,$8e,$dc,$2b,$79,$c8,$16,$65,$b3,$02,$50 .BYTE $9f,$ed,$3c,$8a,$d9,$27,$76,$c4,$13,$61,$b0,$fe,$4c,$9b,$e9,$38 .BYTE $86,$d5,$23,$72,$c0,$0f,$5d,$ac,$fa,$49,$97,$e6,$34,$83,$d1,$20 .BYTE $6e,$bd,$0b,$5a,$a8,$f6,$45,$93,$e2,$30,$7f,$cd,$1c,$6a,$b9,$07 .BYTE $56,$a4,$f3,$41,$90,$de,$2d,$7b,$ca,$18,$67,$b5,$04,$52,$a0,$ef .BYTE $3d,$8c,$da,$29,$77,$c6,$14,$63,$b1,$00,$4e,$9d,$eb,$3a,$88,$d7 .BYTE $25,$74,$c2,$11,$5f,$ae,$fc,$4a,$99,$e7,$36,$84,$d3,$21,$70,$be .BYTE $0d,$5b,$aa,$f8,$47,$95,$e4,$32,$81,$cf,$1e,$6c,$bb,$09,$58,$a6 .BYTE $f5,$43,$91,$e0,$2e,$7d,$cb,$1a,$68,$b7,$05,$54,$a2,$f1,$3f,$8e .BYTE $dc,$2b,$79,$c8,$16,$65,$b3,$02,$50,$9f,$ed,$3b,$8a,$d8,$27,$75 .BYTE $c4,$12,$61,$af,$fe,$4c,$9b,$e9,$38,$86,$d5,$23,$72,$c0,$0f,$5d .BYTE $ac,$fa,$49,$97,$e5,$34,$82,$d1,$1f,$6e,$bc,$0b,$59,$a8,$f6,$45 .BYTE $93,$e2,$30,$7f,$cd,$1c,$6a,$b9,$07,$56,$a4,$f3,$41,$8f,$de,$2c ; a4hi .BYTE $00,$01,$02,$03,$05,$06,$07,$09,$0a,$0b,$0d,$0e,$0f,$10,$12,$13 .BYTE $14,$16,$17,$18,$1a,$1b,$1c,$1e,$1f,$20,$21,$23,$24,$25,$27,$28 .BYTE $29,$2b,$2c,$2d,$2f,$30,$31,$32,$34,$35,$36,$38,$39,$3a,$3c,$3d .BYTE $3e,$40,$41,$42,$43,$45,$46,$47,$49,$4a,$4b,$4d,$4e,$4f,$51,$52 .BYTE $53,$54,$56,$57,$58,$5a,$5b,$5c,$5e,$5f,$60,$61,$63,$64,$65,$67 .BYTE $68,$69,$6b,$6c,$6d,$6f,$70,$71,$72,$74,$75,$76,$78,$79,$7a,$7c .BYTE $7d,$7e,$80,$81,$82,$83,$85,$86,$87,$89,$8a,$8b,$8d,$8e,$8f,$91 .BYTE $92,$93,$94,$96,$97,$98,$9a,$9b,$9c,$9e,$9f,$a0,$a2,$a3,$a4,$a5 .BYTE $a7,$a8,$a9,$ab,$ac,$ad,$af,$b0,$b1,$b3,$b4,$b5,$b6,$b8,$b9,$ba .BYTE $bc,$bd,$be,$c0,$c1,$c2,$c3,$c5,$c6,$c7,$c9,$ca,$cb,$cd,$ce,$cf .BYTE $d1,$d2,$d3,$d4,$d6,$d7,$d8,$da,$db,$dc,$de,$df,$e0,$e2,$e3,$e4 .BYTE $e5,$e7,$e8,$e9,$eb,$ec,$ed,$ef,$f0,$f1,$f3,$f4,$f5,$f6,$f8,$f9 .BYTE $fa,$fc,$fd,$fe,$00,$01,$02,$04,$05,$06,$07,$09,$0a,$0b,$0d,$0e .BYTE $0f,$11,$12,$13,$14,$16,$17,$18,$1a,$1b,$1c,$1e,$1f,$20,$22,$23 .BYTE $24,$25,$27,$28,$29,$2b,$2c,$2d,$2f,$30,$31,$33,$34,$35,$36,$38 .BYTE $39,$3a,$3c,$3d,$3e,$40,$41,$42,$44,$45,$46,$47,$49,$4a,$4b,$4d ; a4gh .BYTE $00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00 .BYTE $00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00 .BYTE $00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00 .BYTE $00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00 .BYTE $00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00 .BYTE $00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00 .BYTE $00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00 .BYTE $00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00 .BYTE $00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00 .BYTE $00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00 .BYTE $00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00 .BYTE $00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00 .BYTE $00,$00,$00,$00,$01,$01,$01,$01,$01,$01,$01,$01,$01,$01,$01,$01 .BYTE $01,$01,$01,$01,$01,$01,$01,$01,$01,$01,$01,$01,$01,$01,$01,$01 .BYTE $01,$01,$01,$01,$01,$01,$01,$01,$01,$01,$01,$01,$01,$01,$01,$01 .BYTE $01,$01,$01,$01,$01,$01,$01,$01,$01,$01,$01,$01,$01,$01,$01,$01 ; a5lo .BYTE $00,$62,$c4,$26,$88,$ea,$4c,$ae,$10,$72,$d4,$36,$98,$fa,$5c,$be .BYTE $1f,$81,$e3,$45,$a7,$09,$6b,$cd,$2f,$91,$f3,$55,$b7,$19,$7b,$dd .BYTE $3f,$a1,$03,$65,$c7,$29,$8b,$ed,$4f,$b1,$13,$75,$d7,$39,$9a,$fc .BYTE $5e,$c0,$22,$84,$e6,$48,$aa,$0c,$6e,$d0,$32,$94,$f6,$58,$ba,$1c .BYTE $7e,$e0,$42,$a4,$06,$68,$ca,$2c,$8e,$f0,$52,$b4,$15,$77,$d9,$3b .BYTE $9d,$ff,$61,$c3,$25,$87,$e9,$4b,$ad,$0f,$71,$d3,$35,$97,$f9,$5b .BYTE $bd,$1f,$81,$e3,$45,$a7,$09,$6b,$cd,$2f,$90,$f2,$54,$b6,$18,$7a .BYTE $dc,$3e,$a0,$02,$64,$c6,$28,$8a,$ec,$4e,$b0,$12,$74,$d6,$38,$9a .BYTE $fc,$5e,$c0,$22,$84,$e6,$48,$aa,$0c,$6d,$cf,$31,$93,$f5,$57,$b9 .BYTE $1b,$7d,$df,$41,$a3,$05,$67,$c9,$2b,$8d,$ef,$51,$b3,$15,$77,$d9 .BYTE $3b,$9d,$ff,$61,$c3,$25,$87,$e8,$4a,$ac,$0e,$70,$d2,$34,$96,$f8 .BYTE $5a,$bc,$1e,$80,$e2,$44,$a6,$08,$6a,$cc,$2e,$90,$f2,$54,$b6,$18 .BYTE $7a,$dc,$3e,$a0,$02,$63,$c5,$27,$89,$eb,$4d,$af,$11,$73,$d5,$37 .BYTE $99,$fb,$5d,$bf,$21,$83,$e5,$47,$a9,$0b,$6d,$cf,$31,$93,$f5,$57 .BYTE $b9,$1b,$7d,$de,$40,$a2,$04,$66,$c8,$2a,$8c,$ee,$50,$b2,$14,$76 .BYTE $d8,$3a,$9c,$fe,$60,$c2,$24,$86,$e8,$4a,$ac,$0e,$70,$d2,$34,$96 ; a5hi .BYTE $00,$00,$00,$01,$01,$01,$02,$02,$03,$03,$03,$04,$04,$04,$05,$05 .BYTE $06,$06,$06,$07,$07,$08,$08,$08,$09,$09,$09,$0a,$0a,$0b,$0b,$0b .BYTE $0c,$0c,$0d,$0d,$0d,$0e,$0e,$0e,$0f,$0f,$10,$10,$10,$11,$11,$11 .BYTE $12,$12,$13,$13,$13,$14,$14,$15,$15,$15,$16,$16,$16,$17,$17,$18 .BYTE $18,$18,$19,$19,$1a,$1a,$1a,$1b,$1b,$1b,$1c,$1c,$1d,$1d,$1d,$1e .BYTE $1e,$1e,$1f,$1f,$20,$20,$20,$21,$21,$22,$22,$22,$23,$23,$23,$24 .BYTE $24,$25,$25,$25,$26,$26,$27,$27,$27,$28,$28,$28,$29,$29,$2a,$2a .BYTE $2a,$2b,$2b,$2c,$2c,$2c,$2d,$2d,$2d,$2e,$2e,$2f,$2f,$2f,$30,$30 .BYTE $30,$31,$31,$32,$32,$32,$33,$33,$34,$34,$34,$35,$35,$35,$36,$36 .BYTE $37,$37,$37,$38,$38,$39,$39,$39,$3a,$3a,$3a,$3b,$3b,$3c,$3c,$3c .BYTE $3d,$3d,$3d,$3e,$3e,$3f,$3f,$3f,$40,$40,$41,$41,$41,$42,$42,$42 .BYTE $43,$43,$44,$44,$44,$45,$45,$46,$46,$46,$47,$47,$47,$48,$48,$49 .BYTE $49,$49,$4a,$4a,$4b,$4b,$4b,$4c,$4c,$4c,$4d,$4d,$4e,$4e,$4e,$4f .BYTE $4f,$4f,$50,$50,$51,$51,$51,$52,$52,$53,$53,$53,$54,$54,$54,$55 .BYTE $55,$56,$56,$56,$57,$57,$58,$58,$58,$59,$59,$59,$5a,$5a,$5b,$5b .BYTE $5b,$5c,$5c,$5c,$5d,$5d,$5e,$5e,$5e,$5f,$5f,$60,$60,$60,$61,$61 ; sec1 .BYTE $00,$00,$01,$00,$01,$00,$02,$00,$02,$00,$03,$00,$03,$00,$04,$00 .BYTE $04,$00,$05,$00,$05,$00,$06,$00,$06,$00,$07,$00,$07,$00,$08,$00 .BYTE $08,$00,$09,$00,$09,$00,$0a,$00,$0a,$00,$0b,$00,$0b,$00,$0c,$00 .BYTE $0c,$00,$0d,$00,$0d,$00,$0e,$00,$0e,$00,$0f,$00,$0f,$00,$10,$00 .BYTE $10,$00,$11,$00,$11,$00,$12,$00,$12,$00,$13,$00,$13,$00,$14,$00 .BYTE $14,$00,$15,$00,$15,$00,$16,$00,$16,$00,$17,$00,$17,$00,$18,$00 .BYTE $18,$00,$19,$00,$19,$00,$1a,$00,$1b,$00,$1b,$00,$1c,$00,$1c,$00 .BYTE $1d,$00,$1d,$00,$1e,$00,$1e,$00,$1f,$00,$1f,$00,$20,$00,$20,$00 .BYTE $21,$00,$21,$00,$22,$00,$22,$00,$23,$00,$23,$00,$24,$00,$24,$00 .BYTE $25,$00,$25,$00,$26,$00,$26,$00,$27,$00,$27,$00,$28,$00,$28,$00 .BYTE $29,$00,$29,$00,$2a,$00,$2a,$00,$2b,$00,$2b,$00,$2c,$00,$2c,$00 .BYTE $2d,$00,$2d,$00,$2e,$00,$2e,$00,$2f,$00,$2f,$00,$30,$00,$30,$00 .BYTE $31,$00,$31,$00,$32,$00,$32,$00,$33,$00,$33,$00,$34,$00,$35,$00 .BYTE $35,$00,$36,$00,$36,$00,$37,$00,$37,$00,$38,$00,$38,$00,$39,$00 .BYTE $39,$00,$3a,$00,$3a,$00,$3b,$00,$3b,$00,$3c,$00,$3c,$00,$3d,$00 .BYTE $3d,$00,$3e,$00,$3e,$00,$3f,$00,$3f,$00,$40,$00,$40,$00,$41,$00 .BYTE $41,$00,$42,$00,$42,$00,$43,$00,$43,$00,$44,$00,$44,$00,$45,$00 .BYTE $45,$00,$46,$00,$46,$00,$47,$00,$47,$00,$48,$00,$48,$00,$49,$00 .BYTE $49,$00,$4a,$00,$4a,$00,$4b,$00,$4b,$00,$4c,$00,$4c,$00,$4d,$00 .BYTE $4d,$00,$4e,$00,$4f,$00,$4f,$00,$50,$00,$50,$00,$51,$00,$51,$00 .BYTE $52,$00,$52,$00,$53,$00,$53,$00,$54,$00,$54,$00,$55,$00,$55,$00 .BYTE $56,$00,$56,$00,$57,$00,$57,$00,$58,$00,$58,$00,$59,$00,$59,$00 .BYTE $5a,$00,$5a,$00,$5b,$00,$5b,$00,$5c,$00,$5c,$00,$5d,$00,$5d,$00 .BYTE $5e,$00,$5e,$00,$5f,$00,$5f,$00,$60,$00,$60,$00,$61,$00,$61,$00 .BYTE $62,$00,$62,$00,$63,$00,$63,$00,$64,$00,$64,$00,$65,$00,$65,$00 .BYTE $66,$00,$66,$00,$67,$00,$67,$00,$68,$00,$69,$00,$69,$00,$6a,$00 .BYTE $6a,$00,$6b,$00,$6b,$00,$6c,$00,$6c,$00,$6d,$00,$6d,$00,$6e,$00 .BYTE $6e,$00,$6f,$00,$6f,$00,$70,$00,$70,$00,$71,$00,$71,$00,$72,$00 .BYTE $72,$00,$73,$00,$73,$00,$74,$00,$74,$00,$75,$00,$75,$00,$76,$00 .BYTE $76,$00,$77,$00,$77,$00,$78,$00,$78,$00,$79,$00,$79,$00,$7a,$00 .BYTE $7a,$00,$7b,$00,$7b,$00,$7c,$00,$7c,$00,$7d,$00,$7d,$00,$7e,$00 .BYTE $7e,$00,$7f,$00,$7f,$00,$80,$00,$80,$00,$81,$00,$81,$00,$82,$00 ; sec2 .BYTE $00,$00,$01,$00,$01,$00,$02,$00,$02,$00,$03,$00,$03,$00,$04,$00 .BYTE $04,$00,$05,$00,$05,$00,$06,$00,$06,$00,$07,$00,$08,$00,$08,$00 .BYTE $09,$00,$09,$00,$0a,$00,$0a,$00,$0b,$00,$0b,$00,$0c,$00,$0c,$00 .BYTE $0d,$00,$0e,$00,$0e,$00,$0f,$00,$0f,$00,$10,$00,$10,$00,$11,$00 .BYTE $11,$00,$12,$00,$12,$00,$13,$00,$13,$00,$14,$00,$15,$00,$15,$00 .BYTE $16,$00,$16,$00,$17,$00,$17,$00,$18,$00,$18,$00,$19,$00,$19,$00 .BYTE $1a,$00,$1b,$00,$1b,$00,$1c,$00,$1c,$00,$1d,$00,$1d,$00,$1e,$00 .BYTE $1e,$00,$1f,$00,$1f,$00,$20,$00,$20,$00,$21,$00,$22,$00,$22,$00 .BYTE $23,$00,$23,$00,$24,$00,$24,$00,$25,$00,$25,$00,$26,$00,$26,$00 .BYTE $27,$00,$28,$00,$28,$00,$29,$00,$29,$00,$2a,$00,$2a,$00,$2b,$00 .BYTE $2b,$00,$2c,$00,$2c,$00,$2d,$00,$2d,$00,$2e,$00,$2f,$00,$2f,$00 .BYTE $30,$00,$30,$00,$31,$00,$31,$00,$32,$00,$32,$00,$33,$00,$33,$00 .BYTE $34,$00,$34,$00,$35,$00,$36,$00,$36,$00,$37,$00,$37,$00,$38,$00 .BYTE $38,$00,$39,$00,$39,$00,$3a,$00,$3a,$00,$3b,$00,$3c,$00,$3c,$00 .BYTE $3d,$00,$3d,$00,$3e,$00,$3e,$00,$3f,$00,$3f,$00,$40,$00,$40,$00 .BYTE $41,$00,$41,$00,$42,$00,$43,$00,$43,$00,$44,$00,$44,$00,$45,$00 .BYTE $45,$00,$46,$00,$46,$00,$47,$00,$47,$00,$48,$00,$49,$00,$49,$00 .BYTE $4a,$00,$4a,$00,$4b,$00,$4b,$00,$4c,$00,$4c,$00,$4d,$00,$4d,$00 .BYTE $4e,$00,$4e,$00,$4f,$00,$50,$00,$50,$00,$51,$00,$51,$00,$52,$00 .BYTE $52,$00,$53,$00,$53,$00,$54,$00,$54,$00,$55,$00,$56,$00,$56,$00 .BYTE $57,$00,$57,$00,$58,$00,$58,$00,$59,$00,$59,$00,$5a,$00,$5a,$00 .BYTE $5b,$00,$5b,$00,$5c,$00,$5d,$00,$5d,$00,$5e,$00,$5e,$00,$5f,$00 .BYTE $5f,$00,$60,$00,$60,$00,$61,$00,$61,$00,$62,$00,$62,$00,$63,$00 .BYTE $64,$00,$64,$00,$65,$00,$65,$00,$66,$00,$66,$00,$67,$00,$67,$00 .BYTE $68,$00,$68,$00,$69,$00,$6a,$00,$6a,$00,$6b,$00,$6b,$00,$6c,$00 .BYTE $6c,$00,$6d,$00,$6d,$00,$6e,$00,$6e,$00,$6f,$00,$6f,$00,$70,$00 .BYTE $71,$00,$71,$00,$72,$00,$72,$00,$73,$00,$73,$00,$74,$00,$74,$00 .BYTE $75,$00,$75,$00,$76,$00,$77,$00,$77,$00,$78,$00,$78,$00,$79,$00 .BYTE $79,$00,$7a,$00,$7a,$00,$7b,$00,$7b,$00,$7c,$00,$7c,$00,$7d,$00 .BYTE $7e,$00,$7e,$00,$7f,$00,$7f,$00,$80,$00,$80,$00,$81,$00,$81,$00 .BYTE $82,$00,$82,$00,$83,$00,$84,$00,$84,$00,$85,$00,$85,$00,$86,$00 .BYTE $86,$00,$87,$00,$87,$00,$88,$00,$88,$00,$89,$00,$89,$00,$8a,$00 ; sec3 .BYTE $00,$00,$01,$00,$01,$00,$02,$00,$02,$00,$03,$00,$04,$00,$04,$00 .BYTE $05,$00,$05,$00,$06,$00,$07,$00,$07,$00,$08,$00,$08,$00,$09,$00 .BYTE $0a,$00,$0a,$00,$0b,$00,$0b,$00,$0c,$00,$0d,$00,$0d,$00,$0e,$00 .BYTE $0e,$00,$0f,$00,$10,$00,$10,$00,$11,$00,$11,$00,$12,$00,$13,$00 .BYTE $13,$00,$14,$00,$14,$00,$15,$00,$16,$00,$16,$00,$17,$00,$17,$00 .BYTE $18,$00,$19,$00,$19,$00,$1a,$00,$1a,$00,$1b,$00,$1c,$00,$1c,$00 .BYTE $1d,$00,$1d,$00,$1e,$00,$1f,$00,$1f,$00,$20,$00,$20,$00,$21,$00 .BYTE $22,$00,$22,$00,$23,$00,$23,$00,$24,$00,$25,$00,$25,$00,$26,$00 .BYTE $26,$00,$27,$00,$28,$00,$28,$00,$29,$00,$29,$00,$2a,$00,$2b,$00 .BYTE $2b,$00,$2c,$00,$2c,$00,$2d,$00,$2e,$00,$2e,$00,$2f,$00,$30,$00 .BYTE $30,$00,$31,$00,$31,$00,$32,$00,$33,$00,$33,$00,$34,$00,$34,$00 .BYTE $35,$00,$36,$00,$36,$00,$37,$00,$37,$00,$38,$00,$39,$00,$39,$00 .BYTE $3a,$00,$3a,$00,$3b,$00,$3c,$00,$3c,$00,$3d,$00,$3d,$00,$3e,$00 .BYTE $3f,$00,$3f,$00,$40,$00,$40,$00,$41,$00,$42,$00,$42,$00,$43,$00 .BYTE $43,$00,$44,$00,$45,$00,$45,$00,$46,$00,$46,$00,$47,$00,$48,$00 .BYTE $48,$00,$49,$00,$49,$00,$4a,$00,$4b,$00,$4b,$00,$4c,$00,$4c,$00 .BYTE $4d,$00,$4e,$00,$4e,$00,$4f,$00,$4f,$00,$50,$00,$51,$00,$51,$00 .BYTE $52,$00,$52,$00,$53,$00,$54,$00,$54,$00,$55,$00,$55,$00,$56,$00 .BYTE $57,$00,$57,$00,$58,$00,$58,$00,$59,$00,$5a,$00,$5a,$00,$5b,$00 .BYTE $5b,$00,$5c,$00,$5d,$00,$5d,$00,$5e,$00,$5e,$00,$5f,$00,$60,$00 .BYTE $60,$00,$61,$00,$61,$00,$62,$00,$63,$00,$63,$00,$64,$00,$64,$00 .BYTE $65,$00,$66,$00,$66,$00,$67,$00,$67,$00,$68,$00,$69,$00,$69,$00 .BYTE $6a,$00,$6a,$00,$6b,$00,$6c,$00,$6c,$00,$6d,$00,$6d,$00,$6e,$00 .BYTE $6f,$00,$6f,$00,$70,$00,$70,$00,$71,$00,$72,$00,$72,$00,$73,$00 .BYTE $73,$00,$74,$00,$75,$00,$75,$00,$76,$00,$76,$00,$77,$00,$78,$00 .BYTE $78,$00,$79,$00,$79,$00,$7a,$00,$7b,$00,$7b,$00,$7c,$00,$7c,$00 .BYTE $7d,$00,$7e,$00,$7e,$00,$7f,$00,$7f,$00,$80,$00,$81,$00,$81,$00 .BYTE $82,$00,$82,$00,$83,$00,$84,$00,$84,$00,$85,$00,$85,$00,$86,$00 .BYTE $87,$00,$87,$00,$88,$00,$89,$00,$89,$00,$8a,$00,$8a,$00,$8b,$00 .BYTE $8c,$00,$8c,$00,$8d,$00,$8d,$00,$8e,$00,$8f,$00,$8f,$00,$90,$00 .BYTE $90,$00,$91,$00,$92,$00,$92,$00,$93,$00,$93,$00,$94,$00,$95,$00 .BYTE $95,$00,$96,$00,$96,$00,$97,$00,$98,$00,$98,$00,$99,$00,$99,$00 ; sec4 .BYTE $00,$00,$01,$00,$01,$00,$02,$00,$03,$00,$04,$00,$04,$00,$05,$00 .BYTE $06,$00,$06,$00,$07,$00,$08,$00,$08,$00,$09,$00,$0a,$00,$0b,$00 .BYTE $0b,$00,$0c,$00,$0d,$00,$0d,$00,$0e,$00,$0f,$00,$10,$00,$10,$00 .BYTE $11,$00,$12,$00,$12,$00,$13,$00,$14,$00,$15,$00,$15,$00,$16,$00 .BYTE $17,$00,$17,$00,$18,$00,$19,$00,$19,$00,$1a,$00,$1b,$00,$1c,$00 .BYTE $1c,$00,$1d,$00,$1e,$00,$1e,$00,$1f,$00,$20,$00,$21,$00,$21,$00 .BYTE $22,$00,$23,$00,$23,$00,$24,$00,$25,$00,$25,$00,$26,$00,$27,$00 .BYTE $28,$00,$28,$00,$29,$00,$2a,$00,$2a,$00,$2b,$00,$2c,$00,$2d,$00 .BYTE $2d,$00,$2e,$00,$2f,$00,$2f,$00,$30,$00,$31,$00,$31,$00,$32,$00 .BYTE $33,$00,$34,$00,$34,$00,$35,$00,$36,$00,$36,$00,$37,$00,$38,$00 .BYTE $39,$00,$39,$00,$3a,$00,$3b,$00,$3b,$00,$3c,$00,$3d,$00,$3e,$00 .BYTE $3e,$00,$3f,$00,$40,$00,$40,$00,$41,$00,$42,$00,$42,$00,$43,$00 .BYTE $44,$00,$45,$00,$45,$00,$46,$00,$47,$00,$47,$00,$48,$00,$49,$00 .BYTE $4a,$00,$4a,$00,$4b,$00,$4c,$00,$4c,$00,$4d,$00,$4e,$00,$4e,$00 .BYTE $4f,$00,$50,$00,$51,$00,$51,$00,$52,$00,$53,$00,$53,$00,$54,$00 .BYTE $55,$00,$56,$00,$56,$00,$57,$00,$58,$00,$58,$00,$59,$00,$5a,$00 .BYTE $5b,$00,$5b,$00,$5c,$00,$5d,$00,$5d,$00,$5e,$00,$5f,$00,$5f,$00 .BYTE $60,$00,$61,$00,$62,$00,$62,$00,$63,$00,$64,$00,$64,$00,$65,$00 .BYTE $66,$00,$67,$00,$67,$00,$68,$00,$69,$00,$69,$00,$6a,$00,$6b,$00 .BYTE $6b,$00,$6c,$00,$6d,$00,$6e,$00,$6e,$00,$6f,$00,$70,$00,$70,$00 .BYTE $71,$00,$72,$00,$73,$00,$73,$00,$74,$00,$75,$00,$75,$00,$76,$00 .BYTE $77,$00,$78,$00,$78,$00,$79,$00,$7a,$00,$7a,$00,$7b,$00,$7c,$00 .BYTE $7c,$00,$7d,$00,$7e,$00,$7f,$00,$7f,$00,$80,$00,$81,$00,$81,$00 .BYTE $82,$00,$83,$00,$84,$00,$84,$00,$85,$00,$86,$00,$86,$00,$87,$00 .BYTE $88,$00,$88,$00,$89,$00,$8a,$00,$8b,$00,$8b,$00,$8c,$00,$8d,$00 .BYTE $8d,$00,$8e,$00,$8f,$00,$90,$00,$90,$00,$91,$00,$92,$00,$92,$00 .BYTE $93,$00,$94,$00,$94,$00,$95,$00,$96,$00,$97,$00,$97,$00,$98,$00 .BYTE $99,$00,$99,$00,$9a,$00,$9b,$00,$9c,$00,$9c,$00,$9d,$00,$9e,$00 .BYTE $9e,$00,$9f,$00,$a0,$00,$a1,$00,$a1,$00,$a2,$00,$a3,$00,$a3,$00 .BYTE $a4,$00,$a5,$00,$a5,$00,$a6,$00,$a7,$00,$a8,$00,$a8,$00,$a9,$00 .BYTE $aa,$00,$aa,$00,$ab,$00,$ac,$00,$ad,$00,$ad,$00,$ae,$00,$af,$00 .BYTE $af,$00,$b0,$00,$b1,$00,$b1,$00,$b2,$00,$b3,$00,$b4,$00,$b4,$00 ; sec5 .BYTE $00,$00,$01,$00,$02,$00,$03,$00,$04,$00,$04,$00,$05,$00,$06,$00 .BYTE $07,$00,$08,$00,$09,$00,$0a,$00,$0b,$00,$0c,$00,$0d,$00,$0d,$00 .BYTE $0e,$00,$0f,$00,$10,$00,$11,$00,$12,$00,$13,$00,$14,$00,$15,$00 .BYTE $16,$00,$16,$00,$17,$00,$18,$00,$19,$00,$1a,$00,$1b,$00,$1c,$00 .BYTE $1d,$00,$1e,$00,$1f,$00,$1f,$00,$20,$00,$21,$00,$22,$00,$23,$00 .BYTE $24,$00,$25,$00,$26,$00,$27,$00,$28,$00,$28,$00,$29,$00,$2a,$00 .BYTE $2b,$00,$2c,$00,$2d,$00,$2e,$00,$2f,$00,$30,$00,$31,$00,$31,$00 .BYTE $32,$00,$33,$00,$34,$00,$35,$00,$36,$00,$37,$00,$38,$00,$39,$00 .BYTE $3a,$00,$3a,$00,$3b,$00,$3c,$00,$3d,$00,$3e,$00,$3f,$00,$40,$00 .BYTE $41,$00,$42,$00,$43,$00,$43,$00,$44,$00,$45,$00,$46,$00,$47,$00 .BYTE $48,$00,$49,$00,$4a,$00,$4b,$00,$4c,$00,$4c,$00,$4d,$00,$4e,$00 .BYTE $4f,$00,$50,$00,$51,$00,$52,$00,$53,$00,$54,$00,$55,$00,$55,$00 .BYTE $56,$00,$57,$00,$58,$00,$59,$00,$5a,$00,$5b,$00,$5c,$00,$5d,$00 .BYTE $5e,$00,$5e,$00,$5f,$00,$60,$00,$61,$00,$62,$00,$63,$00,$64,$00 .BYTE $65,$00,$66,$00,$67,$00,$67,$00,$68,$00,$69,$00,$6a,$00,$6b,$00 .BYTE $6c,$00,$6d,$00,$6e,$00,$6f,$00,$70,$00,$70,$00,$71,$00,$72,$00 .BYTE $73,$00,$74,$00,$75,$00,$76,$00,$77,$00,$78,$00,$79,$00,$79,$00 .BYTE $7a,$00,$7b,$00,$7c,$00,$7d,$00,$7e,$00,$7f,$00,$80,$00,$81,$00 .BYTE $82,$00,$82,$00,$83,$00,$84,$00,$85,$00,$86,$00,$87,$00,$88,$00 .BYTE $89,$00,$8a,$00,$8b,$00,$8b,$00,$8c,$00,$8d,$00,$8e,$00,$8f,$00 .BYTE $90,$00,$91,$00,$92,$00,$93,$00,$94,$00,$94,$00,$95,$00,$96,$00 .BYTE $97,$00,$98,$00,$99,$00,$9a,$00,$9b,$00,$9c,$00,$9d,$00,$9d,$00 .BYTE $9e,$00,$9f,$00,$a0,$00,$a1,$00,$a2,$00,$a3,$00,$a4,$00,$a5,$00 .BYTE $a6,$00,$a6,$00,$a7,$00,$a8,$00,$a9,$00,$aa,$00,$ab,$00,$ac,$00 .BYTE $ad,$00,$ae,$00,$af,$00,$af,$00,$b0,$00,$b1,$00,$b2,$00,$b3,$00 .BYTE $b4,$00,$b5,$00,$b6,$00,$b7,$00,$b8,$00,$b8,$00,$b9,$00,$ba,$00 .BYTE $bb,$00,$bc,$00,$bd,$00,$be,$00,$bf,$00,$c0,$00,$c1,$00,$c1,$00 .BYTE $c2,$00,$c3,$00,$c4,$00,$c5,$00,$c6,$00,$c7,$00,$c8,$00,$c9,$00 .BYTE $ca,$00,$ca,$00,$cb,$00,$cc,$00,$cd,$00,$ce,$00,$cf,$00,$d0,$00 .BYTE $d1,$00,$d2,$00,$d3,$00,$d3,$00,$d4,$00,$d5,$00,$d6,$00,$d7,$00 .BYTE $d8,$00,$d9,$00,$da,$00,$db,$00,$dc,$00,$dc,$00,$dd,$00,$de,$00 .BYTE $df,$00,$e0,$00,$e1,$00,$e2,$00,$e3,$00,$e4,$00,$e5,$00,$e5,$00 ; sec6 .BYTE $00,$00,$01,$00,$03,$00,$04,$00,$05,$00,$07,$00,$08,$00,$09,$00 .BYTE $0a,$00,$0c,$00,$0d,$00,$0e,$00,$10,$00,$11,$00,$12,$00,$14,$00 .BYTE $15,$00,$16,$00,$18,$00,$19,$00,$1a,$00,$1b,$00,$1d,$00,$1e,$00 .BYTE $1f,$00,$21,$00,$22,$00,$23,$00,$25,$00,$26,$00,$27,$00,$29,$00 .BYTE $2a,$00,$2b,$00,$2c,$00,$2e,$00,$2f,$00,$30,$00,$32,$00,$33,$00 .BYTE $34,$00,$36,$00,$37,$00,$38,$00,$39,$00,$3b,$00,$3c,$00,$3d,$00 .BYTE $3f,$00,$40,$00,$41,$00,$43,$00,$44,$00,$45,$00,$47,$00,$48,$00 .BYTE $49,$00,$4a,$00,$4c,$00,$4d,$00,$4e,$00,$50,$00,$51,$00,$52,$00 .BYTE $54,$00,$55,$00,$56,$00,$58,$00,$59,$00,$5a,$00,$5b,$00,$5d,$00 .BYTE $5e,$00,$5f,$00,$61,$00,$62,$00,$63,$00,$65,$00,$66,$00,$67,$00 .BYTE $69,$00,$6a,$00,$6b,$00,$6c,$00,$6e,$00,$6f,$00,$70,$00,$72,$00 .BYTE $73,$00,$74,$00,$76,$00,$77,$00,$78,$00,$7a,$00,$7b,$00,$7c,$00 .BYTE $7d,$00,$7f,$00,$80,$00,$81,$00,$83,$00,$84,$00,$85,$00,$87,$00 .BYTE $88,$00,$89,$00,$8a,$00,$8c,$00,$8d,$00,$8e,$00,$90,$00,$91,$00 .BYTE $92,$00,$94,$00,$95,$00,$96,$00,$98,$00,$99,$00,$9a,$00,$9b,$00 .BYTE $9d,$00,$9e,$00,$9f,$00,$a1,$00,$a2,$00,$a3,$00,$a5,$00,$a6,$00 .BYTE $a7,$00,$a9,$00,$aa,$00,$ab,$00,$ac,$00,$ae,$00,$af,$00,$b0,$00 .BYTE $b2,$00,$b3,$00,$b4,$00,$b6,$00,$b7,$00,$b8,$00,$ba,$00,$bb,$00 .BYTE $bc,$00,$bd,$00,$bf,$00,$c0,$00,$c1,$00,$c3,$00,$c4,$00,$c5,$00 .BYTE $c7,$00,$c8,$00,$c9,$00,$cb,$00,$cc,$00,$cd,$00,$ce,$00,$d0,$00 .BYTE $d1,$00,$d2,$00,$d4,$00,$d5,$00,$d6,$00,$d8,$00,$d9,$00,$da,$00 .BYTE $dc,$00,$dd,$00,$de,$00,$df,$00,$e1,$00,$e2,$00,$e3,$00,$e5,$00 .BYTE $e6,$00,$e7,$00,$e9,$00,$ea,$00,$eb,$00,$ec,$00,$ee,$00,$ef,$00 .BYTE $f0,$00,$f2,$00,$f3,$00,$f4,$00,$f6,$00,$f7,$00,$f8,$00,$fa,$00 .BYTE $fb,$00,$fc,$00,$fd,$00,$ff,$00,$00,$01,$01,$01,$03,$01,$04,$01 .BYTE $05,$01,$07,$01,$08,$01,$09,$01,$0b,$01,$0c,$01,$0d,$01,$0e,$01 .BYTE $10,$01,$11,$01,$12,$01,$14,$01,$15,$01,$16,$01,$18,$01,$19,$01 .BYTE $1a,$01,$1c,$01,$1d,$01,$1e,$01,$1f,$01,$21,$01,$22,$01,$23,$01 .BYTE $25,$01,$26,$01,$27,$01,$29,$01,$2a,$01,$2b,$01,$2d,$01,$2e,$01 .BYTE $2f,$01,$30,$01,$32,$01,$33,$01,$34,$01,$36,$01,$37,$01,$38,$01 .BYTE $3a,$01,$3b,$01,$3c,$01,$3d,$01,$3f,$01,$40,$01,$41,$01,$43,$01 .BYTE $44,$01,$45,$01,$47,$01,$48,$01,$49,$01,$4b,$01,$4c,$01,$4d,$01 ; sec7 .BYTE $00,$00,$03,$00,$05,$00,$08,$00,$0a,$00,$0d,$00,$0f,$00,$12,$00 .BYTE $15,$00,$17,$00,$1a,$00,$1c,$00,$1f,$00,$21,$00,$24,$00,$26,$00 .BYTE $29,$00,$2c,$00,$2e,$00,$31,$00,$33,$00,$36,$00,$38,$00,$3b,$00 .BYTE $3e,$00,$40,$00,$43,$00,$45,$00,$48,$00,$4a,$00,$4d,$00,$4f,$00 .BYTE $52,$00,$55,$00,$57,$00,$5a,$00,$5c,$00,$5f,$00,$61,$00,$64,$00 .BYTE $67,$00,$69,$00,$6c,$00,$6e,$00,$71,$00,$73,$00,$76,$00,$78,$00 .BYTE $7b,$00,$7e,$00,$80,$00,$83,$00,$85,$00,$88,$00,$8a,$00,$8d,$00 .BYTE $90,$00,$92,$00,$95,$00,$97,$00,$9a,$00,$9c,$00,$9f,$00,$a1,$00 .BYTE $a4,$00,$a7,$00,$a9,$00,$ac,$00,$ae,$00,$b1,$00,$b3,$00,$b6,$00 .BYTE $b9,$00,$bb,$00,$be,$00,$c0,$00,$c3,$00,$c5,$00,$c8,$00,$ca,$00 .BYTE $cd,$00,$d0,$00,$d2,$00,$d5,$00,$d7,$00,$da,$00,$dc,$00,$df,$00 .BYTE $e2,$00,$e4,$00,$e7,$00,$e9,$00,$ec,$00,$ee,$00,$f1,$00,$f3,$00 .BYTE $f6,$00,$f9,$00,$fb,$00,$fe,$00,$00,$01,$03,$01,$05,$01,$08,$01 .BYTE $0b,$01,$0d,$01,$10,$01,$12,$01,$15,$01,$17,$01,$1a,$01,$1c,$01 .BYTE $1f,$01,$22,$01,$24,$01,$27,$01,$29,$01,$2c,$01,$2e,$01,$31,$01 .BYTE $34,$01,$36,$01,$39,$01,$3b,$01,$3e,$01,$40,$01,$43,$01,$45,$01 .BYTE $48,$01,$4b,$01,$4d,$01,$50,$01,$52,$01,$55,$01,$57,$01,$5a,$01 .BYTE $5d,$01,$5f,$01,$62,$01,$64,$01,$67,$01,$69,$01,$6c,$01,$6e,$01 .BYTE $71,$01,$74,$01,$76,$01,$79,$01,$7b,$01,$7e,$01,$80,$01,$83,$01 .BYTE $86,$01,$88,$01,$8b,$01,$8d,$01,$90,$01,$92,$01,$95,$01,$98,$01 .BYTE $9a,$01,$9d,$01,$9f,$01,$a2,$01,$a4,$01,$a7,$01,$a9,$01,$ac,$01 .BYTE $af,$01,$b1,$01,$b4,$01,$b6,$01,$b9,$01,$bb,$01,$be,$01,$c1,$01 .BYTE $c3,$01,$c6,$01,$c8,$01,$cb,$01,$cd,$01,$d0,$01,$d2,$01,$d5,$01 .BYTE $d8,$01,$da,$01,$dd,$01,$df,$01,$e2,$01,$e4,$01,$e7,$01,$ea,$01 .BYTE $ec,$01,$ef,$01,$f1,$01,$f4,$01,$f6,$01,$f9,$01,$fb,$01,$fe,$01 .BYTE $01,$02,$03,$02,$06,$02,$08,$02,$0b,$02,$0d,$02,$10,$02,$13,$02 .BYTE $15,$02,$18,$02,$1a,$02,$1d,$02,$1f,$02,$22,$02,$24,$02,$27,$02 .BYTE $2a,$02,$2c,$02,$2f,$02,$31,$02,$34,$02,$36,$02,$39,$02,$3c,$02 .BYTE $3e,$02,$41,$02,$43,$02,$46,$02,$48,$02,$4b,$02,$4d,$02,$50,$02 .BYTE $53,$02,$55,$02,$58,$02,$5a,$02,$5d,$02,$5f,$02,$62,$02,$65,$02 .BYTE $67,$02,$6a,$02,$6c,$02,$6f,$02,$71,$02,$74,$02,$76,$02,$79,$02 .BYTE $7c,$02,$7e,$02,$81,$02,$83,$02,$86,$02,$88,$02,$8b,$02,$8e,$02 dataend: ;; file header data .SEGMENT "EXEHDR" .BYTE 255, 255 ;; run address .SEGMENT "AUTOSTRT" .ADDR 736 .ADDR 737 .ADDR segstart