1;===========================================================================
2; Copyright (c) 1990-2005 Info-ZIP.  All rights reserved.
3;
4; See the accompanying file LICENSE, version 2000-Apr-09 or later
5; (the contents of which are also included in unzip.h) for terms of use.
6; If, for some reason, all these files are missing, the Info-ZIP license
7; also may be found at:  ftp://ftp.info-zip.org/pub/infozip/license.html
8;===========================================================================
9; flate.a created by Paul Kienitz, 20 June 94.  Last modified 30 Dec 2005.
10;
11; 68000 assembly language version of inflate_codes(), for Amiga.  Prototype:
12;
13;   int inflate_codes(__GPRO__ struct huft *tl, struct huft *td,
14;                     unsigned bl, unsigned bd);
15;
16; Where __GPRO__ expands to "Uz_Globs *G," if REENTRANT is defined,
17; otherwise to nothing.  In the latter case G is a global variable.
18;
19; Define AZTEC to use the Aztec C macro version of getc() instead of the
20; library getc() with FUNZIP.  AZTEC is ignored if FUNZIP is not defined.
21;
22; Define NO_CHECK_EOF to not use the fancy paranoid version of NEEDBITS --
23; this is equivalent to removing the #define CHECK_EOF from inflate.c.
24;
25; Define INT16 if ints are short, otherwise it assumes ints are long.
26;
27; Define USE_DEFLATE64 if we're supporting Deflate64 decompression.
28;
29; Do NOT define WSIZE; it is always 32K or 64K depending on USE_DEFLATE64.
30; You also do not need to define FUNZIP or SFX, if you create t:G_offs.a
31; correctly (see below).
32;
33; ------
34;
35; The following include file is generated from globals.h just before this
36; is compiled, and gives us equates that give the offsets in Uz_Globs of
37; the fields we use, which are:
38;       ulg bb
39;       unsigned int bk, wp
40;       (either array of unsigned char, or pointer to unsigned char) redirslide
41; For regular UnZip but not fUnZip:
42;       int incnt, mem_mode
43;       uch *inptr
44; For fUnZip:
45;       FILE *in
46; It also defines a value SIZEOF_slide, which tells us whether the appropriate
47; slide field in G (either area.Slide or redirect_pointer) is a pointer or an
48; array instance.  It is 4 in the former case and a large value in the latter.
49; Lastly, this include will define CRYPT as 1 if appropriate and supply flag
50; definitions for major compile options that may affect the layout of the
51; globals structure and the functionality of the core decompression routines
52; (currently FUNZIP, SFX, REENTRANT, DLL, NO_SLIDE_REDIR, USE_DEFLATE64).
53
54        INCLUDE "t:G_offs.a"
55
56; struct huft is defined as follows:
57;
58;   struct huft {
59;     uch e;                /* number of extra bits or operation */
60;     uch b;                /* number of bits in this code or subcode */
61;     union {
62;       ush n;              /* literal, length base, or distance base */
63;       struct huft *t;     /* pointer to next level of table */
64;     } v;
65;   };                      /* sizeof(struct huft) == 6, or 8 if padded */
66;
67; The G_offs include defines offsets h_e, h_b, h_v_n, and h_v_t in this
68; struct, plus SIZEOF_huft.
69
70                IFD     REENTRANT
71                 IFND   FUNZIP
72REENT_G equ     1
73                 ENDC
74                ENDC
75
76; These macros allow us to deal uniformly with short or long ints:
77
78                IFD     INT16
79MOVINT           MACRO
80        move.w          \1,\2
81                 ENDM
82INTSIZE equ     2
83                ELSE    ; !INT16
84MOVINT           MACRO
85        move.l          \1,\2
86                 ENDM
87INTSIZE equ     4
88                ENDC
89
90; G.bb is the global buffer that holds bits from the huffman code stream, which
91; we cache in the register variable b.  G.bk is the number of valid bits in it,
92; which we cache in k.  The macros NEEDBITS(n) and DUMPBITS(n) have side effects
93; on b and k.
94
95                IFD     REENT_G
96G_SIZE  equ     4
97G_PUSH           MACRO          ; this macro passes "__G__" to functions
98        move.l          G,-(sp)
99                 ENDM
100                ELSE
101        xref    _G              ; Uz_Globs
102G_SIZE  equ     0
103G_PUSH           MACRO
104        ds.b            0       ; does nothing; the assembler dislikes MACRO ENDM
105                 ENDM
106                ENDC    ; REENT_G
107
108;;      xref    _mask_bits      ; const unsigned mask_bits[17];
109                IFD     FUNZIP
110                 IF     CRYPT
111        xref    _encrypted      ; int -- boolean flag
112        xref    _update_keys    ; int update_keys(__GPRO__ int)
113        xref    _decrypt_byte   ; int decrypt_byte(__GPRO)
114                 ENDC   ; CRYPT
115                ELSE    ; !FUNZIP
116        xref    _memflush       ; int memflush(__GPRO__ uch *, ulg)
117        xref    _readbyte       ; int readbyte(__GPRO)
118                ENDC    ; FUNZIP
119
120        xref    _flush          ; if FUNZIP:  int flush(__GPRO__ ulg)
121                                ; else:  int flush(__GPRO__ uch *, ulg, int)
122
123; Here are our register variables.
124
125b       equr    d2              ; unsigned long
126k       equr    d3              ; unsigned short <= 32
127e       equr    d4              ; unsigned int, mostly used as unsigned char
128w       equr    d5              ; unsigned long (was short before deflate64)
129n       equr    d6              ; unsigned long (was short before deflate64)
130d       equr    d7              ; unsigned int, used as unsigned short
131
132t       equr    a2              ; struct huft *
133lmask   equr    a3              ; ulg *
134G       equr    a6              ; Uz_Globs *
135
136; Couple other items we need:
137
138savregs reg     d2-d7/a2/a3/a6
139                IFD     USE_DEFLATE64
140WSIZE   equ     $10000          ; 64K... be careful not to treat as short!
141                ELSE
142WSIZE   equ     $08000          ; 32K... be careful not to treat as negative!
143                ENDC
144EOF     equ     -1
145INVALID equ     99
146
147; inflate_codes() returns one of the following status codes:
148;          0  OK
149;          1  internal inflate error or EOF on input stream
150;         the following return codes are passed through from FLUSH() errors
151;          50 (PK_DISK)   "overflow of output space"
152;          80 (IZ_CTRLC)  "canceled by user's request"
153
154RET_OK  equ     0
155RET_ERR equ     1
156
157                IFD     FUNZIP
158; This does getc(in).  Aztec version is based on #define getc(fp) in stdio.h
159
160                 IFD    AZTEC
161        xref    __filbuf
162GETC              MACRO
163        move.l          in(G),a0
164        move.l          (a0),a1         ; in->_bp
165        cmp.l           4(a0),a1        ; in->_bend
166        blo.s           gci\@
167        move.l          a0,-(sp)
168        jsr             __filbuf
169        addq            #4,sp
170        bra.s           gce\@
171gci\@:  moveq           #0,d0           ; must be valid as longword
172        move.b          (a1)+,d0
173        move.l          a1,(a0)
174gce\@:
175                  ENDM
176                 ELSE   ; !AZTEC
177GETC              MACRO
178        xref    _getc
179        move.l          in(G),-(sp)
180        jsr             _getc
181        addq            #4,sp
182                  ENDM
183                 ENDC   ; AZTEC
184                ENDC    ; FUNZIP
185
186; Input depends on the NEXTBYTE macro.  This exists in three different forms.
187; The first two are for fUnZip, with and without decryption.  The last is for
188; regular UnZip with or without decryption.  The resulting byte is returned
189; in d0 as a longword, and d1, a0, and a1 are clobbered.
190
191; FLUSH also has different forms for UnZip and fUnZip.  Arg must be a longword.
192; The same scratch registers are trashed.
193
194                IFD     FUNZIP
195
196NEXTBYTE         MACRO
197        GETC
198                  IF    CRYPT
199        tst.w           _encrypted+INTSIZE-2    ; test low word if long
200        beq.s           nbe\@
201        MOVINT          d0,-(sp)                ; save thru next call
202        G_PUSH
203        jsr             _decrypt_byte
204        eor.w           d0,G_SIZE+INTSIZE-2(sp) ; becomes arg to update_keys
205        jsr             _update_keys
206        addq            #INTSIZE+G_SIZE,sp
207nbe\@:
208                  ENDC  ; !CRYPT
209                  IFGT 4-INTSIZE
210        ext.l           d0              ; assert -1 <= d0 <= 255
211                  ENDC
212                 ENDM
213
214FLUSH            MACRO
215        move.l          \1,-(sp)
216        G_PUSH
217        jsr             _flush
218        addq            #4+G_SIZE,sp
219                 ENDM
220
221                ELSE    ; !FUNZIP
222
223NEXTBYTE         MACRO
224        subq.w          #1,incnt+INTSIZE-2(G)   ; treat as short
225        bge.s           nbs\@
226        G_PUSH
227        jsr             _readbyte
228                  IFNE G_SIZE
229        addq            #G_SIZE,sp
230                  ENDC
231                  IFGT 4-INTSIZE
232        ext.l           d0            ; assert -1 <= d0 <= 255
233                  ENDC
234        bra.s           nbe\@
235nbs\@:  moveq           #0,d0
236        move.l          inptr(G),a0   ; alt vers: move.b inptr(G),d0
237        move.b          (a0)+,d0      ;           addq   #1,inptr(G)
238        move.l          a0,inptr(G)
239nbe\@:
240                 ENDM
241
242FLUSH            MACRO
243        MOVINT          #0,-(sp)                ; unshrink flag: always false
244        move.l          \1,-(sp)                ; length
245                  IFGT  SIZEOF_slide-4
246        pea             redirslide(G)           ; buffer to flush
247                  ELSE
248        move.l          redirslide(G),-(sp)
249                  ENDC
250        G_PUSH
251        tst.w           mem_mode+INTSIZE-2(G)   ; test lower word if long
252        beq.s           fm\@
253        jsr             _memflush               ; ignores the unshrink flag
254        bra.s           fe\@
255fm\@:   jsr             _flush
256fe\@:   lea             8+INTSIZE+G_SIZE(sp),sp
257                 ENDM
258
259                ENDC    ; ?FUNZIP
260
261; Here are the two bit-grabbing macros, which in their NO_CHECK_EOF form are:
262;
263;   #define NEEDBITS(n) {while(k<(n)){b|=((ulg)NEXTBYTE)<<k;k+=8;}}
264;   #define DUMPBITS(n) {b>>=(n);k-=(n);}
265;
266; Without NO_CHECK_EOF, NEEDBITS reads like this:
267;
268;   {while((int)k<(int)(n)){\
269;      int c=NEXTBYTE;if(c==EOF){\
270;         if((int)k>=0)break;\
271;         retval=1;goto cleanup_and_exit;}\
272;      b|=((ulg)c)<<k;k+=8;}}
273;
274; ...where cleanup_and_exit just does "return retval;".  If
275; FIX_PAST_EOB_BY_TABLEADJUST is defined, there's yet another version,
276; which I don't think this is used by anybody:
277;
278;   {while(k<(n)){\
279;      int c=NEXTBYTE;if(c==EOF){\
280;         retval=1;goto cleanup_and_exit;}\
281;      b|=((ulg)c)<<k;k+=8;}}
282;
283; NEEDBITS clobbers d0, d1, a0, and a1, none of which can be used as the arg to
284; the macro specifying the number of bits.  The arg can be a shortword memory
285; address, or d2-d7.  The result is copied into d1 as a word ready for masking.
286; DUMPBITS has no side effects; the arg must be a d-register (or immediate in
287; the range 1-8?) and only the lower byte is significant.
288
289NEEDBITS        MACRO                   ; arg is short
290nb\@:   cmp.w           \1,k            ; assert 0 < k <= 32 ... arg may be 0
291        bge.s           ne\@            ; signed compare
292        NEXTBYTE                        ; returns in d0.l
293                 IFND   NO_CHECK_EOF
294        cmp.w           #EOF,d0
295        bne.s           nok\@
296        tst.w           k
297        bge.s           ne\@
298        moveq           #RET_ERR,d0
299        bra             return
300                 ENDC   ; !NO_CHECK_EOF
301nok\@:  lsl.l           k,d0
302        or.l            d0,b
303        addq.w          #8,k
304        bra.s           nb\@
305ne\@:   move.l          b,d1            ; return a copy of b in d1
306                ENDM
307
308DUMPBITS        MACRO                   ; arg is byte, not short!
309        lsr.l           \1,b            ; upper bits of \1 are ignored, right?
310        sub.b           \1,k
311                ENDM
312
313
314; This is a longword version of the mask_bits constant array:
315longmasks:      dc.l    $00000000,$00000001,$00000003,$00000007,$0000000F
316                dc.l    $0000001F,$0000003F,$0000007F,$000000FF,$000001FF
317                dc.l    $000003FF,$000007FF,$00000FFF,$00001FFF,$00003FFF
318                dc.l    $00007FFF,$0000FFFF,0,0,0,0,0,0,0,0,0,0,0,0,0,0
319
320
321; ******************************************************************************
322; Here we go, finally:
323
324        xdef    _inflate_codes
325
326_inflate_codes:
327        link            a5,#-8
328        movem.l         savregs,-(sp)
329; 8(a5) = tl, 12(a5) = td, 16(a5) = bl, 18|20(a5) = bd... add 4 for REENT_G
330; -4(a5) = ml, -8(a5) = md, both unsigned long.
331; Here we cache some globals and args:
332                IFD     REENT_G
333        move.l          8(a5),G
334                ELSE
335        lea             _G,G            ; G is now a global instance
336                ENDC
337        lea             longmasks,lmask
338        move.l          bb(G),b
339        MOVINT          bk(G),k
340                IFD     INT16
341        moveq           #0,w            ; keep this usable as longword
342                ENDC
343        MOVINT          wp(G),w
344        moveq           #0,e            ; keep this usable as longword too
345        MOVINT          16+G_SIZE(a5),d0
346        asl.w           #2,d0
347        move.l          (lmask,d0.w),-4(a5)     ; ml = mask_bits[bl]
348        MOVINT          16+INTSIZE+G_SIZE(a5),d0
349        asl.w           #2,d0
350        move.l          (lmask,d0.w),-8(a5)     ; md = mask_bits[bd]
351
352        xdef newtop
353        xdef nonlit
354        xdef distop
355        xdef docopy
356        xdef nonleng
357        xdef tailgo
358        xdef finish
359        xdef disbrk
360main_loop:
361        NEEDBITS        14+INTSIZE+G_SIZE(a5)   ; (unsigned) bl
362        and.l           -4(a5),d1               ; ml
363                IFNE SIZEOF_huft-8
364        mulu            #SIZEOF_huft,d1
365                ELSE
366        asl.l           #3,d1
367                ENDC
368        move.l          8+G_SIZE(a5),t          ; tl
369        add.l           d1,t
370newtop:  move.b         h_b(t),d0
371         DUMPBITS       d0
372         move.b         h_e(t),e
373         cmp.b          #32,e                   ; is it a literal?
374         bne            nonlit                  ; no
375          move.w        h_v_n(t),d0             ; yes
376                IFGT SIZEOF_slide-4
377          lea           redirslide(G),a0
378                ELSE
379          move.l        redirslide(G),a0
380                ENDC
381          move.b        d0,(a0,w.l)             ; stick in the decoded byte
382          addq.l        #1,w
383          cmp.l         #WSIZE,w
384          blo           main_loop
385           FLUSH        w
386           ext.l        d0                      ; does a test as it casts long
387           bne          return
388           moveq        #0,w
389           bra          main_loop               ; break (newtop loop)
390
391nonlit:  cmp.b          #31,e                   ; is it a length?
392         beq            finish                  ; no, it's the end marker
393         bhi            nonleng                 ; no, it's something else
394          NEEDBITS      e                       ; yes: a duplicate string
395          move.w        e,d0
396          asl.w         #2,d0
397          and.l         (lmask,d0.w),d1
398          moveq         #0,n                    ; cast h_v_n(t) to long
399          move.w        h_v_n(t),n
400          add.l         d1,n                    ; length of block to copy
401          DUMPBITS      e
402          NEEDBITS      14+(2*INTSIZE)+G_SIZE(a5)   ; bd, lower word if long
403          and.l         -8(a5),d1                   ; md
404                IFNE SIZEOF_huft-8
405          mulu          #SIZEOF_huft,d1
406                ELSE
407          asl.l         #3,d1
408                ENDC
409          move.l        12+G_SIZE(a5),t                 ; td
410          add.l         d1,t
411distop:    move.b       h_b(t),d0
412           DUMPBITS     d0
413           move.b       h_e(t),e
414           cmp.b        #32,e                   ; is it a literal?
415           blo.s        disbrk                  ; then stop doing this
416            cmp.b       #INVALID,e              ; is it bogus?
417            bne.s       disgo
418             moveq      #RET_ERR,d0             ; then fail
419             bra        return
420disgo:      and.w       #$001F,e
421            NEEDBITS    e
422            move.w      e,d0
423            asl.w       #2,d0
424            and.l       (lmask,d0.w),d1
425                IFNE SIZEOF_huft-8
426            mulu        #SIZEOF_huft,d1
427                ELSE
428            asl.l       #3,d1
429                ENDC
430            move.l      h_v_t(t),t
431            add.l       d1,t
432            bra         distop
433disbrk:   NEEDBITS      e
434          move.l        e,d0
435          asl.w         #2,d0
436          and.l         (lmask,d0.w),d1
437          move.l        w,d
438          move.w        h_v_n(t),d0     ; assert top word of d0 is zero
439          sub.l         d0,d
440          sub.l         d1,d            ; distance back to copy the block
441          DUMPBITS      e
442
443docopy:    move.l       #WSIZE,e        ; copy the duplicated string
444           and.l        #WSIZE-1,d      ; ...but first check if the length
445           cmp.l        d,w             ; will overflow the window...
446           blo.s        ddgw
447            sub.l       w,e
448           bra.s        dadw
449ddgw:       sub.l       d,e
450dadw:      cmp.l        #$08000,e       ; also, only copy <= 32K, so we can
451           bls.s        dnox            ; use a dbra loop to do it
452            move.l      #$08000,e
453dnox:      cmp.l        n,e
454           bls.s        delen
455            move.l      n,e
456delen:     sub.l        e,n             ; size of sub-block to copy in this pass
457                IFGT    SIZEOF_slide-4
458           lea          redirslide(G),a0
459                ELSE
460           move.l       redirslide(G),a0
461                ENDC
462           move.l       a0,a1
463           add.l        w,a0
464           add.l        d,a1
465; Now at this point we could do tests to see if we should use an optimized
466; large block copying method such as movem's, but since (a) such methods require
467; the source and destination to be compatibly aligned -- and odd bytes at each
468; end have to be handled separately, (b) it's only worth checking for if the
469; block is pretty large, and (c) most strings are only a few bytes long, we're
470; just not going to bother.  Therefore we check above to make sure we move at
471; most 32K in one sub-block, so a dbra loop can handle it.
472dshort:    move.l       e,d0
473           subq         #1,d0           ; assert >= 0
474dspin:      move.b      (a1)+,(a0)+
475            dbra        d0,dspin
476           add.l        e,w
477           add.l        e,d
478           cmp.l        #WSIZE,w
479           blo.s        dnfl
480            FLUSH       w
481            ext.l       d0              ; does a test as it casts to long
482            bne         return
483            moveq       #0,w
484dnfl:      tst.l        n               ; need to do more sub-blocks?
485           bne          docopy          ; yes
486          moveq         #0,e            ; restore zeroness in upper bytes of e
487          bra           main_loop       ; break (newtop loop)
488
489nonleng: cmp.w          #INVALID,e      ; bottom of newtop loop -- misc. code
490         bne.s          tailgo          ; invalid code?
491          moveq         #RET_ERR,d0     ; then fail
492          bra           return
493tailgo:  and.w          #$001F,e
494         NEEDBITS       e
495         move.w         e,d0
496         asl.w          #2,d0
497         and.l          (lmask,d0.w),d1
498                IFNE SIZEOF_huft-8
499         mulu           #SIZEOF_huft,d1
500                ELSE
501         asl.l          #3,d1
502                ENDC
503         move.l         h_v_t(t),t
504         add.l          d1,t
505         bra            newtop
506
507finish: MOVINT          w,wp(G)         ; done: restore cached globals
508        MOVINT          k,bk(G)
509        move.l          b,bb(G)
510        moveq           #RET_OK,d0      ; return "no error"
511return: movem.l         (sp)+,savregs
512        unlk            a5
513        rts
514