1 /*
2  * WMA compatible decoder
3  * Copyright (c) 2002 The FFmpeg Project.
4  *
5  * This library is free software; you can redistribute it and/or
6  * modify it under the terms of the GNU Lesser General Public
7  * License as published by the Free Software Foundation; either
8  * version 2 of the License, or (at your option) any later version.
9  *
10  * This library is distributed in the hope that it will be useful,
11  * but WITHOUT ANY WARRANTY; without even the implied warranty of
12  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
13  * Lesser General Public License for more details.
14  *
15  * You should have received a copy of the GNU Lesser General Public
16  * License along with this library; if not, write to the Free Software
17  * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
18  */
19 
20 /**
21  * @file wmadec.c
22  * WMA compatible decoder.
23  */
24 
25 #include <libasf/asf.h>
26 #include "wmadec.h"
27 #include "wmafixed.h"
28 #include "wmadata.h"
29 
30 //#define trace(...) { fprintf (stderr, __VA_ARGS__); }
31 #define trace(fmt,...)
32 #define DEBUGF trace
33 
34 static void wma_lsp_to_curve_init(WMADecodeContext *s, int frame_len);
35 
36 /*declarations of statically allocated variables used to remove malloc calls*/
37 
38 # define IBSS_ATTR
39 
40 /*MDCT reconstruction windows*/
41 static fixed32 stat0[2048] IBSS_ATTR_WMA_XL_IRAM MEM_ALIGN_ATTR;
42 static fixed32 stat1[1024] IBSS_ATTR_WMA_XL_IRAM MEM_ALIGN_ATTR;
43 static fixed32 stat2[ 512] IBSS_ATTR_WMA_XL_IRAM MEM_ALIGN_ATTR;
44 static fixed32 stat3[ 256] IBSS_ATTR_WMA_XL_IRAM MEM_ALIGN_ATTR;
45 static fixed32 stat4[ 128] IBSS_ATTR_WMA_XL_IRAM MEM_ALIGN_ATTR;
46 
47 /*VLC lookup tables*/
48 static uint16_t *runtabarray[2];
49 static uint16_t *levtabarray[2];
50 
51 static uint16_t runtab_big[1336]   MEM_ALIGN_ATTR;
52 static uint16_t runtab_small[1072] MEM_ALIGN_ATTR;
53 static uint16_t levtab_big[1336]   MEM_ALIGN_ATTR;
54 static uint16_t levtab_small[1072] MEM_ALIGN_ATTR;
55 
56 #define VLCBUF1SIZE 4598
57 #define VLCBUF2SIZE 3574
58 #define VLCBUF3SIZE 360
59 #define VLCBUF4SIZE 540
60 
61 /*putting these in IRAM actually makes PP slower*/
62 
63 static VLC_TYPE vlcbuf1[VLCBUF1SIZE][2] IBSS_ATTR_WMA_XL_IRAM MEM_ALIGN_ATTR;
64 static VLC_TYPE vlcbuf2[VLCBUF2SIZE][2] MEM_ALIGN_ATTR;
65 /* This buffer gets reused for lsp tables */
66 static VLC_TYPE vlcbuf3[VLCBUF3SIZE][2] MEM_ALIGN_ATTR;
67 static VLC_TYPE vlcbuf4[VLCBUF4SIZE][2] MEM_ALIGN_ATTR;
68 
69 
70 
71 
72 /**
73   * Apply MDCT window and add into output.
74   *
75   * We ensure that when the windows overlap their squared sum
76   * is always 1 (MDCT reconstruction rule).
77   *
78   * The Vorbis I spec has a great diagram explaining this process.
79   * See section 1.3.2.3 of http://xiph.org/vorbis/doc/Vorbis_I_spec.html
80   */
wma_window(WMADecodeContext * s,fixed32 * in,fixed32 * out)81  static void wma_window(WMADecodeContext *s, fixed32 *in, fixed32 *out)
82  {
83      //float *in = s->output;
84      int block_len, bsize, n;
85 
86      /* left part */
87 
88      /* previous block was larger, so we'll use the size of the current
89       * block to set the window size*/
90      if (s->block_len_bits <= s->prev_block_len_bits) {
91          block_len = s->block_len;
92          bsize = s->frame_len_bits - s->block_len_bits;
93 
94          vector_fmul_add_add(out, in, s->windows[bsize], block_len);
95 
96      } else {
97          /*previous block was smaller or the same size, so use it's size to set the window length*/
98          block_len = 1 << s->prev_block_len_bits;
99          /*find the middle of the two overlapped blocks, this will be the first overlapped sample*/
100          n = (s->block_len - block_len) / 2;
101          bsize = s->frame_len_bits - s->prev_block_len_bits;
102 
103          vector_fmul_add_add(out+n, in+n, s->windows[bsize],  block_len);
104 
105          memcpy(out+n+block_len, in+n+block_len, n*sizeof(fixed32));
106      }
107     /* Advance to the end of the current block and prepare to window it for the next block.
108      * Since the window function needs to be reversed, we do it backwards starting with the
109      * last sample and moving towards the first
110      */
111      out += s->block_len;
112      in += s->block_len;
113 
114      /* right part */
115      if (s->block_len_bits <= s->next_block_len_bits) {
116          block_len = s->block_len;
117          bsize = s->frame_len_bits - s->block_len_bits;
118 
119          vector_fmul_reverse(out, in, s->windows[bsize], block_len);
120 
121      } else {
122          block_len = 1 << s->next_block_len_bits;
123          n = (s->block_len - block_len) / 2;
124          bsize = s->frame_len_bits - s->next_block_len_bits;
125 
126          memcpy(out, in, n*sizeof(fixed32));
127 
128          vector_fmul_reverse(out+n, in+n, s->windows[bsize], block_len);
129 
130          memset(out+n+block_len, 0, n*sizeof(fixed32));
131      }
132  }
133 
134 
135 
136 
137 /* XXX: use same run/length optimization as mpeg decoders */
init_coef_vlc(VLC * vlc,uint16_t ** prun_table,uint16_t ** plevel_table,const CoefVLCTable * vlc_table,int tab)138 static void init_coef_vlc(VLC *vlc,
139                           uint16_t **prun_table, uint16_t **plevel_table,
140                           const CoefVLCTable *vlc_table, int tab)
141 {
142     int n = vlc_table->n;
143     const uint8_t *table_bits = vlc_table->huffbits;
144     const uint32_t *table_codes = vlc_table->huffcodes;
145     const uint16_t *levels_table = vlc_table->levels;
146     uint16_t *run_table, *level_table;
147     const uint16_t *p;
148     int i, l, j, level;
149 
150 
151     init_vlc(vlc, VLCBITS, n, table_bits, 1, 1, table_codes, 4, 4, INIT_VLC_USE_NEW_STATIC);
152 
153     run_table = runtabarray[tab];
154     level_table= levtabarray[tab];
155 
156     p = levels_table;
157     i = 2;
158     level = 1;
159     while (i < n)
160     {
161         l = *p++;
162         for(j=0;j<l;++j)
163         {
164             run_table[i] = j;
165             level_table[i] = level;
166             ++i;
167         }
168         ++level;
169     }
170     *prun_table = run_table;
171     *plevel_table = level_table;
172 }
173 
174 const uint8_t ff_log2_tab[256]={
175         0,0,1,1,2,2,2,2,3,3,3,3,3,3,3,3,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,
176         5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,
177         6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,
178         6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,6,
179         7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,
180         7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,
181         7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,
182         7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7
183 };
184 
185 
186 #define av_log2       av_log2_c
av_log2_c(unsigned int v)187 static inline av_const int av_log2_c(unsigned int v)
188 {
189     int n = 0;
190     if (v & 0xffff0000) {
191         v >>= 16;
192         n += 16;
193     }
194     if (v & 0xff00) {
195         v >>= 8;
196         n += 8;
197     }
198     n += ff_log2_tab[v];
199 
200     return n;
201 }
202 
203 
wma_decode_init(WMADecodeContext * s,asf_waveformatex_t * wfx)204 int wma_decode_init(WMADecodeContext* s, asf_waveformatex_t *wfx)
205 {
206 
207     int i, flags2;
208     fixed32 *window;
209     uint8_t *extradata;
210     fixed64 bps1;
211     fixed32 high_freq;
212     fixed64 bps;
213     int sample_rate1;
214     int coef_vlc_table;
215     //    int filehandle;
216     #ifdef CPU_COLDFIRE
217     coldfire_set_macsr(EMAC_FRACTIONAL | EMAC_SATURATE);
218     #endif
219 
220     /*clear stereo setting to avoid glitches when switching stereo->mono*/
221     s->channel_coded[0]=0;
222     s->channel_coded[1]=0;
223     s->ms_stereo=0;
224 
225     s->sample_rate = wfx->rate;
226     s->nb_channels = wfx->channels;
227     s->bit_rate = wfx->bitrate;
228     s->block_align = wfx->blockalign;
229     trace ("wma samplerate: %d\n", wfx->rate);
230 
231     if (wfx->codec_id == ASF_CODEC_ID_WMAV1) {
232         s->version = 1;
233     } else if (wfx->codec_id == ASF_CODEC_ID_WMAV2 ) {
234         s->version = 2;
235     } else {
236         /*one of those other wma flavors that don't have GPLed decoders */
237         trace ("invalid wma codec id: %d\n", wfx->codec_id);
238         return -1;
239     }
240 
241     trace ("wma version: %d\n", s->version);
242 
243     /* extract flag infos */
244     flags2 = 0;
245     extradata = wfx->data;
246     if (s->version == 1 && wfx->datalen >= 4) {
247         flags2 = extradata[2] | (extradata[3] << 8);
248     }else if (s->version == 2 && wfx->datalen >= 6){
249         flags2 = extradata[4] | (extradata[5] << 8);
250     }
251     s->use_exp_vlc = flags2 & 0x0001;
252     s->use_bit_reservoir = flags2 & 0x0002;
253     s->use_variable_block_len = flags2 & 0x0004;
254 
255     /* compute MDCT block size */
256     if (s->sample_rate <= 16000){
257         s->frame_len_bits = 9;
258     }else if (s->sample_rate <= 22050 ||
259              (s->sample_rate <= 32000 && s->version == 1)){
260         s->frame_len_bits = 10;
261     }else{
262         s->frame_len_bits = 11;
263     }
264     s->frame_len = 1 << s->frame_len_bits;
265     if (s-> use_variable_block_len)
266     {
267         int nb_max, nb;
268         nb = ((flags2 >> 3) & 3) + 1;
269         if ((s->bit_rate / s->nb_channels) >= 32000)
270         {
271             nb += 2;
272         }
273         nb_max = s->frame_len_bits - BLOCK_MIN_BITS;        //max is 11-7
274         if (nb > nb_max)
275             nb = nb_max;
276         s->nb_block_sizes = nb + 1;
277     }
278     else
279     {
280         s->nb_block_sizes = 1;
281     }
282 
283     /* init rate dependant parameters */
284     s->use_noise_coding = 1;
285     high_freq = itofix64(s->sample_rate) >> 1;
286 
287 
288     /* if version 2, then the rates are normalized */
289     sample_rate1 = s->sample_rate;
290     if (s->version == 2)
291     {
292         if (sample_rate1 >= 44100)
293             sample_rate1 = 44100;
294         else if (sample_rate1 >= 22050)
295             sample_rate1 = 22050;
296         else if (sample_rate1 >= 16000)
297             sample_rate1 = 16000;
298         else if (sample_rate1 >= 11025)
299             sample_rate1 = 11025;
300         else if (sample_rate1 >= 8000)
301             sample_rate1 = 8000;
302     }
303 
304     fixed64 tmp = itofix64(s->bit_rate);
305     fixed64 tmp2 = itofix64(s->nb_channels * s->sample_rate);
306     bps = fixdiv64(tmp, tmp2);
307     fixed64 tim = bps * s->frame_len;
308     fixed64 tmpi = fixdiv64(tim,itofix64(8));
309     s->byte_offset_bits = av_log2(fixtoi64(tmpi+0x8000)) + 2;
310 
311     /* compute high frequency value and choose if noise coding should
312        be activated */
313     bps1 = bps;
314     if (s->nb_channels == 2)
315         bps1 = fixmul32(bps,0x1999a);
316     if (sample_rate1 == 44100)
317     {
318         if (bps1 >= 0x9c29)
319             s->use_noise_coding = 0;
320         else
321             high_freq = fixmul32(high_freq,0x6666);
322     }
323     else if (sample_rate1 == 22050)
324     {
325         if (bps1 >= 0x128f6)
326             s->use_noise_coding = 0;
327         else if (bps1 >= 0xb852)
328             high_freq = fixmul32(high_freq,0xb333);
329         else
330             high_freq = fixmul32(high_freq,0x999a);
331     }
332     else if (sample_rate1 == 16000)
333     {
334         if (bps > 0x8000)
335             high_freq = fixmul32(high_freq,0x8000);
336         else
337             high_freq = fixmul32(high_freq,0x4ccd);
338     }
339     else if (sample_rate1 == 11025)
340     {
341         high_freq = fixmul32(high_freq,0xb333);
342     }
343     else if (sample_rate1 == 8000)
344     {
345         if (bps <= 0xa000)
346         {
347            high_freq = fixmul32(high_freq,0x8000);
348         }
349         else if (bps > 0xc000)
350         {
351             s->use_noise_coding = 0;
352         }
353         else
354         {
355             high_freq = fixmul32(high_freq,0xa666);
356         }
357     }
358     else
359     {
360         if (bps >= 0xcccd)
361         {
362             high_freq = fixmul32(high_freq,0xc000);
363         }
364         else if (bps >= 0x999a)
365         {
366             high_freq = fixmul32(high_freq,0x999a);
367         }
368         else
369         {
370             high_freq = fixmul32(high_freq,0x8000);
371         }
372     }
373 
374     /* compute the scale factor band sizes for each MDCT block size */
375     {
376         int a, b, pos, lpos, k, block_len, i, j, n;
377         const uint8_t *table;
378 
379         if (s->version == 1)
380         {
381             s->coefs_start = 3;
382         }
383         else
384         {
385             s->coefs_start = 0;
386         }
387         for(k = 0; k < s->nb_block_sizes; ++k)
388         {
389             block_len = s->frame_len >> k;
390 
391             if (s->version == 1)
392             {
393                 lpos = 0;
394                 for(i=0;i<25;++i)
395                 {
396                     a = wma_critical_freqs[i];
397                     b = s->sample_rate;
398                     pos = ((block_len * 2 * a)  + (b >> 1)) / b;
399                     if (pos > block_len)
400                         pos = block_len;
401                     s->exponent_bands[0][i] = pos - lpos;
402                     if (pos >= block_len)
403                     {
404                         ++i;
405                         break;
406                     }
407                     lpos = pos;
408                 }
409                 s->exponent_sizes[0] = i;
410             }
411             else
412             {
413                 /* hardcoded tables */
414                 table = NULL;
415                 a = s->frame_len_bits - BLOCK_MIN_BITS - k;
416                 if (a < 3)
417                 {
418                     if (s->sample_rate >= 44100)
419                         table = exponent_band_44100[a];
420                     else if (s->sample_rate >= 32000)
421                         table = exponent_band_32000[a];
422                     else if (s->sample_rate >= 22050)
423                         table = exponent_band_22050[a];
424                 }
425                 if (table)
426                 {
427                     n = *table++;
428                     for(i=0;i<n;++i)
429                         s->exponent_bands[k][i] = table[i];
430                     s->exponent_sizes[k] = n;
431                 }
432                 else
433                 {
434                     j = 0;
435                     lpos = 0;
436                     for(i=0;i<25;++i)
437                     {
438                         a = wma_critical_freqs[i];
439                         b = s->sample_rate;
440                         pos = ((block_len * 2 * a)  + (b << 1)) / (4 * b);
441                         pos <<= 2;
442                         if (pos > block_len)
443                             pos = block_len;
444                         if (pos > lpos)
445                             s->exponent_bands[k][j++] = pos - lpos;
446                         if (pos >= block_len)
447                             break;
448                         lpos = pos;
449                     }
450                     s->exponent_sizes[k] = j;
451                 }
452             }
453 
454             /* max number of coefs */
455             s->coefs_end[k] = (s->frame_len - ((s->frame_len * 9) / 100)) >> k;
456             /* high freq computation */
457 
458             fixed32 tmp1 = high_freq*2;            /* high_freq is a fixed32!*/
459             fixed32 tmp2=itofix32(s->sample_rate>>1);
460             s->high_band_start[k] = fixtoi32( fixdiv32(tmp1, tmp2) * (block_len>>1) +0x8000);
461 
462             /*
463             s->high_band_start[k] = (int)((block_len * 2 * high_freq) /
464                                           s->sample_rate + 0.5);*/
465 
466             n = s->exponent_sizes[k];
467             j = 0;
468             pos = 0;
469             for(i=0;i<n;++i)
470             {
471                 int start, end;
472                 start = pos;
473                 pos += s->exponent_bands[k][i];
474                 end = pos;
475                 if (start < s->high_band_start[k])
476                     start = s->high_band_start[k];
477                 if (end > s->coefs_end[k])
478                     end = s->coefs_end[k];
479                 if (end > start)
480                     s->exponent_high_bands[k][j++] = end - start;
481             }
482             s->exponent_high_sizes[k] = j;
483         }
484     }
485 
486     /* ffmpeg uses malloc to only allocate as many window sizes as needed.
487     *  However, we're really only interested in the worst case memory usage.
488     *  In the worst case you can have 5 window sizes, 128 doubling up 2048
489     *  Smaller windows are handled differently.
490     *  Since we don't have malloc, just statically allocate this
491     */
492     fixed32 *temp[5];
493     temp[0] = stat0;
494     temp[1] = stat1;
495     temp[2] = stat2;
496     temp[3] = stat3;
497     temp[4] = stat4;
498 
499     /* init MDCT windows : simple sinus window */
500     for(i = 0; i < s->nb_block_sizes; i++)
501     {
502         int n, j;
503         fixed32 alpha;
504         n = 1 << (s->frame_len_bits - i);
505         window = temp[i];
506 
507          /* this calculates 0.5/(2*n) */
508         alpha = (1<<15)>>(s->frame_len_bits - i+1);
509         for(j=0;j<n;++j)
510         {
511             fixed32 j2 = itofix32(j) + 0x8000;
512             /*alpha between 0 and pi/2*/
513             window[j] = fsincos(fixmul32(j2,alpha)<<16, 0);
514         }
515         s->windows[i] = window;
516 
517     }
518 
519     s->reset_block_lengths = 1;
520 
521     if (s->use_noise_coding) /* init the noise generator */
522     {
523         /* LSP values are simply 2x the EXP values */
524         if (s->use_exp_vlc)
525         {
526             s->noise_mult = 0x51f;
527             /*unlikely, but we may have previoiusly used this table for LSP,
528             so halve the values if needed*/
529             if(noisetable_exp[0] == 0x0a) {
530                 for (i=0;i<NOISE_TAB_SIZE;++i)
531                     noisetable_exp[i] >>= 1;
532             }
533             s->noise_table = noisetable_exp;
534         }
535         else
536         {
537             s->noise_mult = 0xa3d;
538             /*check that we haven't already doubled this table*/
539             if(noisetable_exp[0] == 0x5) {
540                 for (i=0;i<NOISE_TAB_SIZE;++i)
541                     noisetable_exp[i] <<= 1;
542             }
543             s->noise_table = noisetable_exp;
544         }
545 #if 0
546 /*TODO:  Rockbox has a dither function.  Consider using it for noise coding*/
547 
548 /* We use a lookup table computered in advance, so no need to do this*/
549         {
550             unsigned int seed;
551             fixed32 norm;
552             seed = 1;
553             norm = 0;   // PJJ: near as makes any diff to 0!
554             for (i=0;i<NOISE_TAB_SIZE;++i)
555             {
556                 seed = seed * 314159 + 1;
557                 s->noise_table[i] = itofix32((int)seed) * norm;
558             }
559         }
560 #endif
561 
562          s->hgain_vlc.table = vlcbuf4;
563          s->hgain_vlc.table_allocated = VLCBUF4SIZE;
564          init_vlc(&s->hgain_vlc, HGAINVLCBITS, sizeof(hgain_huffbits),
565                   hgain_huffbits, 1, 1,
566                   hgain_huffcodes, 2, 2, INIT_VLC_USE_NEW_STATIC);
567     }
568 
569     if (s->use_exp_vlc)
570     {
571 
572         s->exp_vlc.table = vlcbuf3;
573         s->exp_vlc.table_allocated = VLCBUF3SIZE;
574 
575          init_vlc(&s->exp_vlc, EXPVLCBITS, sizeof(scale_huffbits),
576                   scale_huffbits, 1, 1,
577                   scale_huffcodes, 4, 4, INIT_VLC_USE_NEW_STATIC);
578     }
579     else
580     {
581         wma_lsp_to_curve_init(s, s->frame_len);
582     }
583 
584     /* choose the VLC tables for the coefficients */
585     coef_vlc_table = 2;
586     if (s->sample_rate >= 32000)
587     {
588         if (bps1 < 0xb852)
589             coef_vlc_table = 0;
590         else if (bps1 < 0x128f6)
591             coef_vlc_table = 1;
592     }
593 
594     /* since the coef2 table is the biggest and that has index 2 in coef_vlcs
595        it's safe to always assign like this */
596     runtabarray[0] = runtab_big; runtabarray[1] = runtab_small;
597     levtabarray[0] = levtab_big; levtabarray[1] = levtab_small;
598 
599     s->coef_vlc[0].table = vlcbuf1;
600     s->coef_vlc[0].table_allocated = VLCBUF1SIZE;
601     s->coef_vlc[1].table = vlcbuf2;
602     s->coef_vlc[1].table_allocated = VLCBUF2SIZE;
603 
604 
605     init_coef_vlc(&s->coef_vlc[0], &s->run_table[0], &s->level_table[0],
606                   &coef_vlcs[coef_vlc_table * 2], 0);
607     init_coef_vlc(&s->coef_vlc[1], &s->run_table[1], &s->level_table[1],
608                   &coef_vlcs[coef_vlc_table * 2 + 1], 1);
609 
610     s->last_superframe_len = 0;
611     s->last_bitoffset = 0;
612 
613     return 0;
614 }
615 
616 
617 /* compute x^-0.25 with an exponent and mantissa table. We use linear
618    interpolation to reduce the mantissa table size at a small speed
619    expense (linear interpolation approximately doubles the number of
620    bits of precision). */
pow_m1_4(WMADecodeContext * s,fixed32 x)621 static inline fixed32 pow_m1_4(WMADecodeContext *s, fixed32 x)
622 {
623     union {
624         float f;
625         unsigned int v;
626     } u, t;
627     unsigned int e, m;
628     fixed32 a, b;
629 
630     u.f = fixtof64(x);
631     e = u.v >> 23;
632     m = (u.v >> (23 - LSP_POW_BITS)) & ((1 << LSP_POW_BITS) - 1);
633     /* build interpolation scale: 1 <= t < 2. */
634     t.v = ((u.v << LSP_POW_BITS) & ((1 << 23) - 1)) | (127 << 23);
635     a = ((fixed32*)s->lsp_pow_m_table1)[m];
636     b = ((fixed32*)s->lsp_pow_m_table2)[m];
637 
638     /* lsp_pow_e_table contains 32.32 format */
639     /* TODO:  Since we're unlikely have value that cover the whole
640      * IEEE754 range, we probably don't need to have all possible exponents */
641 
642     return (lsp_pow_e_table[e] * (a + fixmul32(b, ftofix32(t.f))) >>32);
643 }
644 
wma_lsp_to_curve_init(WMADecodeContext * s,int frame_len)645 static void wma_lsp_to_curve_init(WMADecodeContext *s, int frame_len)
646 {
647     fixed32 wdel, a, b, temp2;
648     int i;
649 
650     wdel = fixdiv32(itofix32(1),     itofix32(frame_len));
651     for (i=0; i<frame_len; ++i)
652     {
653         /* TODO: can probably reuse the trig_init values here */
654         fsincos((wdel*i)<<15, &temp2);
655         /* get 3 bits headroom + 1 bit from not doubleing the values */
656         s->lsp_cos_table[i] = temp2>>3;
657 
658     }
659     /* NOTE: these two tables are needed to avoid two operations in
660        pow_m1_4 */
661     b = itofix32(1);
662     int ix = 0;
663 
664     s->lsp_pow_m_table1 = &vlcbuf3[0];
665     s->lsp_pow_m_table2 = &vlcbuf3[1<<LSP_POW_BITS];
666 
667     /*double check this later*/
668     for(i=(1 << LSP_POW_BITS) - 1;i>=0;i--)
669     {
670         a = pow_a_table[ix++]<<4;
671         ((fixed32*)s->lsp_pow_m_table1)[i] = 2 * a - b;
672         ((fixed32*)s->lsp_pow_m_table2)[i] = b - a;
673         b = a;
674     }
675 
676 }
677 
678 /* NOTE: We use the same code as Vorbis here */
679 /* XXX: optimize it further with SSE/3Dnow */
wma_lsp_to_curve(WMADecodeContext * s,fixed32 * out,fixed32 * val_max_ptr,int n,fixed32 * lsp)680 static void wma_lsp_to_curve(WMADecodeContext *s,
681                              fixed32 *out,
682                              fixed32 *val_max_ptr,
683                              int n,
684                              fixed32 *lsp)
685 {
686     int i, j;
687     fixed32 p, q, w, v, val_max, temp2;
688 
689     val_max = 0;
690     for(i=0;i<n;++i)
691     {
692         /* shift by 2 now to reduce rounding error,
693          * we can renormalize right before pow_m1_4
694          */
695 
696         p = 0x8000<<5;
697         q = 0x8000<<5;
698         w = s->lsp_cos_table[i];
699 
700         for (j=1;j<NB_LSP_COEFS;j+=2)
701         {
702             /* w is 5.27 format, lsp is in 16.16, temp2 becomes 5.27 format */
703             temp2 = ((w - (lsp[j - 1]<<11)));
704 
705             /* q is 16.16 format, temp2 is 5.27, q becomes 16.16 */
706             q = fixmul32b(q, temp2 )<<4;
707             p = fixmul32b(p, (w - (lsp[j]<<11)))<<4;
708         }
709 
710         /* 2 in 5.27 format is 0x10000000 */
711         p = fixmul32(p, fixmul32b(p, (0x10000000 - w)))<<3;
712         q = fixmul32(q, fixmul32b(q, (0x10000000 + w)))<<3;
713 
714         v = (p + q) >>9;  /* p/q end up as 16.16 */
715         v = pow_m1_4(s, v);
716         if (v > val_max)
717             val_max = v;
718         out[i] = v;
719     }
720 
721     *val_max_ptr = val_max;
722 }
723 
724 /* decode exponents coded with LSP coefficients (same idea as Vorbis)
725  * only used for low bitrate (< 16kbps) files
726  */
decode_exp_lsp(WMADecodeContext * s,int ch)727 static void decode_exp_lsp(WMADecodeContext *s, int ch)
728 {
729     fixed32 lsp_coefs[NB_LSP_COEFS];
730     int val, i;
731 
732     for (i = 0; i < NB_LSP_COEFS; ++i)
733     {
734         if (i == 0 || i >= 8)
735             val = get_bits(&s->gb, 3);
736         else
737             val = get_bits(&s->gb, 4);
738         lsp_coefs[i] = lsp_codebook[i][val];
739     }
740 
741     wma_lsp_to_curve(s,
742                      s->exponents[ch],
743                      &s->max_exponent[ch],
744                      s->block_len,
745                      lsp_coefs);
746 }
747 
748 /* decode exponents coded with VLC codes - used for bitrate >= 32kbps*/
decode_exp_vlc(WMADecodeContext * s,int ch)749 static int decode_exp_vlc(WMADecodeContext *s, int ch)
750 {
751     int last_exp, n, code;
752     const uint16_t *ptr, *band_ptr;
753     fixed32 v, max_scale;
754     fixed32 *q,*q_end;
755 
756     /*accommodate the 60 negative indices */
757     const fixed32 *pow_10_to_yover16_ptr = &pow_10_to_yover16[61];
758 
759     band_ptr = s->exponent_bands[s->frame_len_bits - s->block_len_bits];
760     ptr = band_ptr;
761     q = s->exponents[ch];
762     q_end = q + s->block_len;
763     max_scale = 0;
764 
765 
766     if (s->version == 1)        //wmav1 only
767     {
768         last_exp = get_bits(&s->gb, 5) + 10;
769 
770         v = pow_10_to_yover16_ptr[last_exp];
771         max_scale = v;
772         n = *ptr++;
773         switch (n & 3) do {
774             case 0: *q++ = v;
775             case 3: *q++ = v;
776             case 2: *q++ = v;
777             case 1: *q++ = v;
778         } while ((n -= 4) > 0);
779     } else {
780        last_exp = 36;
781     }
782 
783     while (q < q_end)
784     {
785         code = get_vlc2(&s->gb, s->exp_vlc.table, EXPVLCBITS, EXPMAX);
786         if (code < 0)
787         {
788             return -1;
789         }
790         /* NOTE: this offset is the same as MPEG4 AAC ! */
791         last_exp += code - 60;
792 
793         v = pow_10_to_yover16_ptr[last_exp];
794         if (v > max_scale)
795         {
796             max_scale = v;
797         }
798         n = *ptr++;
799         switch (n & 3) do {
800             case 0: *q++ = v;
801             case 3: *q++ = v;
802             case 2: *q++ = v;
803             case 1: *q++ = v;
804         } while ((n -= 4) > 0);
805     }
806 
807     s->max_exponent[ch] = max_scale;
808     return 0;
809 }
810 
811 /* return 0 if OK. return 1 if last block of frame. return -1 if
812    unrecorrable error. */
wma_decode_block(WMADecodeContext * s)813 static int wma_decode_block(WMADecodeContext *s)
814 {
815     int n, v, a, ch, code, bsize;
816     int coef_nb_bits, total_gain;
817     int nb_coefs[MAX_CHANNELS];
818     fixed32 mdct_norm;
819 
820     /*DEBUGF("***decode_block: %d  (%d samples of %d in frame)\n",  s->block_num, s->block_len, s->frame_len);*/
821 
822    /* compute current block length */
823     if (s->use_variable_block_len)
824     {
825         n = av_log2(s->nb_block_sizes - 1) + 1;
826 
827         if (s->reset_block_lengths)
828         {
829             s->reset_block_lengths = 0;
830             v = get_bits(&s->gb, n);
831             if (v >= s->nb_block_sizes)
832             {
833                 return -2;
834             }
835             s->prev_block_len_bits = s->frame_len_bits - v;
836             v = get_bits(&s->gb, n);
837             if (v >= s->nb_block_sizes)
838             {
839                 return -3;
840             }
841             s->block_len_bits = s->frame_len_bits - v;
842         }
843         else
844         {
845             /* update block lengths */
846             s->prev_block_len_bits = s->block_len_bits;
847             s->block_len_bits = s->next_block_len_bits;
848         }
849         v = get_bits(&s->gb, n);
850 
851         if (v >= s->nb_block_sizes)
852         {
853          // rb->splash(HZ*4, "v was %d", v);        //5, 7
854             return -4;        //this is it
855         }
856         else{
857               //rb->splash(HZ, "passed v block (%d)!", v);
858       }
859         s->next_block_len_bits = s->frame_len_bits - v;
860     }
861     else
862     {
863         /* fixed block len */
864         s->next_block_len_bits = s->frame_len_bits;
865         s->prev_block_len_bits = s->frame_len_bits;
866         s->block_len_bits = s->frame_len_bits;
867     }
868     /* now check if the block length is coherent with the frame length */
869     s->block_len = 1 << s->block_len_bits;
870 
871     if ((s->block_pos + s->block_len) > s->frame_len)
872     {
873         return -5;  //oddly 32k sample from tracker fails here
874     }
875 
876     if (s->nb_channels == 2)
877     {
878         s->ms_stereo = get_bits1(&s->gb);
879     }
880     v = 0;
881     for (ch = 0; ch < s->nb_channels; ++ch)
882     {
883         a = get_bits1(&s->gb);
884         s->channel_coded[ch] = a;
885         v |= a;
886     }
887     /* if no channel coded, no need to go further */
888     /* XXX: fix potential framing problems */
889     if (!v)
890     {
891         goto next;
892     }
893 
894     bsize = s->frame_len_bits - s->block_len_bits;
895 
896     /* read total gain and extract corresponding number of bits for
897        coef escape coding */
898     total_gain = 1;
899     for(;;)
900     {
901         a = get_bits(&s->gb, 7);
902         total_gain += a;
903         if (a != 127)
904         {
905             break;
906         }
907     }
908 
909     if (total_gain < 15)
910         coef_nb_bits = 13;
911     else if (total_gain < 32)
912         coef_nb_bits = 12;
913     else if (total_gain < 40)
914         coef_nb_bits = 11;
915     else if (total_gain < 45)
916         coef_nb_bits = 10;
917     else
918         coef_nb_bits = 9;
919 
920     /* compute number of coefficients */
921     n = s->coefs_end[bsize] - s->coefs_start;
922 
923     for(ch = 0; ch < s->nb_channels; ++ch)
924     {
925         nb_coefs[ch] = n;
926     }
927     /* complex coding */
928     if (s->use_noise_coding)
929     {
930 
931         for(ch = 0; ch < s->nb_channels; ++ch)
932         {
933             if (s->channel_coded[ch])
934             {
935                 int i, n, a;
936                 n = s->exponent_high_sizes[bsize];
937                 for(i=0;i<n;++i)
938                 {
939                     a = get_bits1(&s->gb);
940                     s->high_band_coded[ch][i] = a;
941                     /* if noise coding, the coefficients are not transmitted */
942                     if (a)
943                         nb_coefs[ch] -= s->exponent_high_bands[bsize][i];
944                 }
945             }
946         }
947         for(ch = 0; ch < s->nb_channels; ++ch)
948         {
949             if (s->channel_coded[ch])
950             {
951                 int i, n, val, code;
952 
953                 n = s->exponent_high_sizes[bsize];
954                 val = (int)0x80000000;
955                 for(i=0;i<n;++i)
956                 {
957                     if (s->high_band_coded[ch][i])
958                     {
959                         if (val == (int)0x80000000)
960                         {
961                             val = get_bits(&s->gb, 7) - 19;
962                         }
963                         else
964                         {
965                             //code = get_vlc(&s->gb, &s->hgain_vlc);
966                             code = get_vlc2(&s->gb, s->hgain_vlc.table, HGAINVLCBITS, HGAINMAX);
967                             if (code < 0)
968                             {
969                                 return -6;
970                             }
971                             val += code - 18;
972                         }
973                         s->high_band_values[ch][i] = val;
974                     }
975                 }
976             }
977         }
978     }
979 
980     /* exponents can be reused in short blocks. */
981     if ((s->block_len_bits == s->frame_len_bits) || get_bits1(&s->gb))
982     {
983         for(ch = 0; ch < s->nb_channels; ++ch)
984         {
985             if (s->channel_coded[ch])
986             {
987                 if (s->use_exp_vlc)
988                 {
989                     if (decode_exp_vlc(s, ch) < 0)
990                     {
991                         return -7;
992                     }
993                 }
994                 else
995                 {
996                     decode_exp_lsp(s, ch);
997                 }
998                 s->exponents_bsize[ch] = bsize;
999             }
1000         }
1001     }
1002 
1003     /* parse spectral coefficients : just RLE encoding */
1004     for(ch = 0; ch < s->nb_channels; ++ch)
1005     {
1006         if (s->channel_coded[ch])
1007         {
1008             VLC *coef_vlc;
1009             int level, run, sign, tindex;
1010             int16_t *ptr, *eptr;
1011             const int16_t *level_table, *run_table;
1012 
1013             /* special VLC tables are used for ms stereo because
1014                there is potentially less energy there */
1015             tindex = (ch == 1 && s->ms_stereo);
1016             coef_vlc = &s->coef_vlc[tindex];
1017             run_table = s->run_table[tindex];
1018             level_table = s->level_table[tindex];
1019             /* XXX: optimize */
1020             ptr = &s->coefs1[ch][0];
1021             eptr = ptr + nb_coefs[ch];
1022             memset(ptr, 0, s->block_len * sizeof(int16_t));
1023 
1024             for(;;)
1025             {
1026                 code = get_vlc2(&s->gb, coef_vlc->table, VLCBITS, VLCMAX);
1027 
1028                 if (code < 0)
1029                 {
1030                     return -8;
1031                 }
1032                 if (code == 1)
1033                 {
1034                     /* EOB */
1035                     break;
1036                 }
1037                 else if (code == 0)
1038                 {
1039                     /* escape */
1040                     level = get_bits(&s->gb, coef_nb_bits);
1041                     /* NOTE: this is rather suboptimal. reading
1042                        block_len_bits would be better */
1043                     run = get_bits(&s->gb, s->frame_len_bits);
1044                 }
1045                 else
1046                 {
1047                     /* normal code */
1048                     run = run_table[code];
1049                     level = level_table[code];
1050                 }
1051                 sign = get_bits1(&s->gb);
1052                 if (!sign)
1053                     level = -level;
1054                 ptr += run;
1055                 if (ptr >= eptr)
1056                 {
1057                     break;
1058                 }
1059                 *ptr++ = level;
1060 
1061 
1062                 /* NOTE: EOB can be omitted */
1063                 if (ptr >= eptr)
1064                     break;
1065             }
1066         }
1067         if (s->version == 1 && s->nb_channels >= 2)
1068         {
1069             align_get_bits(&s->gb);
1070         }
1071     }
1072 
1073     {
1074         int n4 = s->block_len >> 1;
1075 
1076 
1077         mdct_norm = 0x10000>>(s->block_len_bits-1);
1078 
1079         if (s->version == 1)
1080         {
1081              mdct_norm *= fixtoi32(fixsqrt32(itofix32(n4)));
1082         }
1083     }
1084 
1085 
1086    /* finally compute the MDCT coefficients */
1087     for(ch = 0; ch < s->nb_channels; ++ch)
1088     {
1089         if (s->channel_coded[ch])
1090         {
1091             int16_t *coefs1;
1092             fixed32 *exponents;
1093             fixed32 *coefs, atemp;
1094             fixed64 mult;
1095             fixed64 mult1;
1096             fixed32 noise, temp1, temp2, mult2;
1097             int i, j, n, n1, last_high_band, esize;
1098             fixed32 exp_power[HIGH_BAND_MAX_SIZE];
1099 
1100             //total_gain, coefs1, mdctnorm are lossless
1101 
1102             coefs1 = s->coefs1[ch];
1103             exponents = s->exponents[ch];
1104             esize = s->exponents_bsize[ch];
1105             coefs = s->coefs[ch];
1106             n=0;
1107 
1108           /*
1109           *  The calculation of coefs has a shift right by 2 built in.  This
1110           *  prepares samples for the Tremor IMDCT which uses a slightly
1111           *  different fixed format then the ffmpeg one. If the old ffmpeg
1112           *  imdct is used, each shift storing into coefs should be reduced
1113           *  by 1.
1114           *  See SVN logs for details.
1115           */
1116 
1117 
1118             if (s->use_noise_coding)
1119             {
1120                 /*This case is only used for low bitrates (typically less then 32kbps)*/
1121 
1122                 /*TODO:  mult should be converted to 32 bit to speed up noise coding*/
1123 
1124                 mult = fixdiv64(pow_table[total_gain+20],Fixed32To64(s->max_exponent[ch]));
1125                 mult = mult* mdct_norm;
1126                 mult1 = mult;
1127 
1128                 /* very low freqs : noise */
1129                 for(i = 0;i < s->coefs_start; ++i)
1130                 {
1131                     *coefs++ = fixmul32( (fixmul32(s->noise_table[s->noise_index],
1132                             exponents[i<<bsize>>esize])>>4),Fixed32From64(mult1)) >>2;
1133                     s->noise_index = (s->noise_index + 1) & (NOISE_TAB_SIZE - 1);
1134                 }
1135 
1136                 n1 = s->exponent_high_sizes[bsize];
1137 
1138                 /* compute power of high bands */
1139                 exponents = s->exponents[ch] +(s->high_band_start[bsize]<<bsize);
1140                 last_high_band = 0; /* avoid warning */
1141                 for (j=0;j<n1;++j)
1142                 {
1143                     n = s->exponent_high_bands[s->frame_len_bits -
1144                                                s->block_len_bits][j];
1145                     if (s->high_band_coded[ch][j])
1146                     {
1147                         fixed32 e2, v;
1148                         e2 = 0;
1149                         for(i = 0;i < n; ++i)
1150                         {
1151                             /*v is normalized later on so its fixed format is irrelevant*/
1152                             v = exponents[i<<bsize>>esize]>>4;
1153                             e2 += fixmul32(v, v)>>3;
1154                         }
1155                          exp_power[j] = e2/n; /*n is an int...*/
1156                         last_high_band = j;
1157                     }
1158                     exponents += n<<bsize;
1159                 }
1160 
1161                 /* main freqs and high freqs */
1162                 exponents = s->exponents[ch] + (s->coefs_start<<bsize);
1163                 for(j=-1;j<n1;++j)
1164                 {
1165                     if (j < 0)
1166                     {
1167                         n = s->high_band_start[bsize] -
1168                             s->coefs_start;
1169                     }
1170                     else
1171                     {
1172                         n = s->exponent_high_bands[s->frame_len_bits -
1173                                                    s->block_len_bits][j];
1174                     }
1175                     if (j >= 0 && s->high_band_coded[ch][j])
1176                     {
1177                         /* use noise with specified power */
1178                         fixed32 tmp = fixdiv32(exp_power[j],exp_power[last_high_band]);
1179 
1180                         /*mult1 is 48.16, pow_table is 48.16*/
1181                         mult1 = fixmul32(fixsqrt32(tmp),
1182                                 pow_table[s->high_band_values[ch][j]+20]) >> 16;
1183 
1184                         /*this step has a fairly high degree of error for some reason*/
1185                         mult1 = fixdiv64(mult1,fixmul32(s->max_exponent[ch],s->noise_mult));
1186                         mult1 = mult1*mdct_norm>>PRECISION;
1187                         for(i = 0;i < n; ++i)
1188                         {
1189                             noise = s->noise_table[s->noise_index];
1190                             s->noise_index = (s->noise_index + 1) & (NOISE_TAB_SIZE - 1);
1191                             *coefs++ = fixmul32((fixmul32(exponents[i<<bsize>>esize],noise)>>4),
1192                                     Fixed32From64(mult1)) >>2;
1193 
1194                         }
1195                         exponents += n<<bsize;
1196                     }
1197                     else
1198                     {
1199                         /* coded values + small noise */
1200                         for(i = 0;i < n; ++i)
1201                         {
1202                             noise = s->noise_table[s->noise_index];
1203                             s->noise_index = (s->noise_index + 1) & (NOISE_TAB_SIZE - 1);
1204 
1205                            /*don't forget to renormalize the noise*/
1206                            temp1 = (((int32_t)*coefs1++)<<16) + (noise>>4);
1207                            temp2 = fixmul32(exponents[i<<bsize>>esize], mult>>18);
1208                            *coefs++ = fixmul32(temp1, temp2);
1209                         }
1210                         exponents += n<<bsize;
1211                     }
1212                 }
1213 
1214                 /* very high freqs : noise */
1215                 n = s->block_len - s->coefs_end[bsize];
1216                 mult2 = fixmul32(mult>>16,exponents[((-1<<bsize))>>esize]) ;
1217                 for (i = 0; i < n; ++i)
1218                 {
1219                     /*renormalize the noise product and then reduce to 14.18 precison*/
1220                     *coefs++ = fixmul32(s->noise_table[s->noise_index],mult2) >>6;
1221 
1222                     s->noise_index = (s->noise_index + 1) & (NOISE_TAB_SIZE - 1);
1223                 }
1224             }
1225             else
1226             {
1227                 /*Noise coding not used, simply convert from exp to fixed representation*/
1228 
1229                 fixed32 mult3 = (fixed32)(fixdiv64(pow_table[total_gain+20],
1230                         Fixed32To64(s->max_exponent[ch])));
1231                 mult3 = fixmul32(mult3, mdct_norm);
1232 
1233                 /*zero the first 3 coefficients for WMA V1, does nothing otherwise*/
1234                 for(i=0; i<s->coefs_start; i++)
1235                     *coefs++=0;
1236 
1237                 n = nb_coefs[ch];
1238 
1239                 /* XXX: optimize more, unrolling this loop in asm
1240                                 might be a good idea */
1241 
1242                 for(i = 0;i < n; ++i)
1243                 {
1244                     /*ffmpeg imdct needs 15.17, while tremor 14.18*/
1245                     atemp = (coefs1[i] * mult3)>>2;
1246                     *coefs++=fixmul32(atemp,exponents[i<<bsize>>esize]);
1247                 }
1248                 n = s->block_len - s->coefs_end[bsize];
1249                 memset(coefs, 0, n*sizeof(fixed32));
1250             }
1251         }
1252     }
1253 
1254 
1255 
1256     if (s->ms_stereo && s->channel_coded[1])
1257     {
1258         fixed32 a, b;
1259         int i;
1260         /* nominal case for ms stereo: we do it before mdct */
1261         /* no need to optimize this case because it should almost
1262            never happen */
1263         if (!s->channel_coded[0])
1264         {
1265             memset(s->coefs[0], 0, sizeof(fixed32) * s->block_len);
1266             s->channel_coded[0] = 1;
1267         }
1268 
1269         for(i = 0; i < s->block_len; ++i)
1270         {
1271             a = s->coefs[0][i];
1272             b = s->coefs[1][i];
1273             s->coefs[0][i] = a + b;
1274             s->coefs[1][i] = a - b;
1275         }
1276     }
1277 
1278     for(ch = 0; ch < s->nb_channels; ++ch)
1279     {
1280         /* BLOCK_MAX_SIZE is 2048 (samples) and MAX_CHANNELS is 2. */
1281         static uint32_t scratch_buf[BLOCK_MAX_SIZE * MAX_CHANNELS] IBSS_ATTR MEM_ALIGN_ATTR;
1282         if (s->channel_coded[ch])
1283         {
1284             int n4, index;
1285 
1286             n4 = s->block_len >>1;
1287 
1288             ff_imdct_calc((s->frame_len_bits - bsize + 1),
1289                           scratch_buf,
1290                           s->coefs[ch]);
1291 
1292             /* add in the frame */
1293             index = (s->frame_len / 2) + s->block_pos - n4;
1294             wma_window(s, scratch_buf, &(s->frame_out[ch][index]));
1295 
1296 
1297 
1298             /* specific fast case for ms-stereo : add to second
1299                channel if it is not coded */
1300             if (s->ms_stereo && !s->channel_coded[1])
1301             {
1302                 wma_window(s, scratch_buf, &(s->frame_out[1][index]));
1303             }
1304         }
1305     }
1306 next:
1307     /* update block number */
1308     ++s->block_num;
1309     s->block_pos += s->block_len;
1310     if (s->block_pos >= s->frame_len)
1311     {
1312         return 1;
1313     }
1314     else
1315     {
1316         return 0;
1317     }
1318 }
1319 
1320 /* decode a frame of frame_len samples */
wma_decode_frame(WMADecodeContext * s)1321 static int wma_decode_frame(WMADecodeContext *s)
1322 {
1323     int ret;
1324 
1325     /* read each block */
1326     s->block_num = 0;
1327     s->block_pos = 0;
1328 
1329 
1330     for(;;)
1331     {
1332         ret = wma_decode_block(s);
1333         if (ret < 0)
1334         {
1335 
1336             DEBUGF("wma_decode_block failed with code %d\n", ret);
1337             return -1;
1338         }
1339         if (ret)
1340         {
1341             break;
1342         }
1343     }
1344 
1345     return 0;
1346 }
1347 
1348 /* Initialise the superframe decoding */
1349 
wma_decode_superframe_init(WMADecodeContext * s,const uint8_t * buf,int buf_size)1350 int wma_decode_superframe_init(WMADecodeContext* s,
1351                                  const uint8_t *buf,  /*input*/
1352                                  int buf_size)
1353 {
1354     if (buf_size==0)
1355     {
1356         s->last_superframe_len = 0;
1357         return 0;
1358     }
1359 
1360     s->current_frame = 0;
1361 
1362     init_get_bits(&s->gb, buf, buf_size*8);
1363 
1364     if (s->use_bit_reservoir)
1365     {
1366         /* read super frame header */
1367         skip_bits(&s->gb, 4); /* super frame index */
1368         s->nb_frames = get_bits(&s->gb, 4);
1369 
1370         if (s->last_superframe_len == 0)
1371             s->nb_frames --;
1372         else if (s->nb_frames == 0)
1373             s->nb_frames++;
1374 
1375         s->bit_offset = get_bits(&s->gb, s->byte_offset_bits + 3);
1376     } else {
1377         s->nb_frames = 1;
1378     }
1379 
1380     return 1;
1381 }
1382 
1383 
1384 /* Decode a single frame in the current superframe - return -1 if
1385    there was a decoding error, or the number of samples decoded.
1386 */
1387 
wma_decode_superframe_frame(WMADecodeContext * s,const uint8_t * buf,int buf_size)1388 int wma_decode_superframe_frame(WMADecodeContext* s,
1389                                 const uint8_t *buf,  /*input*/
1390                                 int buf_size)
1391 {
1392     int pos, len, ch;
1393     uint8_t *q;
1394     int done = 0;
1395 
1396     for(ch = 0; ch < s->nb_channels; ch++)
1397         memmove(&(s->frame_out[ch][0]),
1398                 &(s->frame_out[ch][s->frame_len]),
1399                 s->frame_len * sizeof(fixed32));
1400 
1401     if ((s->use_bit_reservoir) && (s->current_frame == 0))
1402     {
1403         if (s->last_superframe_len > 0)
1404         {
1405             /* add s->bit_offset bits to last frame */
1406             if ((s->last_superframe_len + ((s->bit_offset + 7) >> 3)) >
1407                     MAX_CODED_SUPERFRAME_SIZE)
1408             {
1409                 DEBUGF("superframe size too large error\n");
1410                 goto fail;
1411             }
1412             q = s->last_superframe + s->last_superframe_len;
1413             len = s->bit_offset;
1414             while (len > 7)
1415             {
1416                 *q++ = (get_bits)(&s->gb, 8);
1417                 len -= 8;
1418             }
1419             if (len > 0)
1420             {
1421                 *q++ = (get_bits)(&s->gb, len) << (8 - len);
1422             }
1423 
1424             /* XXX: s->bit_offset bits into last frame */
1425             init_get_bits(&s->gb, s->last_superframe, MAX_CODED_SUPERFRAME_SIZE*8);
1426             /* skip unused bits */
1427             if (s->last_bitoffset > 0)
1428                 skip_bits(&s->gb, s->last_bitoffset);
1429 
1430             /* this frame is stored in the last superframe and in the
1431                current one */
1432             if (wma_decode_frame(s) < 0)
1433             {
1434                 goto fail;
1435             }
1436             done = 1;
1437         }
1438 
1439         /* read each frame starting from s->bit_offset */
1440         pos = s->bit_offset + 4 + 4 + s->byte_offset_bits + 3;
1441         init_get_bits(&s->gb, buf + (pos >> 3), (MAX_CODED_SUPERFRAME_SIZE - (pos >> 3))*8);
1442         len = pos & 7;
1443         if (len > 0)
1444             skip_bits(&s->gb, len);
1445 
1446         s->reset_block_lengths = 1;
1447     }
1448 
1449     /* If we haven't decoded a frame yet, do it now */
1450     if (!done)
1451         {
1452             if (wma_decode_frame(s) < 0)
1453             {
1454                 goto fail;
1455             }
1456         }
1457 
1458     s->current_frame++;
1459 
1460     if ((s->use_bit_reservoir) && (s->current_frame == s->nb_frames))
1461     {
1462         /* we copy the end of the frame in the last frame buffer */
1463         pos = get_bits_count(&s->gb) + ((s->bit_offset + 4 + 4 + s->byte_offset_bits + 3) & ~7);
1464         s->last_bitoffset = pos & 7;
1465         pos >>= 3;
1466         len = buf_size - pos;
1467         if (len > MAX_CODED_SUPERFRAME_SIZE || len < 0)
1468         {
1469             DEBUGF("superframe size too large error after decoding\n");
1470             goto fail;
1471         }
1472         s->last_superframe_len = len;
1473         memcpy(s->last_superframe, buf + pos, len);
1474     }
1475 
1476     return s->frame_len;
1477 
1478 fail:
1479     /* when error, we reset the bit reservoir */
1480 
1481     s->last_superframe_len = 0;
1482     return -1;
1483 }
1484 
1485