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