]> git.sur5r.net Git - cc65/blob - libsrc/zlib/inflatemem.s
Removed (pretty inconsistently used) tab chars from source code base.
[cc65] / libsrc / zlib / inflatemem.s
1 ;
2 ; Piotr Fusik, 21.09.2003
3 ;
4 ; unsigned __fastcall__ inflatemem (char* dest, const char* source);
5 ;
6
7         .export         _inflatemem
8
9         .import         incsp2
10         .importzp       sp, sreg, ptr1, ptr2, ptr3, ptr4, tmp1
11
12 ; --------------------------------------------------------------------------
13 ;
14 ; Constants
15 ;
16
17 ; Maximum length of a Huffman code.
18 MAX_BITS      = 15
19
20 ; All Huffman trees are stored in the bitsCount, bitsPointer_l
21 ; and bitsPointer_h arrays.  There may be two trees: the literal/length tree
22 ; and the distance tree, or just one - the temporary tree.
23
24 ; Index in the mentioned arrays for the beginning of the literal/length tree
25 ; or the temporary tree.
26 PRIMARY_TREE  = 0
27
28 ; Index in the mentioned arrays for the beginning of the distance tree.
29 DISTANCE_TREE = MAX_BITS
30
31 ; Size of each array.
32 TREES_SIZE    = 2*MAX_BITS
33
34
35 ; --------------------------------------------------------------------------
36 ;
37 ; Page zero
38 ;
39
40 ; Pointer to the compressed data.
41 inputPointer            =       ptr1    ; 2 bytes
42
43 ; Pointer to the uncompressed data.
44 outputPointer           =       ptr2    ; 2 bytes
45
46 ; Local variables.
47 ; As far as there is no conflict, same memory locations are used
48 ; for different variables.
49
50 inflateDynamicBlock_cnt =       ptr3    ; 1 byte
51 inflateCodes_src        =       ptr3    ; 2 bytes
52 buildHuffmanTree_src    =       ptr3    ; 2 bytes
53 getNextLength_last      =       ptr3    ; 1 byte
54 getNextLength_index     =       ptr3+1  ; 1 byte
55
56 buildHuffmanTree_ptr    =       ptr4    ; 2 bytes
57 fetchCode_ptr           =       ptr4    ; 2 bytes
58 getBits_tmp             =       ptr4    ; 1 byte
59
60 moveBlock_len           =       sreg    ; 2 bytes
61 inflateDynamicBlock_np  =       sreg    ; 1 byte
62 inflateDynamicBlock_nd  =       sreg+1  ; 1 byte
63
64 getBit_hold             =       tmp1    ; 1 byte
65
66
67 ; --------------------------------------------------------------------------
68 ;
69 ; Code
70 ;
71
72 _inflatemem:
73
74 ; inputPointer = source
75         sta     inputPointer
76         stx     inputPointer+1
77 ; outputPointer = dest
78 .ifpc02
79         lda     (sp)
80         ldy     #1
81 .else
82         ldy     #0
83         lda     (sp),y
84         iny
85 .endif
86         sta     outputPointer
87         lda     (sp),y
88         sta     outputPointer+1
89
90 ;       ldy     #1
91         sty     getBit_hold
92 inflatemem_1:
93 ; Get a bit of EOF and two bits of block type
94         ldx     #3
95         lda     #0
96         jsr     getBits
97         lsr     a
98 ; A and Z contain block type, C contains EOF flag
99 ; Save EOF flag
100         php
101 ; Go to the routine decompressing this block
102         jsr     callExtr
103         plp
104         bcc     inflatemem_1
105 ; C flag is set!
106
107 ; return outputPointer - dest;
108         lda     outputPointer
109 .ifpc02
110         sbc     (sp)            ; C flag is set
111         ldy     #1
112 .else
113         ldy     #0
114         sbc     (sp),y          ; C flag is set
115         iny
116 .endif
117         pha
118         lda     outputPointer+1
119         sbc     (sp),y
120         tax
121         pla
122 ; pop dest
123         jmp     incsp2
124
125 ; --------------------------------------------------------------------------
126 ; Go to proper block decoding routine.
127
128 callExtr:
129         bne     inflateCompressedBlock
130
131 ; --------------------------------------------------------------------------
132 ; Decompress a 'stored' data block.
133
134 inflateCopyBlock:
135 ; Ignore bits until byte boundary
136         ldy     #1
137         sty     getBit_hold
138 ; Get 16-bit length
139         ldx     #inputPointer
140         lda     (0,x)
141         sta     moveBlock_len
142         lda     (inputPointer),y
143         sta     moveBlock_len+1
144 ; Skip the length and one's complement of it
145         lda     #4
146         clc
147         adc     inputPointer
148         sta     inputPointer
149         bcc     moveBlock
150         inc     inputPointer+1
151 ;       jmp     moveBlock
152
153 ; --------------------------------------------------------------------------
154 ; Copy block of length moveBlock_len from (0,x) to the output.
155
156 moveBlock:
157         ldy     moveBlock_len
158         beq     moveBlock_1
159 .ifpc02
160 .else
161         ldy     #0
162 .endif
163         inc     moveBlock_len+1
164 moveBlock_1:
165         lda     (0,x)
166 .ifpc02
167         sta     (outputPointer)
168 .else
169         sta     (outputPointer),y
170 .endif
171         inc     0,x
172         bne     moveBlock_2
173         inc     1,x
174 moveBlock_2:
175         inc     outputPointer
176         bne     moveBlock_3
177         inc     outputPointer+1
178 moveBlock_3:
179 .ifpc02
180         dey
181 .else
182         dec     moveBlock_len
183 .endif
184         bne     moveBlock_1
185         dec     moveBlock_len+1
186         bne     moveBlock_1
187         rts
188
189 ; --------------------------------------------------------------------------
190 ; Decompress a Huffman-coded data block
191 ; (A = 1: fixed, A = 2: dynamic).
192
193 inflateCompressedBlock:
194         lsr     a
195         bne     inflateDynamicBlock
196 ; Note: inflateDynamicBlock may assume that A = 1
197
198 ; --------------------------------------------------------------------------
199 ; Decompress a Huffman-coded data block with default Huffman trees
200 ; (defined by the DEFLATE format):
201 ; literalCodeLength:  144 times 8, 112 times 9
202 ; endCodeLength:      7
203 ; lengthCodeLength:   23 times 7, 6 times 8
204 ; distanceCodeLength: 30 times 5+DISTANCE_TREE, 2 times 8
205 ;                     (two 8-bit codes from the primary tree are not used).
206
207 inflateFixedBlock:
208         ldx     #159
209         stx     distanceCodeLength+32
210         lda     #8
211 inflateFixedBlock_1:
212         sta     literalCodeLength-1,x
213         sta     literalCodeLength+159-1,x
214         dex
215         bne     inflateFixedBlock_1
216         ldx     #112
217 ;       lda     #9
218 inflateFixedBlock_2:
219         inc     literalCodeLength+144-1,x       ; sta
220         dex
221         bne     inflateFixedBlock_2
222         ldx     #24
223 ;       lda     #7
224 inflateFixedBlock_3:
225         dec     endCodeLength-1,x       ; sta
226         dex
227         bne     inflateFixedBlock_3
228         ldx     #30
229         lda     #5+DISTANCE_TREE
230 inflateFixedBlock_4:
231         sta     distanceCodeLength-1,x
232         dex
233         bne     inflateFixedBlock_4
234         beq     inflateCodes            ; branch always
235
236 ; --------------------------------------------------------------------------
237 ; Decompress a Huffman-coded data block, reading Huffman trees first.
238
239 inflateDynamicBlock:
240 ; numberOfPrimaryCodes = 257 + getBits(5)
241         ldx     #5
242 ;       lda     #1
243         jsr     getBits
244         sta     inflateDynamicBlock_np
245 ; numberOfDistanceCodes = 1 + getBits(5)
246         ldx     #5
247         lda     #1+29+1
248         jsr     getBits
249         sta     inflateDynamicBlock_nd
250 ; numberOfTemporaryCodes = 4 + getBits(4)
251         lda     #4
252         tax
253         jsr     getBits
254         sta     inflateDynamicBlock_cnt
255 ; Get lengths of temporary codes in the order stored in tempCodeLengthOrder
256         txa                     ; lda #0
257         tay
258 inflateDynamicBlock_1:
259         ldx     #3              ; A = 0
260         jsr     getBits         ; does not change Y
261 inflateDynamicBlock_2:
262         ldx     tempCodeLengthOrder,y
263         sta     literalCodeLength,x
264         lda     #0
265         iny
266         cpy     inflateDynamicBlock_cnt
267         bcc     inflateDynamicBlock_1
268         cpy     #19
269         bcc     inflateDynamicBlock_2
270         ror     literalCodeLength+19    ; C flag is set, so this will set b7
271 ; Build the tree for temporary codes
272         jsr     buildHuffmanTree
273
274 ; Use temporary codes to get lengths of literal/length and distance codes
275         ldx     #0
276         ldy     #1
277         stx     getNextLength_last
278 inflateDynamicBlock_3:
279         jsr     getNextLength
280         sta     literalCodeLength,x
281         inx
282         bne     inflateDynamicBlock_3
283 inflateDynamicBlock_4:
284         jsr     getNextLength
285 inflateDynamicBlock_5:
286         sta     endCodeLength,x
287         inx
288         cpx     inflateDynamicBlock_np
289         bcc     inflateDynamicBlock_4
290         lda     #0
291         cpx     #1+29
292         bcc     inflateDynamicBlock_5
293 inflateDynamicBlock_6:
294         jsr     getNextLength
295         cmp     #0
296         beq     inflateDynamicBlock_7
297         adc     #DISTANCE_TREE-1        ; C flag is set
298 inflateDynamicBlock_7:
299         sta     endCodeLength,x
300         inx
301         cpx     inflateDynamicBlock_nd
302         bcc     inflateDynamicBlock_6
303         ror     endCodeLength,x         ; C flag is set, so this will set b7
304 ;       jmp     inflateCodes
305
306 ; --------------------------------------------------------------------------
307 ; Decompress a data block basing on given Huffman trees.
308
309 inflateCodes:
310         jsr     buildHuffmanTree
311 inflateCodes_1:
312         jsr     fetchPrimaryCode
313         bcs     inflateCodes_2
314 ; Literal code
315 .ifpc02
316         sta     (outputPointer)
317 .else
318         ldy     #0
319         sta     (outputPointer),y
320 .endif
321         inc     outputPointer
322         bne     inflateCodes_1
323         inc     outputPointer+1
324         bcc     inflateCodes_1  ; branch always
325 ; End of block
326 inflateCodes_ret:
327         rts
328 inflateCodes_2:
329         beq     inflateCodes_ret
330 ; Restore a block from the look-behind buffer
331         jsr     getValue
332         sta     moveBlock_len
333         tya
334         jsr     getBits
335         sta     moveBlock_len+1
336         ldx     #DISTANCE_TREE
337         jsr     fetchCode
338         jsr     getValue
339         sec
340         eor     #$ff
341         adc     outputPointer
342         sta     inflateCodes_src
343         php
344         tya
345         jsr     getBits
346         plp
347         eor     #$ff
348         adc     outputPointer+1
349         sta     inflateCodes_src+1
350         ldx     #inflateCodes_src
351         jsr     moveBlock
352         beq     inflateCodes_1  ; branch always
353
354 ; --------------------------------------------------------------------------
355 ; Build Huffman trees basing on code lengths (in bits).
356 ; stored in the *CodeLength arrays.
357 ; A byte with its highest bit set marks the end.
358
359 buildHuffmanTree:
360         lda     #<literalCodeLength
361         sta     buildHuffmanTree_src
362         lda     #>literalCodeLength
363         sta     buildHuffmanTree_src+1
364 ; Clear bitsCount and bitsPointer_l
365         ldy     #2*TREES_SIZE+1
366         lda     #0
367 buildHuffmanTree_1:
368         sta     bitsCount-1,y
369         dey
370         bne     buildHuffmanTree_1
371         beq     buildHuffmanTree_3      ; branch always
372 ; Count number of codes of each length
373 buildHuffmanTree_2:
374         tax
375         inc     bitsPointer_l,x
376         iny
377         bne     buildHuffmanTree_3
378         inc     buildHuffmanTree_src+1
379 buildHuffmanTree_3:
380         lda     (buildHuffmanTree_src),y
381         bpl     buildHuffmanTree_2
382 ; Calculate a pointer for each length
383         ldx     #0
384         lda     #<sortedCodes
385         ldy     #>sortedCodes
386         clc
387 buildHuffmanTree_4:
388         sta     bitsPointer_l,x
389         tya
390         sta     bitsPointer_h,x
391         lda     bitsPointer_l+1,x
392         adc     bitsPointer_l,x         ; C flag is zero
393         bcc     buildHuffmanTree_5
394         iny
395 buildHuffmanTree_5:
396         inx
397         cpx     #TREES_SIZE
398         bcc     buildHuffmanTree_4
399         lda     #>literalCodeLength
400         sta     buildHuffmanTree_src+1
401         ldy     #0
402         bcs     buildHuffmanTree_9      ; branch always
403 ; Put codes into their place in sorted table
404 buildHuffmanTree_6:
405         beq     buildHuffmanTree_7
406         tax
407         lda     bitsPointer_l-1,x
408         sta     buildHuffmanTree_ptr
409         lda     bitsPointer_h-1,x
410         sta     buildHuffmanTree_ptr+1
411         tya
412         ldy     bitsCount-1,x
413         inc     bitsCount-1,x
414         sta     (buildHuffmanTree_ptr),y
415         tay
416 buildHuffmanTree_7:
417         iny
418         bne     buildHuffmanTree_9
419         inc     buildHuffmanTree_src+1
420         ldx     #MAX_BITS-1
421 buildHuffmanTree_8:
422         lda     bitsCount,x
423         sta     literalCount,x
424         dex
425         bpl     buildHuffmanTree_8
426 buildHuffmanTree_9:
427         lda     (buildHuffmanTree_src),y
428         bpl     buildHuffmanTree_6
429         rts
430
431 ; --------------------------------------------------------------------------
432 ; Decode next code length using temporary codes.
433
434 getNextLength:
435         stx     getNextLength_index
436         dey
437         bne     getNextLength_1
438 ; Fetch a temporary code
439         jsr     fetchPrimaryCode
440 ; Temporary code 0..15: put this length
441         ldy     #1
442         cmp     #16
443         bcc     getNextLength_2
444 ; Temporary code 16: repeat last length 3 + getBits(2) times
445 ; Temporary code 17: put zero length 3 + getBits(3) times
446 ; Temporary code 18: put zero length 11 + getBits(7) times
447         tay
448         ldx     tempExtraBits-16,y
449         lda     tempBaseValue-16,y
450         jsr     getBits
451         cpy     #17
452         tay
453         txa                     ; lda #0
454         bcs     getNextLength_2
455 getNextLength_1:
456         lda     getNextLength_last
457 getNextLength_2:
458         sta     getNextLength_last
459         ldx     getNextLength_index
460         rts
461
462 ; --------------------------------------------------------------------------
463 ; Read a code basing on the primary tree.
464
465 fetchPrimaryCode:
466         ldx     #PRIMARY_TREE
467 ;       jmp     fetchCode
468
469 ; --------------------------------------------------------------------------
470 ; Read a code from input basing on the tree specified in X.
471 ; Return low byte of this code in A.
472 ; For the literal/length tree, the C flag is set if the code is non-literal.
473
474 fetchCode:
475         lda     #0
476 fetchCode_1:
477         jsr     getBit
478         rol     a
479         inx
480         sec
481         sbc     bitsCount-1,x
482         bcs     fetchCode_1
483         adc     bitsCount-1,x   ; C flag is zero
484         cmp     literalCount-1,x
485         sta     fetchCode_ptr
486         ldy     bitsPointer_l-1,x
487         lda     bitsPointer_h-1,x
488         sta     fetchCode_ptr+1
489         lda     (fetchCode_ptr),y
490         rts
491
492 ; --------------------------------------------------------------------------
493 ; Decode low byte of a value (length or distance), basing on the code in A.
494 ; The result is the base value for this code plus some bits read from input.
495
496 getValue:
497         tay
498         ldx     lengthExtraBits-1,y
499         lda     lengthBaseValue_l-1,y
500         pha
501         lda     lengthBaseValue_h-1,y
502         tay
503         pla
504 ;       jmp     getBits
505
506 ; --------------------------------------------------------------------------
507 ; Read X-bit number from the input and add it to A.
508 ; Increment Y if overflow.
509 ; If X > 8, read only 8 bits.
510 ; On return X holds number of unread bits: X = (X > 8 ? X - 8 : 0);
511
512 getBits:
513         cpx     #0
514         beq     getBits_ret
515 .ifpc02
516         stz     getBits_tmp
517         dec     getBits_tmp
518 .else
519         pha
520         lda     #$ff
521         sta     getBits_tmp
522         pla
523 .endif
524 getBits_1:
525         jsr     getBit
526         bcc     getBits_2
527         sbc     getBits_tmp     ; C flag is set
528         bcc     getBits_2
529         iny
530 getBits_2:
531         dex
532         beq     getBits_ret
533         asl     getBits_tmp
534         bmi     getBits_1
535 getBits_ret:
536         rts
537
538 ; --------------------------------------------------------------------------
539 ; Read a single bit from input, return it in the C flag.
540
541 getBit:
542         lsr     getBit_hold
543         bne     getBit_ret
544         pha
545 .ifpc02
546         lda     (inputPointer)
547 .else
548         sty     getBit_hold
549         ldy     #0
550         lda     (inputPointer),y
551         ldy     getBit_hold
552 .endif
553         inc     inputPointer
554         bne     getBit_1
555         inc     inputPointer+1
556 getBit_1:
557         ror     a       ; C flag is set
558         sta     getBit_hold
559         pla
560 getBit_ret:
561         rts
562
563
564 ; --------------------------------------------------------------------------
565 ;
566 ; Constant data
567 ;
568
569         .rodata
570 ; --------------------------------------------------------------------------
571 ; Arrays for the temporary codes.
572
573 ; Order, in which lengths of the temporary codes are stored.
574 tempCodeLengthOrder:
575         .byte   16,17,18,0,8,7,9,6,10,5,11,4,12,3,13,2,14,1,15
576
577 ; Base values.
578 tempBaseValue:
579         .byte   3,3,11
580
581 ; Number of extra bits to read.
582 tempExtraBits:
583         .byte   2,3,7
584
585 ; --------------------------------------------------------------------------
586 ; Arrays for the length and distance codes.
587
588 ; Base values.
589 lengthBaseValue_l:
590         .byte   <3,<4,<5,<6,<7,<8,<9,<10
591         .byte   <11,<13,<15,<17,<19,<23,<27,<31
592         .byte   <35,<43,<51,<59,<67,<83,<99,<115
593         .byte   <131,<163,<195,<227,<258
594 distanceBaseValue_l:
595         .byte   <1,<2,<3,<4,<5,<7,<9,<13
596         .byte   <17,<25,<33,<49,<65,<97,<129,<193
597         .byte   <257,<385,<513,<769,<1025,<1537,<2049,<3073
598         .byte   <4097,<6145,<8193,<12289,<16385,<24577
599 lengthBaseValue_h:
600         .byte   >3,>4,>5,>6,>7,>8,>9,>10
601         .byte   >11,>13,>15,>17,>19,>23,>27,>31
602         .byte   >35,>43,>51,>59,>67,>83,>99,>115
603         .byte   >131,>163,>195,>227,>258
604 distanceBaseValue_h:
605         .byte   >1,>2,>3,>4,>5,>7,>9,>13
606         .byte   >17,>25,>33,>49,>65,>97,>129,>193
607         .byte   >257,>385,>513,>769,>1025,>1537,>2049,>3073
608         .byte   >4097,>6145,>8193,>12289,>16385,>24577
609
610 ; Number of extra bits to read.
611 lengthExtraBits:
612         .byte   0,0,0,0,0,0,0,0
613         .byte   1,1,1,1,2,2,2,2
614         .byte   3,3,3,3,4,4,4,4
615         .byte   5,5,5,5,0
616 distanceExtraBits:
617         .byte   0,0,0,0,1,1,2,2
618         .byte   3,3,4,4,5,5,6,6
619         .byte   7,7,8,8,9,9,10,10
620         .byte   11,11,12,12,13,13
621
622
623 ; --------------------------------------------------------------------------
624 ;
625 ; Uninitialised data
626 ;
627
628         .bss
629
630 ; Number of literal codes of each length in the primary tree
631 ; (MAX_BITS bytes, overlap with literalCodeLength).
632 literalCount:
633
634 ; --------------------------------------------------------------------------
635 ; Data for building the primary tree.
636
637 ; Lengths of literal codes.
638 literalCodeLength:
639         .res    256
640 ; Length of the end code.
641 endCodeLength:
642         .res    1
643 ; Lengths of length codes.
644 lengthCodeLength:
645         .res    29
646
647 ; --------------------------------------------------------------------------
648 ; Data for building the distance tree.
649
650 ; Lengths of distance codes.
651 distanceCodeLength:
652         .res    30
653 ; For two unused codes in the fixed trees and an 'end' mark.
654         .res    3
655
656 ; --------------------------------------------------------------------------
657 ; The Huffman trees.
658
659 ; Number of codes of each length.
660 bitsCount:
661         .res    TREES_SIZE
662 ; Pointers to sorted codes of each length.
663 bitsPointer_l:
664         .res    TREES_SIZE+1
665 bitsPointer_h:
666         .res    TREES_SIZE
667
668 ; Sorted codes.
669 sortedCodes:
670         .res    256+1+29+30+2
671
672
673