A set of windows utf8 patches fromJanne Hyvärinen <cse@sci.fi>.
[platform/upstream/flac.git] / src / libFLAC / ia32 / bitreader_asm.nasm
1 ;  vim:filetype=nasm ts=8
2
3 ;  libFLAC - Free Lossless Audio Codec library
4 ;  Copyright (C) 2001,2002,2003,2004,2005,2006,2007,2008,2009  Josh Coalson
5 ;
6 ;  Redistribution and use in source and binary forms, with or without
7 ;  modification, are permitted provided that the following conditions
8 ;  are met:
9 ;
10 ;  - Redistributions of source code must retain the above copyright
11 ;  notice, this list of conditions and the following disclaimer.
12 ;
13 ;  - Redistributions in binary form must reproduce the above copyright
14 ;  notice, this list of conditions and the following disclaimer in the
15 ;  documentation and/or other materials provided with the distribution.
16 ;
17 ;  - Neither the name of the Xiph.org Foundation nor the names of its
18 ;  contributors may be used to endorse or promote products derived from
19 ;  this software without specific prior written permission.
20 ;
21 ;  THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
22 ;  ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
23 ;  LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
24 ;  A PARTICULAR PURPOSE ARE DISCLAIMED.  IN NO EVENT SHALL THE FOUNDATION OR
25 ;  CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL,
26 ;  EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO,
27 ;  PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR
28 ;  PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF
29 ;  LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING
30 ;  NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS
31 ;  SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
32
33 %include "nasm.h"
34
35         data_section
36
37 cextern FLAC__crc16_table               ; unsigned FLAC__crc16_table[256];
38 cextern bitreader_read_from_client_     ; FLAC__bool bitreader_read_from_client_(FLAC__BitReader *br);
39
40 cglobal FLAC__bitreader_read_rice_signed_block_asm_ia32_bswap
41
42         code_section
43
44
45 ; **********************************************************************
46 ;
47 ; void FLAC__bool FLAC__bitreader_read_rice_signed_block(FLAC__BitReader *br, int vals[], unsigned nvals, unsigned parameter)
48 ;
49 ; Some details like assertions and other checking is performed by the caller.
50         ALIGN 16
51 cident FLAC__bitreader_read_rice_signed_block_asm_ia32_bswap
52
53         ;ASSERT(0 != br);
54         ;ASSERT(0 != br->buffer);
55         ; WATCHOUT: code only works if sizeof(brword)==32; we can make things much faster with this assertion
56         ;ASSERT(FLAC__BITS_PER_WORD == 32);
57         ;ASSERT(parameter < 32);
58         ; the above two asserts also guarantee that the binary part never straddles more than 2 words, so we don't have to loop to read it
59
60         ;; peppered throughout the code at major checkpoints are keys like this as to where things are at that point in time
61         ;; [esp + 16]   unsigned parameter
62         ;; [esp + 12]   unsigned nvals
63         ;; [esp + 8]    int vals[]
64         ;; [esp + 4]    FLAC__BitReader *br
65         mov     eax, [esp + 12]         ; if(nvals == 0)
66         test    eax, eax
67         ja      .nvals_gt_0
68         mov     eax, 1                  ;   return true;
69         ret
70
71 .nvals_gt_0:
72         push    ebp
73         push    ebx
74         push    esi
75         push    edi
76         sub     esp, 4
77         ;; [esp + 36]   unsigned parameter
78         ;; [esp + 32]   unsigned nvals
79         ;; [esp + 28]   int vals[]
80         ;; [esp + 24]   FLAC__BitReader *br
81         ;; [esp]        ucbits
82         mov     ebp, [esp + 24]         ; ebp <- br == br->buffer
83         mov     esi, [ebp + 16]         ; esi <- br->consumed_words (aka 'cwords' in the C version)
84         mov     ecx, [ebp + 20]         ; ecx <- br->consumed_bits  (aka 'cbits'  in the C version)
85         xor     edi, edi                ; edi <- 0  'uval'
86         ;; ecx          cbits
87         ;; esi          cwords
88         ;; edi          uval
89         ;; ebp          br
90         ;; [ebp]        br->buffer
91         ;; [ebp + 8]    br->words
92         ;; [ebp + 12]   br->bytes
93         ;; [ebp + 16]   br->consumed_words
94         ;; [ebp + 20]   br->consumed_bits
95         ;; [ebp + 24]   br->read_crc
96         ;; [ebp + 28]   br->crc16_align
97
98                                         ; ucbits = (br->words-cwords)*FLAC__BITS_PER_WORD + br->bytes*8 - cbits;
99         mov     eax, [ebp + 8]          ;   eax <- br->words
100         sub     eax, esi                ;   eax <- br->words-cwords
101         shl     eax, 2                  ;   eax <- (br->words-cwords)*FLAC__BYTES_PER_WORD
102         add     eax, [ebp + 12]         ;   eax <- (br->words-cwords)*FLAC__BYTES_PER_WORD + br->bytes
103         shl     eax, 3                  ;   eax <- (br->words-cwords)*FLAC__BITS_PER_WORD + br->bytes*8
104         sub     eax, ecx                ;   eax <- (br->words-cwords)*FLAC__BITS_PER_WORD + br->bytes*8 - cbits
105         mov     [esp], eax              ;   ucbits <- eax
106
107         ALIGN 16
108 .val_loop:                              ; while(1) {
109
110         ;
111         ; read unary part
112         ;
113 .unary_loop:                            ;   while(1) {
114         ;; ecx          cbits
115         ;; esi          cwords
116         ;; edi          uval
117         ;; ebp          br
118         cmp     esi, [ebp + 8]          ;     while(cwords < br->words)   /* if we've not consumed up to a partial tail word... */
119         jae     near .c1_next1
120 .c1_loop:                               ;     {
121         mov     ebx, [ebp]
122         mov     eax, [ebx + 4*esi]      ;       b = br->buffer[cwords]
123         mov     edx, eax                ;       edx = br->buffer[cwords] (saved for later use)
124         shl     eax, cl                 ;       b = br->buffer[cwords] << cbits
125         test    eax, eax                ;         (still have to test since cbits may be 0, thus ZF not updated for shl eax,0)
126         jz      near .c1_next2          ;       if(b) {
127         bsr     ebx, eax
128         not     ebx
129         and     ebx, 31                 ;         ebx = 'i' = # of leading 0 bits in 'b' (eax)
130         add     ecx, ebx                ;         cbits += i;
131         add     edi, ebx                ;         uval += i;
132         add     ecx, byte 1             ;         cbits++; /* skip over stop bit */
133         test    ecx, ~31
134         jz      near .break1            ;         if(cbits >= FLAC__BITS_PER_WORD) { /* faster way of testing if(cbits == FLAC__BITS_PER_WORD) */
135                                         ;           crc16_update_word_(br, br->buffer[cwords]);
136         push    edi                     ;               [need more registers]
137         bswap   edx                     ;               edx = br->buffer[cwords] swapped; now we can CRC the bytes from LSByte to MSByte which makes things much easier
138         mov     ecx, [ebp + 28]         ;               ecx <- br->crc16_align
139         mov     eax, [ebp + 24]         ;               ax <- br->read_crc (a.k.a. crc)
140 %ifdef FLAC__PUBLIC_NEEDS_UNDERSCORE
141         mov     edi, _FLAC__crc16_table
142 %else
143 %ifdef OBJ_FORMAT_elf
144         mov     edi, [esp + 16]         ;               saved ebx (GOT base)
145         lea     edi, [edi + FLAC__crc16_table wrt ..gotoff]
146 %else
147         mov     edi, FLAC__crc16_table
148 %endif
149 %endif
150         ;; eax (ax)     crc a.k.a. br->read_crc
151         ;; ebx (bl)     intermediate result index into FLAC__crc16_table[]
152         ;; ecx          br->crc16_align
153         ;; edx          byteswapped brword to CRC
154         ;; esi          cwords
155         ;; edi          unsigned FLAC__crc16_table[]
156         ;; ebp          br
157         test    ecx, ecx                ;               switch(br->crc16_align) ...
158         jnz     .c0b4                   ;               [br->crc16_align is 0 the vast majority of the time so we optimize the common case]
159 .c0b0:  xor     dl, ah                  ;               dl <- (crc>>8)^(word>>24)
160         movzx   ebx, dl
161         mov     ecx, [ebx*4 + edi]      ;               cx <- FLAC__crc16_table[(crc>>8)^(word>>24)]
162         shl     eax, 8                  ;               ax <- (crc<<8)
163         xor     eax, ecx                ;               crc <- ax <- (crc<<8) ^ FLAC__crc16_table[(crc>>8)^(word>>24)]
164 .c0b1:  xor     dh, ah                  ;               dh <- (crc>>8)^((word>>16)&0xff))
165         movzx   ebx, dh
166         mov     ecx, [ebx*4 + edi]      ;               cx <- FLAC__crc16_table[(crc>>8)^((word>>16)&0xff))]
167         shl     eax, 8                  ;               ax <- (crc<<8)
168         xor     eax, ecx                ;               crc <- ax <- (crc<<8) ^ FLAC__crc16_table[(crc>>8)^((word>>16)&0xff))]
169         shr     edx, 16
170 .c0b2:  xor     dl, ah                  ;               dl <- (crc>>8)^((word>>8)&0xff))
171         movzx   ebx, dl
172         mov     ecx, [ebx*4 + edi]      ;               cx <- FLAC__crc16_table[(crc>>8)^((word>>8)&0xff))]
173         shl     eax, 8                  ;               ax <- (crc<<8)
174         xor     eax, ecx                ;               crc <- ax <- (crc<<8) ^ FLAC__crc16_table[(crc>>8)^((word>>8)&0xff))]
175 .c0b3:  xor     dh, ah                  ;               dh <- (crc>>8)^(word&0xff)
176         movzx   ebx, dh
177         mov     ecx, [ebx*4 + edi]      ;               cx <- FLAC__crc16_table[(crc>>8)^(word&0xff)]
178         shl     eax, 8                  ;               ax <- (crc<<8)
179         xor     eax, ecx                ;               crc <- ax <- (crc<<8) ^ FLAC__crc16_table[(crc>>8)^(word&0xff)]
180         movzx   eax, ax
181         mov     [ebp + 24], eax         ;               br->read_crc <- crc
182         pop     edi
183
184         add     esi, byte 1             ;           cwords++;
185         xor     ecx, ecx                ;           cbits = 0;
186                                         ;         }
187         jmp     near .break1            ;         goto break1;
188         ;; this section relocated out of the way for performance
189 .c0b4:
190         mov     [ebp + 28], dword 0     ;               br->crc16_align <- 0
191         cmp     ecx, 8
192         je      .c0b1
193         shr     edx, 16
194         cmp     ecx, 16
195         je      .c0b2
196         jmp     .c0b3
197
198         ;; this section relocated out of the way for performance
199 .c1b4:
200         mov     [ebp + 28], dword 0     ;               br->crc16_align <- 0
201         cmp     ecx, 8
202         je      .c1b1
203         shr     edx, 16
204         cmp     ecx, 16
205         je      .c1b2
206         jmp     .c1b3
207
208 .c1_next2:                              ;       } else {
209         ;; ecx          cbits
210         ;; edx          current brword 'b'
211         ;; esi          cwords
212         ;; edi          uval
213         ;; ebp          br
214         add     edi, 32
215         sub     edi, ecx                ;         uval += FLAC__BITS_PER_WORD - cbits;
216                                         ;         crc16_update_word_(br, br->buffer[cwords]);
217         push    edi                     ;               [need more registers]
218         bswap   edx                     ;               edx = br->buffer[cwords] swapped; now we can CRC the bytes from LSByte to MSByte which makes things much easier
219         mov     ecx, [ebp + 28]         ;               ecx <- br->crc16_align
220         mov     eax, [ebp + 24]         ;               ax <- br->read_crc (a.k.a. crc)
221 %ifdef FLAC__PUBLIC_NEEDS_UNDERSCORE
222         mov     edi, _FLAC__crc16_table
223 %else
224 %ifdef OBJ_FORMAT_elf
225         mov     edi, [esp + 16]         ;               saved ebx (GOT base)
226         lea     edi, [edi + FLAC__crc16_table wrt ..gotoff]
227 %else
228         mov     edi, FLAC__crc16_table
229 %endif
230 %endif
231         ;; eax (ax)     crc a.k.a. br->read_crc
232         ;; ebx (bl)     intermediate result index into FLAC__crc16_table[]
233         ;; ecx          br->crc16_align
234         ;; edx          byteswapped brword to CRC
235         ;; esi          cwords
236         ;; edi          unsigned FLAC__crc16_table[]
237         ;; ebp          br
238         test    ecx, ecx                ;               switch(br->crc16_align) ...
239         jnz     .c1b4                   ;               [br->crc16_align is 0 the vast majority of the time so we optimize the common case]
240 .c1b0:  xor     dl, ah                  ;               dl <- (crc>>8)^(word>>24)
241         movzx   ebx, dl
242         mov     ecx, [ebx*4 + edi]      ;               cx <- FLAC__crc16_table[(crc>>8)^(word>>24)]
243         shl     eax, 8                  ;               ax <- (crc<<8)
244         xor     eax, ecx                ;               crc <- ax <- (crc<<8) ^ FLAC__crc16_table[(crc>>8)^(word>>24)]
245 .c1b1:  xor     dh, ah                  ;               dh <- (crc>>8)^((word>>16)&0xff))
246         movzx   ebx, dh
247         mov     ecx, [ebx*4 + edi]      ;               cx <- FLAC__crc16_table[(crc>>8)^((word>>16)&0xff))]
248         shl     eax, 8                  ;               ax <- (crc<<8)
249         xor     eax, ecx                ;               crc <- ax <- (crc<<8) ^ FLAC__crc16_table[(crc>>8)^((word>>16)&0xff))]
250         shr     edx, 16
251 .c1b2:  xor     dl, ah                  ;               dl <- (crc>>8)^((word>>8)&0xff))
252         movzx   ebx, dl
253         mov     ecx, [ebx*4 + edi]      ;               cx <- FLAC__crc16_table[(crc>>8)^((word>>8)&0xff))]
254         shl     eax, 8                  ;               ax <- (crc<<8)
255         xor     eax, ecx                ;               crc <- ax <- (crc<<8) ^ FLAC__crc16_table[(crc>>8)^((word>>8)&0xff))]
256 .c1b3:  xor     dh, ah                  ;               dh <- (crc>>8)^(word&0xff)
257         movzx   ebx, dh
258         mov     ecx, [ebx*4 + edi]      ;               cx <- FLAC__crc16_table[(crc>>8)^(word&0xff)]
259         shl     eax, 8                  ;               ax <- (crc<<8)
260         xor     eax, ecx                ;               crc <- ax <- (crc<<8) ^ FLAC__crc16_table[(crc>>8)^(word&0xff)]
261         movzx   eax, ax
262         mov     [ebp + 24], eax         ;               br->read_crc <- crc
263         pop     edi
264
265         add     esi, byte 1             ;         cwords++;
266         xor     ecx, ecx                ;         cbits = 0;
267                                         ;         /* didn't find stop bit yet, have to keep going... */
268                                         ;       }
269
270         cmp     esi, [ebp + 8]          ;     } while(cwords < br->words)   /* if we've not consumed up to a partial tail word... */
271         jb      near .c1_loop
272
273 .c1_next1:
274         ; at this point we've eaten up all the whole words; have to try
275         ; reading through any tail bytes before calling the read callback.
276         ; this is a repeat of the above logic adjusted for the fact we
277         ; don't have a whole word.  note though if the client is feeding
278         ; us data a byte at a time (unlikely), br->consumed_bits may not
279         ; be zero.
280         ;; ecx          cbits
281         ;; esi          cwords
282         ;; edi          uval
283         ;; ebp          br
284         mov     edx, [ebp + 12]         ;     edx <- br->bytes
285         shl     edx, 3                  ;     edx <- br->bytes*8
286         cmp     edx, ecx
287         jbe     .read1                  ;     if(br->bytes*8 > cbits) {  [NOTE: this case is rare so it doesn't have to be all that fast ]
288         mov     ebx, [ebp]
289                                         ;       edx <- const unsigned end = br->bytes * 8;
290         mov     eax, [ebx + 4*esi]      ;       b = br->buffer[cwords]
291         xchg    edx, ecx                ;       [edx <- cbits , ecx <- end]
292         mov     ebx, 0xffffffff         ;       ebx <- FLAC__WORD_ALL_ONES
293         shr     ebx, cl                 ;       ebx <- FLAC__WORD_ALL_ONES >> end
294         not     ebx                     ;       ebx <- ~(FLAC__WORD_ALL_ONES >> end)
295         xchg    edx, ecx                ;       [edx <- end , ecx <- cbits]
296         and     eax, ebx                ;       b = (br->buffer[cwords] & ~(FLAC__WORD_ALL_ONES >> end));
297         shl     eax, cl                 ;       b = (br->buffer[cwords] & ~(FLAC__WORD_ALL_ONES >> end)) << cbits;
298         test    eax, eax                ;         (still have to test since cbits may be 0, thus ZF not updated for shl eax,0)
299         jz      .c1_next3               ;       if(b) {
300         bsr     ebx, eax
301         not     ebx
302         and     ebx, 31                 ;         ebx = 'i' = # of leading 0 bits in 'b' (eax)
303         add     ecx, ebx                ;         cbits += i;
304         add     edi, ebx                ;         uval += i;
305         add     ecx, byte 1             ;         cbits++; /* skip over stop bit */
306         jmp     short .break1           ;         goto break1;
307 .c1_next3:                              ;       } else {
308         sub     edi, ecx
309         add     edi, edx                ;         uval += end - cbits;
310         mov     ecx, edx                ;         cbits = end
311                                         ;         /* didn't find stop bit yet, have to keep going... */
312                                         ;       }
313                                         ;     }
314 .read1:
315         ; flush registers and read; bitreader_read_from_client_() does
316         ; not touch br->consumed_bits at all but we still need to set
317         ; it in case it fails and we have to return false.
318         ;; ecx          cbits
319         ;; esi          cwords
320         ;; edi          uval
321         ;; ebp          br
322         mov     [ebp + 16], esi         ;     br->consumed_words = cwords;
323         mov     [ebp + 20], ecx         ;     br->consumed_bits = cbits;
324         push    ecx                     ;     /* save */
325         push    ebp                     ;     /* push br argument */
326 %ifdef FLAC__PUBLIC_NEEDS_UNDERSCORE
327         call    _bitreader_read_from_client_
328 %else
329 %ifdef OBJ_FORMAT_elf
330         mov     ebx, [esp + 20]         ;               saved ebx (GOT base)
331         call    bitreader_read_from_client_ wrt ..plt
332 %else
333         call    bitreader_read_from_client_
334 %endif
335 %endif
336         pop     edx                     ;     /* discard, unused */
337         pop     ecx                     ;     /* restore */
338         mov     esi, [ebp + 16]         ;     cwords = br->consumed_words;
339                                         ;     ucbits = (br->words-cwords)*FLAC__BITS_PER_WORD + br->bytes*8 - cbits;
340         mov     ebx, [ebp + 8]          ;       ebx <- br->words
341         sub     ebx, esi                ;       ebx <- br->words-cwords
342         shl     ebx, 2                  ;       ebx <- (br->words-cwords)*FLAC__BYTES_PER_WORD
343         add     ebx, [ebp + 12]         ;       ebx <- (br->words-cwords)*FLAC__BYTES_PER_WORD + br->bytes
344         shl     ebx, 3                  ;       ebx <- (br->words-cwords)*FLAC__BITS_PER_WORD + br->bytes*8
345         sub     ebx, ecx                ;       ebx <- (br->words-cwords)*FLAC__BITS_PER_WORD + br->bytes*8 - cbits
346         add     ebx, edi                ;       ebx <- (br->words-cwords)*FLAC__BITS_PER_WORD + br->bytes*8 - cbits + uval
347                                         ;           + uval to offset our count by the # of unary bits already
348                                         ;           consumed before the read, because we will add these back
349                                         ;           in all at once at break1
350         mov     [esp], ebx              ;       ucbits <- ebx
351         test    eax, eax                ;     if(!bitreader_read_from_client_(br))
352         jnz     near .unary_loop
353         jmp     .end                    ;       return false; /* eax (the return value) is already 0 */
354                                         ;   } /* end while(1) unary part */
355
356         ALIGN 16
357 .break1:
358         ;; ecx          cbits
359         ;; esi          cwords
360         ;; edi          uval
361         ;; ebp          br
362         ;; [esp]        ucbits
363         sub     [esp], edi              ;   ucbits -= uval;
364         sub     dword [esp], byte 1     ;   ucbits--; /* account for stop bit */
365
366         ;
367         ; read binary part
368         ;
369         mov     ebx, [esp + 36]         ;   ebx <- parameter
370         test    ebx, ebx                ;   if(parameter) {
371         jz      near .break2
372 .read2:
373         cmp     [esp], ebx              ;     while(ucbits < parameter) {
374         jae     .c2_next1
375         ; flush registers and read; bitreader_read_from_client_() does
376         ; not touch br->consumed_bits at all but we still need to set
377         ; it in case it fails and we have to return false.
378         mov     [ebp + 16], esi         ;       br->consumed_words = cwords;
379         mov     [ebp + 20], ecx         ;       br->consumed_bits = cbits;
380         push    ecx                     ;       /* save */
381         push    ebx                     ;       /* save */
382         push    ebp                     ;       /* push br argument */
383 %ifdef FLAC__PUBLIC_NEEDS_UNDERSCORE
384         call    _bitreader_read_from_client_
385 %else
386 %ifdef OBJ_FORMAT_elf
387         mov     ebx, [esp + 24]         ;               saved ebx (GOT base)
388         call    bitreader_read_from_client_ wrt ..plt
389 %else
390         call    bitreader_read_from_client_
391 %endif
392 %endif
393         pop     edx                     ;       /* discard, unused */
394         pop     ebx                     ;       /* restore */
395         pop     ecx                     ;       /* restore */
396         mov     esi, [ebp + 16]         ;       cwords = br->consumed_words;
397                                         ;       ucbits = (br->words-cwords)*FLAC__BITS_PER_WORD + br->bytes*8 - cbits;
398         mov     edx, [ebp + 8]          ;         edx <- br->words
399         sub     edx, esi                ;         edx <- br->words-cwords
400         shl     edx, 2                  ;         edx <- (br->words-cwords)*FLAC__BYTES_PER_WORD
401         add     edx, [ebp + 12]         ;         edx <- (br->words-cwords)*FLAC__BYTES_PER_WORD + br->bytes
402         shl     edx, 3                  ;         edx <- (br->words-cwords)*FLAC__BITS_PER_WORD + br->bytes*8
403         sub     edx, ecx                ;         edx <- (br->words-cwords)*FLAC__BITS_PER_WORD + br->bytes*8 - cbits
404         mov     [esp], edx              ;         ucbits <- edx
405         test    eax, eax                ;       if(!bitreader_read_from_client_(br))
406         jnz     .read2
407         jmp     .end                    ;         return false; /* eax (the return value) is already 0 */
408                                         ;     }
409 .c2_next1:
410         ;; ebx          parameter
411         ;; ecx          cbits
412         ;; esi          cwords
413         ;; edi          uval
414         ;; ebp          br
415         ;; [esp]        ucbits
416         cmp     esi, [ebp + 8]          ;     if(cwords < br->words) { /* if we've not consumed up to a partial tail word... */
417         jae     near .c2_next2
418         test    ecx, ecx                ;       if(cbits) {
419         jz      near .c2_next3          ;         /* this also works when consumed_bits==0, it's just a little slower than necessary for that case */
420         mov     eax, 32
421         mov     edx, [ebp]
422         sub     eax, ecx                ;         const unsigned n = FLAC__BITS_PER_WORD - cbits;
423         mov     edx, [edx + 4*esi]      ;         const brword word = br->buffer[cwords];
424         cmp     ebx, eax                ;         if(parameter < n) {
425         jae     .c2_next4
426                                         ;           uval <<= parameter;
427                                         ;           uval |= (word & (FLAC__WORD_ALL_ONES >> cbits)) >> (n-parameter);
428         shl     edx, cl
429         xchg    ebx, ecx
430         shld    edi, edx, cl
431         add     ebx, ecx                ;           cbits += parameter;
432         xchg    ebx, ecx                ;           ebx <- parameter, ecx <- cbits
433         jmp     .break2                 ;           goto break2;
434                                         ;         }
435 .c2_next4:
436                                         ;         uval <<= n;
437                                         ;         uval |= word & (FLAC__WORD_ALL_ONES >> cbits);
438 %if 1
439         rol     edx, cl                 ;            @@@@@@OPT: may be faster to use rol to save edx so we can restore it for CRC'ing
440                                         ;            @@@@@@OPT: or put parameter in ch instead and free up ebx completely again
441 %else
442         shl     edx, cl
443 %endif
444         xchg    eax, ecx
445         shld    edi, edx, cl
446         xchg    eax, ecx
447 %if 1
448         ror     edx, cl                 ;            restored.
449 %else
450         mov     edx, [ebp]
451         mov     edx, [edx + 4*esi]
452 %endif
453                                         ;         crc16_update_word_(br, br->buffer[cwords]);
454         push    edi                     ;               [need more registers]
455         push    ebx                     ;               [need more registers]
456         push    eax                     ;               [need more registers]
457         bswap   edx                     ;               edx = br->buffer[cwords] swapped; now we can CRC the bytes from LSByte to MSByte which makes things much easier
458         mov     ecx, [ebp + 28]         ;               ecx <- br->crc16_align
459         mov     eax, [ebp + 24]         ;               ax <- br->read_crc (a.k.a. crc)
460 %ifdef FLAC__PUBLIC_NEEDS_UNDERSCORE
461         mov     edi, _FLAC__crc16_table
462 %else
463 %ifdef OBJ_FORMAT_elf
464         mov     edi, [esp + 24]         ;               saved ebx (GOT base)
465         lea     edi, [edi + FLAC__crc16_table wrt ..gotoff]
466 %else
467         mov     edi, FLAC__crc16_table
468 %endif
469 %endif
470         ;; eax (ax)     crc a.k.a. br->read_crc
471         ;; ebx (bl)     intermediate result index into FLAC__crc16_table[]
472         ;; ecx          br->crc16_align
473         ;; edx          byteswapped brword to CRC
474         ;; esi          cwords
475         ;; edi          unsigned FLAC__crc16_table[]
476         ;; ebp          br
477         test    ecx, ecx                ;               switch(br->crc16_align) ...
478         jnz     .c2b4                   ;               [br->crc16_align is 0 the vast majority of the time so we optimize the common case]
479 .c2b0:  xor     dl, ah                  ;               dl <- (crc>>8)^(word>>24)
480         movzx   ebx, dl
481         mov     ecx, [ebx*4 + edi]      ;               cx <- FLAC__crc16_table[(crc>>8)^(word>>24)]
482         shl     eax, 8                  ;               ax <- (crc<<8)
483         xor     eax, ecx                ;               crc <- ax <- (crc<<8) ^ FLAC__crc16_table[(crc>>8)^(word>>24)]
484 .c2b1:  xor     dh, ah                  ;               dh <- (crc>>8)^((word>>16)&0xff))
485         movzx   ebx, dh
486         mov     ecx, [ebx*4 + edi]      ;               cx <- FLAC__crc16_table[(crc>>8)^((word>>16)&0xff))]
487         shl     eax, 8                  ;               ax <- (crc<<8)
488         xor     eax, ecx                ;               crc <- ax <- (crc<<8) ^ FLAC__crc16_table[(crc>>8)^((word>>16)&0xff))]
489         shr     edx, 16
490 .c2b2:  xor     dl, ah                  ;               dl <- (crc>>8)^((word>>8)&0xff))
491         movzx   ebx, dl
492         mov     ecx, [ebx*4 + edi]      ;               cx <- FLAC__crc16_table[(crc>>8)^((word>>8)&0xff))]
493         shl     eax, 8                  ;               ax <- (crc<<8)
494         xor     eax, ecx                ;               crc <- ax <- (crc<<8) ^ FLAC__crc16_table[(crc>>8)^((word>>8)&0xff))]
495 .c2b3:  xor     dh, ah                  ;               dh <- (crc>>8)^(word&0xff)
496         movzx   ebx, dh
497         mov     ecx, [ebx*4 + edi]      ;               cx <- FLAC__crc16_table[(crc>>8)^(word&0xff)]
498         shl     eax, 8                  ;               ax <- (crc<<8)
499         xor     eax, ecx                ;               crc <- ax <- (crc<<8) ^ FLAC__crc16_table[(crc>>8)^(word&0xff)]
500         movzx   eax, ax
501         mov     [ebp + 24], eax         ;               br->read_crc <- crc
502         pop     eax
503         pop     ebx
504         pop     edi
505         add     esi, byte 1             ;         cwords++;
506         mov     ecx, ebx
507         sub     ecx, eax                ;         cbits = parameter - n;
508         jz      .break2                 ;         if(cbits) { /* parameter > n, i.e. if there are still bits left to read, there have to be less than 32 so they will all be in the next word */
509                                         ;           uval <<= cbits;
510                                         ;           uval |= (br->buffer[cwords] >> (FLAC__BITS_PER_WORD-cbits));
511         mov     eax, [ebp]
512         mov     eax, [eax + 4*esi]
513         shld    edi, eax, cl
514                                         ;         }
515         jmp     .break2                 ;         goto break2;
516
517         ;; this section relocated out of the way for performance
518 .c2b4:
519         mov     [ebp + 28], dword 0     ;               br->crc16_align <- 0
520         cmp     ecx, 8
521         je      .c2b1
522         shr     edx, 16
523         cmp     ecx, 16
524         je      .c2b2
525         jmp     .c2b3
526
527 .c2_next3:                              ;       } else {
528         mov     ecx, ebx                ;         cbits = parameter;
529                                         ;         uval <<= cbits;
530                                         ;         uval |= (br->buffer[cwords] >> (FLAC__BITS_PER_WORD-cbits));
531         mov     eax, [ebp]
532         mov     eax, [eax + 4*esi]
533         shld    edi, eax, cl
534         jmp     .break2                 ;         goto break2;
535                                         ;       }
536 .c2_next2:                              ;     } else {
537         ; in this case we're starting our read at a partial tail word;
538         ; the reader has guaranteed that we have at least 'parameter'
539         ; bits available to read, which makes this case simpler.
540                                         ;       uval <<= parameter;
541                                         ;       if(cbits) {
542                                         ;         /* this also works when consumed_bits==0, it's just a little slower than necessary for that case */
543                                         ;         uval |= (br->buffer[cwords] & (FLAC__WORD_ALL_ONES >> cbits)) >> (FLAC__BITS_PER_WORD-cbits-parameter);
544                                         ;         cbits += parameter;
545                                         ;         goto break2;
546                                         ;       } else {
547                                         ;         cbits = parameter;
548                                         ;         uval |= br->buffer[cwords] >> (FLAC__BITS_PER_WORD-cbits);
549                                         ;         goto break2;
550                                         ;       }
551                                         ;       the above is much shorter in assembly:
552         mov     eax, [ebp]
553         mov     eax, [eax + 4*esi]      ;       eax <- br->buffer[cwords]
554         shl     eax, cl                 ;       eax <- br->buffer[cwords] << cbits
555         add     ecx, ebx                ;       cbits += parameter
556         xchg    ebx, ecx                ;       ebx <- cbits, ecx <- parameter
557         shld    edi, eax, cl            ;       uval <<= parameter <<< 'parameter' bits of tail word
558         xchg    ebx, ecx                ;       ebx <- parameter, ecx <- cbits
559                                         ;     }
560                                         ;   }
561 .break2:
562         sub     [esp], ebx              ;   ucbits -= parameter;
563
564         ;
565         ; compose the value
566         ;
567         mov     ebx, [esp + 28]         ;   ebx <- vals
568         mov     edx, edi                ;   edx <- uval
569         and     edi, 1                  ;   edi <- uval & 1
570         shr     edx, 1                  ;   edx <- uval >> 1
571         neg     edi                     ;   edi <- -(int)(uval & 1)
572         xor     edx, edi                ;   edx <- (uval >> 1 ^ -(int)(uval & 1))
573         mov     [ebx], edx              ;   *vals <- edx
574         sub     dword [esp + 32], byte 1        ;   --nvals;
575         jz      .finished               ;   if(nvals == 0) /* jump to finish */
576         xor     edi, edi                ;   uval = 0;
577         add     dword [esp + 28], 4     ;   ++vals
578         jmp     .val_loop               ; }
579
580 .finished:
581         mov     [ebp + 16], esi         ; br->consumed_words = cwords;
582         mov     [ebp + 20], ecx         ; br->consumed_bits = cbits;
583         mov     eax, 1
584 .end:
585         add     esp, 4
586         pop     edi
587         pop     esi
588         pop     ebx
589         pop     ebp
590         ret
591
592 end