1/*
2  Copyright (c) 1990-2005 Info-ZIP.  All rights reserved.
3
4  See the accompanying file LICENSE, version 2004-May-22 or later
5  (the contents of which are also included in zip.h) for terms of use.
6  If, for some reason, both of 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
10/*
11 * match.s by Jean-loup Gailly. Translated to 32 bit code by Kai Uwe Rommel.
12 * The 68020 version has been written by Francesco Potorti` <pot@cnuce.cnr.it>
13 * with adaptations by Carsten Steger <stegerc@informatik.tu-muenchen.de>,
14 * Andreas Schwab <schwab@lamothe.informatik.uni-dortmund.de> and
15 * Kristoffer Eriksson <ske@pkmab.se>
16 */
17
18/* This file is NOT used in conjunction with zlib. */
19#ifndef USE_ZLIB
20
21/* Preprocess with -DNO_UNDERLINE if your C compiler does not prefix
22 * external symbols with an underline character '_'.
23 */
24#if defined(NO_UNDERLINE) || defined(__ELF__)
25#  define _prev             prev
26#  define _window           window
27#  define _match_start      match_start
28#  define _prev_length      prev_length
29#  define _good_match       good_match
30#  define _nice_match       nice_match
31#  define _strstart         strstart
32#  define _max_chain_length max_chain_length
33
34#  define _match_init       match_init
35#  define _longest_match    longest_match
36#endif
37
38#ifdef DYN_ALLOC
39  error: DYN_ALLOC not yet supported in match.s
40#endif
41
42/* Use 16-bytes alignment if your assembler supports it. Warning: gas
43 * uses a log(x) parameter (.align 4 means 16-bytes alignment). On SVR4
44 * the parameter is a number of bytes.
45 */
46#ifndef ALIGNMENT
47#  define ALIGNMENT 4
48#endif
49
50
51#ifndef WSIZE
52# define WSIZE          32768
53#endif
54#define MIN_MATCH       3
55#define MAX_MATCH       258
56#define MIN_LOOKAHEAD   (MAX_MATCH + MIN_MATCH + 1)
57#define MAX_DIST        (WSIZE - MIN_LOOKAHEAD)
58
59#if defined(i386) || defined(_I386) || defined(_i386) || defined(__i386)
60
61/* This version is for 386 Unix or OS/2 in 32 bit mode.
62 * Warning: it uses the AT&T syntax: mov source,dest
63 * This file is only optional. If you want to force the C version,
64 * add -DNO_ASM to CFLAGS in Makefile and set OBJA to an empty string.
65 * If you have reduced WSIZE in (g)zip.h, then make sure this is
66 * assembled with an equivalent -DWSIZE=<whatever>.
67 * This version assumes static allocation of the arrays (-DDYN_ALLOC not used).
68 */
69
70        .file   "match.S"
71
72        .globl  _match_init
73        .globl  _longest_match
74
75        .text
76
77_match_init:
78        ret
79
80/*-----------------------------------------------------------------------
81 * Set match_start to the longest match starting at the given string and
82 * return its length. Matches shorter or equal to prev_length are discarded,
83 * in which case the result is equal to prev_length and match_start is
84 * garbage.
85 * IN assertions: cur_match is the head of the hash chain for the current
86 *   string (strstart) and its distance is <= MAX_DIST, and prev_length >= 1
87 */
88
89        .align  ALIGNMENT
90
91_longest_match: /* int longest_match(cur_match) */
92
93#define cur_match   20(%esp)
94     /* return address */               /* esp+16 */
95        push    %ebp                    /* esp+12 */
96        push    %edi                    /* esp+8  */
97        push    %esi                    /* esp+4  */
98        push    %ebx                    /* esp    */
99
100/*
101 *      match        equ esi
102 *      scan         equ edi
103 *      chain_length equ ebp
104 *      best_len     equ ebx
105 *      limit        equ edx
106 */
107        mov     cur_match,%esi
108        mov     _strstart,%edx
109        mov     _max_chain_length,%ebp /* chain_length = max_chain_length */
110        mov     %edx,%edi
111        sub     $(MAX_DIST),%edx       /* limit = strstart-MAX_DIST */
112        cld                            /* string ops increment si and di */
113        jae     limit_ok
114        sub     %edx,%edx              /* limit = NIL */
115limit_ok:
116        add     $2+_window,%edi        /* edi = offset(window+strstart+2) */
117        mov     _prev_length,%ebx      /* best_len = prev_length */
118        movw    -2(%edi),%cx           /* cx = scan[0..1] */
119        movw    -3(%ebx,%edi),%ax      /* ax = scan[best_len-1..best_len] */
120        cmp     _good_match,%ebx       /* do we have a good match already? */
121        jb      do_scan
122        shr     $2,%ebp                /* chain_length >>= 2 */
123        jmp     do_scan
124
125        .align  ALIGNMENT
126long_loop:
127/* at this point, edi == scan+2, esi == cur_match */
128        movw    -3(%ebx,%edi),%ax       /* ax = scan[best_len-1..best_len] */
129        movw     -2(%edi),%cx           /* cx = scan[0..1] */
130short_loop:
131/*
132 * at this point, di == scan+2, si == cur_match,
133 * ax = scan[best_len-1..best_len] and cx = scan[0..1]
134 */
135        and     $(WSIZE-1), %esi
136        dec     %ebp                    /* --chain_length */
137        movw    _prev(,%esi,2),%si      /* cur_match = prev[cur_match] */
138                                        /* top word of esi is still 0 */
139        jz      the_end
140        cmp     %edx,%esi               /* cur_match <= limit ? */
141        jbe     the_end
142do_scan:
143        cmpw    _window-1(%ebx,%esi),%ax/* check match at best_len-1 */
144        jne     short_loop
145        cmpw    _window(%esi),%cx       /* check min_match_length match */
146        jne     short_loop
147
148        add     $2+_window,%esi         /* si = match */
149        mov     $((MAX_MATCH>>1)-1),%ecx/* scan for at most MAX_MATCH bytes */
150        mov     %edi,%eax               /* ax = scan+2 */
151        repe;   cmpsw                   /* loop until mismatch */
152        je      maxmatch                /* match of length MAX_MATCH? */
153mismatch:
154        movb    -2(%edi),%cl        /* mismatch on first or second byte? */
155        xchg    %edi,%eax           /* edi = scan+2, eax = end of scan */
156        subb    -2(%esi),%cl        /* cl = 0 if first bytes equal */
157        sub     %edi,%eax           /* eax = len */
158        sub     $2+_window,%esi     /* esi = cur_match + len */
159        sub     %eax,%esi           /* esi = cur_match */
160        subb    $1,%cl              /* set carry if cl == 0 (cannot use DEC) */
161        adc     $0,%eax             /* eax = carry ? len+1 : len */
162        cmp     %ebx,%eax           /* len > best_len ? */
163        jle     long_loop
164        mov     %esi,_match_start       /* match_start = cur_match */
165        mov     %eax,%ebx               /* ebx = best_len = len */
166#ifdef FULL_SEARCH
167        cmp     $(MAX_MATCH),%eax       /* len >= MAX_MATCH ? */
168#else
169        cmp     _nice_match,%eax        /* len >= nice_match ? */
170#endif
171        jl      long_loop
172the_end:
173        mov     %ebx,%eax               /* result = eax = best_len */
174        pop     %ebx
175        pop     %esi
176        pop     %edi
177        pop     %ebp
178        ret
179        .align  ALIGNMENT
180maxmatch:
181        cmpsb
182        jmp     mismatch
183
184#else /* !(i386 || _I386 || _i386 || __i386) */
185
186/* ======================== 680x0 version ================================= */
187
188#if defined(m68k)||defined(mc68k)||defined(__mc68000__)||defined(__MC68000__)
189#  ifndef mc68000
190#    define mc68000
191#  endif
192#endif
193
194#if defined(__mc68020__) || defined(__MC68020__) || defined(sysV68)
195#  ifndef mc68020
196#    define mc68020
197#  endif
198#endif
199
200#if defined(mc68020) || defined(mc68000)
201
202#if (defined(mc68020) || defined(NeXT)) && !defined(UNALIGNED_OK)
203#  define UNALIGNED_OK
204#endif
205
206#ifdef sysV68  /* Try Motorola Delta style */
207
208#  define GLOBAL(symbol)        global  symbol
209#  define TEXT                  text
210#  define FILE(filename)        file    filename
211#  define invert_maybe(src,dst) dst,src
212#  define imm(data)             &data
213#  define reg(register)         %register
214
215#  define addl                  add.l
216#  define addql                 addq.l
217#  define blos                  blo.b
218#  define bhis                  bhi.b
219#  define bras                  bra.b
220#  define clrl                  clr.l
221#  define cmpmb                 cmpm.b
222#  define cmpw                  cmp.w
223#  define cmpl                  cmp.l
224#  define lslw                  lsl.w
225#  define lsrl                  lsr.l
226#  define movel                 move.l
227#  define movew                 move.w
228#  define moveb                 move.b
229#  define moveml                movem.l
230#  define subl                  sub.l
231#  define subw                  sub.w
232#  define subql                 subq.l
233
234#  define IndBase(bd,An)        (bd,An)
235#  define IndBaseNdxl(bd,An,Xn) (bd,An,Xn.l)
236#  define IndBaseNdxw(bd,An,Xn) (bd,An,Xn.w)
237#  define predec(An)            -(An)
238#  define postinc(An)           (An)+
239
240#else /* default style (Sun 3, NeXT, Amiga, Atari) */
241
242#  define GLOBAL(symbol)        .globl  symbol
243#  define TEXT                  .text
244#  define FILE(filename)        .even
245#  define invert_maybe(src,dst) src,dst
246#  if defined(sun) || defined(mc68k)
247#    define imm(data)           #data
248#  else
249#    define imm(data)           \#data
250#  endif
251#  define reg(register)         register
252
253#  define blos                  bcss
254#  if defined(sun) || defined(mc68k)
255#    define movel               movl
256#    define movew               movw
257#    define moveb               movb
258#  endif
259#  define IndBase(bd,An)        An@(bd)
260#  define IndBaseNdxl(bd,An,Xn) An@(bd,Xn:l)
261#  define IndBaseNdxw(bd,An,Xn) An@(bd,Xn:w)
262#  define predec(An)            An@-
263#  define postinc(An)           An@+
264
265#endif  /* styles */
266
267#define Best_Len        reg(d0)         /* unsigned */
268#define Cur_Match       reg(d1)         /* Ipos */
269#define Loop_Counter    reg(d2)         /* int */
270#define Scan_Start      reg(d3)         /* unsigned short */
271#define Scan_End        reg(d4)         /* unsigned short */
272#define Limit           reg(d5)         /* IPos */
273#define Chain_Length    reg(d6)         /* unsigned */
274#define Scan_Test       reg(d7)
275#define Scan            reg(a0)         /* *uch */
276#define Match           reg(a1)         /* *uch */
277#define Prev_Address    reg(a2)         /* *Pos */
278#define Scan_Ini        reg(a3)         /* *uch */
279#define Match_Ini       reg(a4)         /* *uch */
280#define Stack_Pointer   reg(sp)
281
282        GLOBAL  (_match_init)
283        GLOBAL  (_longest_match)
284
285        TEXT
286
287        FILE    ("match.S")
288
289_match_init:
290        rts
291
292/*-----------------------------------------------------------------------
293 * Set match_start to the longest match starting at the given string and
294 * return its length. Matches shorter or equal to prev_length are discarded,
295 * in which case the result is equal to prev_length and match_start is
296 * garbage.
297 * IN assertions: cur_match is the head of the hash chain for the current
298 *   string (strstart) and its distance is <= MAX_DIST, and prev_length >= 1
299 */
300
301/* int longest_match (cur_match) */
302
303#ifdef UNALIGNED_OK
304#  define pushreg       15928           /* d2-d6/a2-a4 */
305#  define popreg        7292
306#else
307#  define pushreg       16184           /* d2-d7/a2-a4 */
308#  define popreg        7420
309#endif
310
311_longest_match:
312        movel   IndBase(4,Stack_Pointer),Cur_Match
313        moveml  imm(pushreg),predec(Stack_Pointer)
314        movel   _max_chain_length,Chain_Length
315        movel   _prev_length,Best_Len
316        movel   imm(_prev),Prev_Address
317        movel   imm(_window+MIN_MATCH),Match_Ini
318        movel   _strstart,Limit
319        movel   Match_Ini,Scan_Ini
320        addl    Limit,Scan_Ini
321        subw    imm(MAX_DIST),Limit
322        bhis    L__limit_ok
323        clrl    Limit
324L__limit_ok:
325        cmpl    invert_maybe(_good_match,Best_Len)
326        blos    L__length_ok
327        lsrl    imm(2),Chain_Length
328L__length_ok:
329        subql   imm(1),Chain_Length
330#ifdef UNALIGNED_OK
331        movew   IndBase(-MIN_MATCH,Scan_Ini),Scan_Start
332        movew   IndBaseNdxw(-MIN_MATCH-1,Scan_Ini,Best_Len),Scan_End
333#else
334        moveb   IndBase(-MIN_MATCH,Scan_Ini),Scan_Start
335        lslw    imm(8),Scan_Start
336        moveb   IndBase(-MIN_MATCH+1,Scan_Ini),Scan_Start
337        moveb   IndBaseNdxw(-MIN_MATCH-1,Scan_Ini,Best_Len),Scan_End
338        lslw    imm(8),Scan_End
339        moveb   IndBaseNdxw(-MIN_MATCH,Scan_Ini,Best_Len),Scan_End
340#endif
341        bras    L__do_scan
342
343L__long_loop:
344#ifdef UNALIGNED_OK
345        movew   IndBaseNdxw(-MIN_MATCH-1,Scan_Ini,Best_Len),Scan_End
346#else
347        moveb   IndBaseNdxw(-MIN_MATCH-1,Scan_Ini,Best_Len),Scan_End
348        lslw    imm(8),Scan_End
349        moveb   IndBaseNdxw(-MIN_MATCH,Scan_Ini,Best_Len),Scan_End
350#endif
351
352L__short_loop:
353        lslw    imm(1),Cur_Match
354        movew   IndBaseNdxl(0,Prev_Address,Cur_Match),Cur_Match
355        cmpw    invert_maybe(Limit,Cur_Match)
356        dbls    Chain_Length,L__do_scan
357        bras    L__return
358
359L__do_scan:
360        movel   Match_Ini,Match
361        addl    Cur_Match,Match
362#ifdef UNALIGNED_OK
363        cmpw    invert_maybe(IndBaseNdxw(-MIN_MATCH-1,Match,Best_Len),Scan_End)
364        bne     L__short_loop
365        cmpw    invert_maybe(IndBase(-MIN_MATCH,Match),Scan_Start)
366        bne     L__short_loop
367#else
368        moveb   IndBaseNdxw(-MIN_MATCH-1,Match,Best_Len),Scan_Test
369        lslw    imm(8),Scan_Test
370        moveb   IndBaseNdxw(-MIN_MATCH,Match,Best_Len),Scan_Test
371        cmpw    invert_maybe(Scan_Test,Scan_End)
372        bne     L__short_loop
373        moveb   IndBase(-MIN_MATCH,Match),Scan_Test
374        lslw    imm(8),Scan_Test
375        moveb   IndBase(-MIN_MATCH+1,Match),Scan_Test
376        cmpw    invert_maybe(Scan_Test,Scan_Start)
377        bne     L__short_loop
378#endif
379
380        movew   imm((MAX_MATCH-MIN_MATCH+1)-1),Loop_Counter
381        movel   Scan_Ini,Scan
382L__scan_loop:
383        cmpmb   postinc(Match),postinc(Scan)
384        dbne    Loop_Counter,L__scan_loop
385
386        subl    Scan_Ini,Scan
387        addql   imm(MIN_MATCH-1),Scan
388        cmpl    invert_maybe(Best_Len,Scan)
389        bls     L__short_loop
390        movel   Scan,Best_Len
391        movel   Cur_Match,_match_start
392#ifdef FULL_SEARCH
393        cmpl    invert_maybe(imm(MAX_MATCH),Best_Len)
394#else
395        cmpl    invert_maybe(_nice_match,Best_Len)
396#endif
397        blos    L__long_loop
398L__return:
399        moveml  postinc(Stack_Pointer),imm(popreg)
400        rts
401
402#else
403 error: this asm version is for 386 or 680x0 only
404#endif /* mc68000 || mc68020 */
405#endif /* i386 || _I386 || _i386 || __i386  */
406
407#endif /* !USE_ZLIB */
408