OSDN Git Service

Various fixes for ffmpeg input files (mp4, avi, mkv, etc.):
[handbrake-jp/handbrake-jp-git.git] / libhb / decavcodec.c
1 /* $Id: decavcodec.c,v 1.6 2005/03/06 04:08:54 titer Exp $
2
3    This file is part of the HandBrake source code.
4    Homepage: <http://handbrake.fr/>.
5    It may be used under the terms of the GNU General Public License. */
6
7 /* This module is Handbrake's interface to the ffmpeg decoder library
8    (libavcodec & small parts of libavformat). It contains four Handbrake
9    "work objects":
10
11     decavcodec  connects HB to an ffmpeg audio decoder
12     decavcodecv connects HB to an ffmpeg video decoder
13
14         (Two different routines are needed because the ffmpeg library
15         has different decoder calling conventions for audio & video.
16         The audio decoder should have had its name changed to "decavcodeca"
17         but I got lazy.) These work objects are self-contained & follow all
18         of HB's conventions for a decoder module. They can be used like
19         any other HB decoder (deca52, decmpeg2, etc.).
20
21     decavcodecai "internal" (incestuous?) version of decavcodec
22     decavcodecvi "internal" (incestuous?) version of decavcodecv
23
24         These routine are functionally equivalent to the routines above but
25         can only be used by the ffmpeg-based stream reader in libhb/stream.c.
26         The reason they exist is because the ffmpeg library leaves some of
27         the information needed by the decoder in the AVStream (the data
28         structure used by the stream reader) and we need to retrieve it
29         to successfully decode frames. But in HB the reader and decoder
30         modules are in completely separate threads and nothing goes between
31         them but hb_buffers containing frames to be decoded. I.e., there's
32         no easy way for the ffmpeg stream reader to pass a pointer to its
33         AVStream over to the ffmpeg video or audio decoder. So the *i work
34         objects use a private back door to the stream reader to get access
35         to the AVStream (routines hb_ffmpeg_avstream and hb_ffmpeg_context)
36         and the codec_param passed to these work objects is the key to this
37         back door (it's basically an index that allows the correct AVStream
38         to be retrieved).
39
40     The normal & *i objects share a lot of code (the basic frame decoding
41     and bitstream info code is factored out into subroutines that can be
42     called by either) but the top level routines of the *i objects
43     (decavcodecviWork, decavcodecviInfo, etc.) are different because:
44      1) they *have* to use the AVCodecContext that's contained in the
45         reader's AVStream rather than just allocating & using their own,
46      2) the Info routines have access to stuff kept in the AVStream in addition
47         to stuff kept in the AVCodecContext. This shouldn't be necessary but
48         crucial information like video frame rate that should be in the
49         AVCodecContext is either missing or wrong in the version of ffmpeg
50         we're currently using.
51
52     A consequence of the above is that the non-i work objects *can't* use
53     information from the AVStream because there isn't one - they get their
54     data from either the dvd reader or the mpeg reader, not the ffmpeg stream
55     reader. That means that they have to make up for deficiencies in the
56     AVCodecContext info by using stuff kept in the HB "title" struct. It
57     also means that ffmpeg codecs that randomly scatter state needed by
58     the decoder across both the AVCodecContext & the AVStream (e.g., the
59     VC1 decoder) can't easily be used by the HB mpeg stream reader.
60  */
61
62 #include "hb.h"
63
64 #include "libavcodec/avcodec.h"
65 #include "libavformat/avformat.h"
66
67 static int  decavcodecInit( hb_work_object_t *, hb_job_t * );
68 static int  decavcodecWork( hb_work_object_t *, hb_buffer_t **, hb_buffer_t ** );
69 static void decavcodecClose( hb_work_object_t * );
70 static int decavcodecInfo( hb_work_object_t *, hb_work_info_t * );
71 static int decavcodecBSInfo( hb_work_object_t *, const hb_buffer_t *, hb_work_info_t * );
72
73 hb_work_object_t hb_decavcodec =
74 {
75     WORK_DECAVCODEC,
76     "MPGA decoder (libavcodec)",
77     decavcodecInit,
78     decavcodecWork,
79     decavcodecClose,
80     decavcodecInfo,
81     decavcodecBSInfo
82 };
83
84 #define HEAP_SIZE 8
85 typedef struct {
86     // there are nheap items on the heap indexed 1..nheap (i.e., top of
87     // heap is 1). The 0th slot is unused - a marker is put there to check
88     // for overwrite errs.
89     int64_t h[HEAP_SIZE+1];
90     int     nheap;
91 } pts_heap_t;
92
93 struct hb_work_private_s
94 {
95     hb_job_t             *job;
96     AVCodecContext       *context;
97     AVCodecParserContext *parser;
98     hb_list_t            *list;
99     double               duration;  // frame duration (for video)
100     double               pts_next;  // next pts we expect to generate
101     int64_t              pts;       // (video) pts passing from parser to decoder
102     int64_t              chap_time; // time of next chap mark (if new_chap != 0)
103     int                  new_chap;
104     uint32_t             nframes;
105     uint32_t             ndrops;
106     uint32_t             decode_errors;
107     hb_buffer_t*         delayq[HEAP_SIZE];
108     pts_heap_t           pts_heap;
109     void*                buffer;
110 };
111
112 static int64_t heap_pop( pts_heap_t *heap )
113 {
114     int64_t result;
115
116     if ( heap->nheap <= 0 )
117     {
118         return -1;
119     }
120
121     // return the top of the heap then put the bottom element on top,
122     // decrease the heap size by one & rebalence the heap.
123     result = heap->h[1];
124
125     int64_t v = heap->h[heap->nheap--];
126     int parent = 1;
127     int child = parent << 1;
128     while ( child <= heap->nheap )
129     {
130         // find the smallest of the two children of parent
131         if (child < heap->nheap && heap->h[child] > heap->h[child+1] )
132             ++child;
133
134         if (v <= heap->h[child])
135             // new item is smaller than either child so it's the new parent.
136             break;
137
138         // smallest child is smaller than new item so move it up then
139         // check its children.
140         int64_t hp = heap->h[child];
141         heap->h[parent] = hp;
142         parent = child;
143         child = parent << 1;
144     }
145     heap->h[parent] = v;
146     return result;
147 }
148
149 static void heap_push( pts_heap_t *heap, int64_t v )
150 {
151     if ( heap->nheap < HEAP_SIZE )
152     {
153         ++heap->nheap;
154     }
155
156     // stick the new value on the bottom of the heap then bubble it
157     // up to its correct spot.
158         int child = heap->nheap;
159         while (child > 1) {
160                 int parent = child >> 1;
161                 if (heap->h[parent] <= v)
162                         break;
163                 // move parent down
164                 int64_t hp = heap->h[parent];
165                 heap->h[child] = hp;
166                 child = parent;
167         }
168         heap->h[child] = v;
169 }
170
171
172 /***********************************************************************
173  * hb_work_decavcodec_init
174  ***********************************************************************
175  *
176  **********************************************************************/
177 static int decavcodecInit( hb_work_object_t * w, hb_job_t * job )
178 {
179     AVCodec * codec;
180
181     hb_work_private_t * pv = calloc( 1, sizeof( hb_work_private_t ) );
182     w->private_data = pv;
183
184     pv->job   = job;
185
186     int codec_id = w->codec_param;
187     /*XXX*/
188     if ( codec_id == 0 )
189         codec_id = CODEC_ID_MP2;
190     codec = avcodec_find_decoder( codec_id );
191     pv->parser = av_parser_init( codec_id );
192
193     pv->context = avcodec_alloc_context();
194     avcodec_open( pv->context, codec );
195
196     return 0;
197 }
198
199 /***********************************************************************
200  * Close
201  ***********************************************************************
202  *
203  **********************************************************************/
204 static void decavcodecClose( hb_work_object_t * w )
205 {
206     hb_work_private_t * pv = w->private_data;
207
208     if ( pv )
209     {
210         if ( pv->job && pv->context && pv->context->codec )
211         {
212             hb_log( "%s-decoder done: %u frames, %u decoder errors, %u drops",
213                     pv->context->codec->name, pv->nframes, pv->decode_errors,
214                     pv->ndrops );
215         }
216         if ( pv->parser )
217         {
218             av_parser_close(pv->parser);
219         }
220         if ( pv->context && pv->context->codec )
221         {
222             avcodec_close( pv->context );
223         }
224         if ( pv->list )
225         {
226             hb_list_close( &pv->list );
227         }
228         if ( pv->buffer )
229         {
230             free( pv->buffer );
231             pv->buffer = NULL;
232         }
233         free( pv );
234         w->private_data = NULL;
235     }
236 }
237
238 /***********************************************************************
239  * Work
240  ***********************************************************************
241  *
242  **********************************************************************/
243 static int decavcodecWork( hb_work_object_t * w, hb_buffer_t ** buf_in,
244                     hb_buffer_t ** buf_out )
245 {
246     hb_work_private_t * pv = w->private_data;
247     hb_buffer_t * in = *buf_in, * buf, * last = NULL;
248     int   pos, len, out_size, i, uncompressed_len;
249     short buffer[AVCODEC_MAX_AUDIO_FRAME_SIZE];
250     uint64_t cur;
251     unsigned char *parser_output_buffer;
252     int parser_output_buffer_len;
253
254     if ( (*buf_in)->size <= 0 )
255     {
256         /* EOF on input stream - send it downstream & say that we're done */
257         *buf_out = *buf_in;
258         *buf_in = NULL;
259         return HB_WORK_DONE;
260     }
261
262     *buf_out = NULL;
263
264     cur = ( in->start < 0 )? pv->pts_next : in->start;
265
266     pos = 0;
267     while( pos < in->size )
268     {
269         len = av_parser_parse( pv->parser, pv->context,
270                                &parser_output_buffer, &parser_output_buffer_len,
271                                in->data + pos, in->size - pos, cur, cur );
272         out_size = 0;
273         uncompressed_len = 0;
274         if (parser_output_buffer_len)
275         {
276             out_size = sizeof(buffer);
277             uncompressed_len = avcodec_decode_audio2( pv->context, buffer,
278                                                       &out_size,
279                                                       parser_output_buffer,
280                                                       parser_output_buffer_len );
281         }
282         if( out_size )
283         {
284             short * s16;
285             float * fl32;
286
287             buf = hb_buffer_init( 2 * out_size );
288
289             int sample_size_in_bytes = 2;   // Default to 2 bytes
290             switch (pv->context->sample_fmt)
291             {
292               case SAMPLE_FMT_S16:
293                 sample_size_in_bytes = 2;
294                 break;
295               /* We should handle other formats here - but that needs additional format conversion work below */
296               /* For now we'll just report the error and try to carry on */
297               default:
298                 hb_log("decavcodecWork - Unknown Sample Format from avcodec_decode_audio (%d) !", pv->context->sample_fmt);
299                 break;
300             }
301
302             buf->start = cur;
303             buf->stop  = cur + 90000 * ( out_size / (sample_size_in_bytes * pv->context->channels) ) /
304                          pv->context->sample_rate;
305             cur = buf->stop;
306
307             s16  = buffer;
308             fl32 = (float *) buf->data;
309             for( i = 0; i < out_size / 2; i++ )
310             {
311                 fl32[i] = s16[i];
312             }
313
314             if( last )
315             {
316                 last = last->next = buf;
317             }
318             else
319             {
320                 *buf_out = last = buf;
321             }
322         }
323
324         pos += len;
325     }
326
327     pv->pts_next = cur;
328
329     return HB_WORK_OK;
330 }
331
332 static int decavcodecInfo( hb_work_object_t *w, hb_work_info_t *info )
333 {
334     hb_work_private_t *pv = w->private_data;
335
336     memset( info, 0, sizeof(*info) );
337
338     if ( pv && pv->context )
339     {
340         AVCodecContext *context = pv->context;
341         info->bitrate = context->bit_rate;
342         info->rate = context->time_base.num;
343         info->rate_base = context->time_base.den;
344         info->profile = context->profile;
345         info->level = context->level;
346         return 1;
347     }
348     return 0;
349 }
350
351 static int decavcodecBSInfo( hb_work_object_t *w, const hb_buffer_t *buf,
352                              hb_work_info_t *info )
353 {
354     hb_work_private_t *pv = w->private_data;
355
356     memset( info, 0, sizeof(*info) );
357
358     if ( pv && pv->context )
359     {
360         return decavcodecInfo( w, info );
361     }
362     // XXX
363     // We should parse the bitstream to find its parameters but for right
364     // now we just return dummy values if there's a codec that will handle it.
365     AVCodec *codec = avcodec_find_decoder( w->codec_param? w->codec_param :
366                                                            CODEC_ID_MP2 );
367     if ( codec )
368     {
369         static char codec_name[64];
370
371         info->name =  strncpy( codec_name, codec->name, sizeof(codec_name)-1 );
372         info->bitrate = 384000;
373         info->rate = 48000;
374         info->rate_base = 1;
375         info->channel_layout = HB_INPUT_CH_LAYOUT_STEREO;
376         return 1;
377     }
378     return -1;
379 }
380
381 /* -------------------------------------------------------------
382  * General purpose video decoder using libavcodec
383  */
384
385 static uint8_t *copy_plane( uint8_t *dst, uint8_t* src, int dstride, int sstride,
386                             int h )
387 {
388     if ( dstride == sstride )
389     {
390         memcpy( dst, src, dstride * h );
391         return dst + dstride * h;
392     }
393     int lbytes = dstride <= sstride? dstride : sstride;
394     while ( --h >= 0 )
395     {
396         memcpy( dst, src, lbytes );
397         src += sstride;
398         dst += dstride;
399     }
400     return dst;
401 }
402
403 /* Note: assumes frame format is PIX_FMT_YUV420P */
404 static hb_buffer_t *copy_frame( AVCodecContext *context, AVFrame *frame )
405 {
406     int w = context->width, h = context->height;
407     hb_buffer_t *buf = hb_buffer_init( w * h * 3 / 2 );
408     uint8_t *dst = buf->data;
409
410     dst = copy_plane( dst, frame->data[0], w, frame->linesize[0], h );
411     w >>= 1; h >>= 1;
412     dst = copy_plane( dst, frame->data[1], w, frame->linesize[1], h );
413     dst = copy_plane( dst, frame->data[2], w, frame->linesize[2], h );
414
415     return buf;
416 }
417
418 static int get_frame_buf( AVCodecContext *context, AVFrame *frame )
419 {
420     hb_work_private_t *pv = context->opaque;
421     frame->pts = pv->pts;
422     pv->pts = -1;
423     return avcodec_default_get_buffer( context, frame );
424 }
425
426 static void log_chapter( hb_work_private_t *pv, int chap_num, int64_t pts )
427 {
428     hb_chapter_t *c = hb_list_item( pv->job->title->list_chapter, chap_num - 1 );
429     if ( c && c->title )
430     {
431         hb_log( "%s: \"%s\" (%d) at frame %u time %lld",
432                 pv->context->codec->name, c->title, chap_num, pv->nframes, pts );
433     }
434     else
435     {
436         hb_log( "%s: Chapter %d at frame %u time %lld",
437                 pv->context->codec->name, chap_num, pv->nframes, pts );
438     }
439 }
440
441 static void flushDelayQueue( hb_work_private_t *pv )
442 {
443     hb_buffer_t *buf;
444     int slot = pv->nframes & (HEAP_SIZE-1);
445
446     // flush all the video packets left on our timestamp-reordering delay q
447     while ( ( buf = pv->delayq[slot] ) != NULL )
448     {
449         buf->start = heap_pop( &pv->pts_heap );
450         hb_list_add( pv->list, buf );
451         pv->delayq[slot] = NULL;
452         slot = ( slot + 1 ) & (HEAP_SIZE-1);
453     }
454 }
455
456 static int decodeFrame( hb_work_private_t *pv, uint8_t *data, int size )
457 {
458     int got_picture;
459     AVFrame frame;
460
461     if ( avcodec_decode_video( pv->context, &frame, &got_picture, data, size ) < 0 )
462     {
463         ++pv->decode_errors;     
464     }
465     if( got_picture )
466     {
467         // ffmpeg makes it hard to attach a pts to a frame. if the MPEG ES
468         // packet had a pts we handed it to av_parser_parse (if the packet had
469         // no pts we set it to -1 but before the parse we can't distinguish between
470         // the start of a video frame with no pts & an intermediate packet of
471         // some frame which never has a pts). we hope that when parse returns
472         // the frame to us the pts we originally handed it will be in parser->pts.
473         // we put this pts into pv->pts so that when a avcodec_decode_video
474         // finally gets around to allocating an AVFrame to hold the decoded
475         // frame we can stuff that pts into the frame. if all of these relays
476         // worked at this point frame.pts should hold the frame's pts from the
477         // original data stream or -1 if it didn't have one. in the latter case
478         // we generate the next pts in sequence for it.
479         double frame_dur = pv->duration;
480         if ( frame_dur <= 0 )
481         {
482             frame_dur = 90000. * (double)pv->context->time_base.num /
483                         (double)pv->context->time_base.den;
484             pv->duration = frame_dur;
485         }
486         if ( frame.repeat_pict )
487         {
488             frame_dur += frame.repeat_pict * frame_dur * 0.5;
489         }
490         // If there was no pts for this frame, assume constant frame rate
491         // video & estimate the next frame time from the last & duration.
492         double pts = frame.pts;
493         if ( pts < 0 )
494         {
495             pts = pv->pts_next;
496         }
497         pv->pts_next = pts + frame_dur;
498
499         hb_buffer_t *buf;
500
501         // if we're doing a scan we don't worry about timestamp reordering
502         if ( ! pv->job )
503         {
504             buf = copy_frame( pv->context, &frame );
505             buf->start = pts;
506             hb_list_add( pv->list, buf );
507             ++pv->nframes;
508             return got_picture;
509         }
510
511         // XXX This following probably addresses a libavcodec bug but I don't
512         //     see an easy fix so we workaround it here.
513         //
514         // The M$ 'packed B-frames' atrocity results in decoded frames with
515         // the wrong timestamp. E.g., if there are 2 b-frames the timestamps
516         // we see here will be "2 3 1 5 6 4 ..." instead of "1 2 3 4 5 6".
517         // The frames are actually delivered in the right order but with
518         // the wrong timestamp. To get the correct timestamp attached to
519         // each frame we have a delay queue (longer than the max number of
520         // b-frames) & a sorting heap for the timestamps. As each frame
521         // comes out of the decoder the oldest frame in the queue is removed
522         // and associated with the smallest timestamp. Then the new frame is
523         // added to the queue & its timestamp is pushed on the heap.
524         // This does nothing if the timestamps are correct (i.e., the video
525         // uses a codec that Micro$oft hasn't broken yet) but the frames
526         // get timestamped correctly even when M$ has munged them.
527
528         // remove the oldest picture from the frame queue (if any) &
529         // give it the smallest timestamp from our heap. The queue size
530         // is a power of two so we get the slot of the oldest by masking
531         // the frame count & this will become the slot of the newest
532         // once we've removed & processed the oldest.
533         int slot = pv->nframes & (HEAP_SIZE-1);
534         if ( ( buf = pv->delayq[slot] ) != NULL )
535         {
536             buf->start = heap_pop( &pv->pts_heap );
537
538             if ( pv->new_chap && buf->start >= pv->chap_time )
539             {
540                 buf->new_chap = pv->new_chap;
541                 pv->new_chap = 0;
542                 pv->chap_time = 0;
543                 log_chapter( pv, buf->new_chap, buf->start );
544             }
545             else if ( pv->nframes == 0 )
546             {
547                 log_chapter( pv, pv->job->chapter_start, buf->start );
548             }
549             hb_list_add( pv->list, buf );
550         }
551
552         // add the new frame to the delayq & push its timestamp on the heap
553         pv->delayq[slot] = copy_frame( pv->context, &frame );
554         heap_push( &pv->pts_heap, pts );
555
556         ++pv->nframes;
557     }
558
559     return got_picture;
560 }
561
562 static void decodeVideo( hb_work_private_t *pv, uint8_t *data, int size,
563                          int64_t pts, int64_t dts )
564 {
565     /*
566      * The following loop is a do..while because we need to handle both
567      * data & the flush at the end (signaled by size=0). At the end there's
568      * generally a frame in the parser & one or more frames in the decoder
569      * (depending on the bframes setting).
570      */
571     int pos = 0;
572     do {
573         uint8_t *pout;
574         int pout_len;
575         int len = av_parser_parse( pv->parser, pv->context, &pout, &pout_len,
576                                    data + pos, size - pos, pts, dts );
577         pos += len;
578
579         if ( pout_len > 0 )
580         {
581             pv->pts = pv->parser->pts;
582             decodeFrame( pv, pout, pout_len );
583         }
584     } while ( pos < size );
585
586     /* the stuff above flushed the parser, now flush the decoder */
587     if ( size <= 0 )
588     {
589         while ( decodeFrame( pv, NULL, 0 ) )
590         {
591         }
592         flushDelayQueue( pv );
593     }
594 }
595
596 static hb_buffer_t *link_buf_list( hb_work_private_t *pv )
597 {
598     hb_buffer_t *head = hb_list_item( pv->list, 0 );
599
600     if ( head )
601     {
602         hb_list_rem( pv->list, head );
603
604         hb_buffer_t *last = head, *buf;
605
606         while ( ( buf = hb_list_item( pv->list, 0 ) ) != NULL )
607         {
608             hb_list_rem( pv->list, buf );
609             last->next = buf;
610             last = buf;
611         }
612     }
613     return head;
614 }
615
616
617 static int decavcodecvInit( hb_work_object_t * w, hb_job_t * job )
618 {
619
620     hb_work_private_t *pv = calloc( 1, sizeof( hb_work_private_t ) );
621     w->private_data = pv;
622     pv->job   = job;
623     pv->list = hb_list_init();
624
625     int codec_id = w->codec_param;
626     pv->parser = av_parser_init( codec_id );
627     pv->context = avcodec_alloc_context2( CODEC_TYPE_VIDEO );
628
629     /* we have to wrap ffmpeg's get_buffer to be able to set the pts (?!) */
630     pv->context->opaque = pv;
631     pv->context->get_buffer = get_frame_buf;
632
633     AVCodec *codec = avcodec_find_decoder( codec_id );
634
635     // we can't call the avstream funcs but the read_header func in the
636     // AVInputFormat may set up some state in the AVContext. In particular 
637     // vc1t_read_header allocates 'extradata' to deal with header issues
638     // related to Microsoft's bizarre engineering notions. We alloc a chunk
639     // of space to make vc1 work then associate the codec with the context.
640     pv->context->extradata_size = 32;
641     pv->context->extradata = av_malloc(pv->context->extradata_size);
642     avcodec_open( pv->context, codec );
643
644     return 0;
645 }
646
647 static int decavcodecvWork( hb_work_object_t * w, hb_buffer_t ** buf_in,
648                             hb_buffer_t ** buf_out )
649 {
650     hb_work_private_t *pv = w->private_data;
651     hb_buffer_t *in = *buf_in;
652     int64_t pts = AV_NOPTS_VALUE;
653     int64_t dts = pts;
654
655     *buf_in = NULL;
656
657     /* if we got an empty buffer signaling end-of-stream send it downstream */
658     if ( in->size == 0 )
659     {
660         decodeVideo( pv, in->data, in->size, pts, dts );
661         hb_list_add( pv->list, in );
662         *buf_out = link_buf_list( pv );
663         return HB_WORK_DONE;
664     }
665
666     if( in->start >= 0 )
667     {
668         pts = in->start;
669         dts = in->renderOffset;
670     }
671     if ( in->new_chap )
672     {
673         pv->new_chap = in->new_chap;
674         pv->chap_time = pts >= 0? pts : pv->pts_next;
675     }
676     decodeVideo( pv, in->data, in->size, pts, dts );
677     hb_buffer_close( &in );
678     *buf_out = link_buf_list( pv );
679     return HB_WORK_OK;
680 }
681
682 static int decavcodecvInfo( hb_work_object_t *w, hb_work_info_t *info )
683 {
684     hb_work_private_t *pv = w->private_data;
685
686     memset( info, 0, sizeof(*info) );
687
688     if ( pv && pv->context )
689     {
690         AVCodecContext *context = pv->context;
691         info->bitrate = context->bit_rate;
692         info->width = context->width;
693         info->height = context->height;
694
695         /* ffmpeg gives the frame rate in frames per second while HB wants
696          * it in units of the 27MHz MPEG clock. */
697         info->rate = 27000000;
698         info->rate_base = (int64_t)context->time_base.num * 27000000LL /
699                           context->time_base.den;
700         
701         /* Sometimes there's no pixel aspect set in the source. In that case,
702            assume a 1:1 PAR. Otherwise, preserve the source PAR.             */
703         info->pixel_aspect_width = context->sample_aspect_ratio.num ?
704                                         context->sample_aspect_ratio.num : 1;
705         info->pixel_aspect_height = context->sample_aspect_ratio.den ?
706                                         context->sample_aspect_ratio.den : 1;
707
708         /* ffmpeg returns the Pixel Aspect Ratio (PAR). Handbrake wants the
709          * Display Aspect Ratio so we convert by scaling by the Storage
710          * Aspect Ratio (w/h). We do the calc in floating point to get the
711          * rounding right. */
712         info->aspect = (double)info->pixel_aspect_width * 
713                        (double)context->width /
714                        (double)info->pixel_aspect_height /
715                        (double)context->height;
716
717         info->profile = context->profile;
718         info->level = context->level;
719         info->name = context->codec->name;
720         return 1;
721     }
722     return 0;
723 }
724
725 static int decavcodecvBSInfo( hb_work_object_t *w, const hb_buffer_t *buf,
726                              hb_work_info_t *info )
727 {
728     return 0;
729 }
730
731 hb_work_object_t hb_decavcodecv =
732 {
733     WORK_DECAVCODECV,
734     "Video decoder (libavcodec)",
735     decavcodecvInit,
736     decavcodecvWork,
737     decavcodecClose,
738     decavcodecvInfo,
739     decavcodecvBSInfo
740 };
741
742
743 // This is a special decoder for ffmpeg streams. The ffmpeg stream reader
744 // includes a parser and passes information from the parser to the decoder
745 // via a codec context kept in the AVStream of the reader's AVFormatContext.
746 // We *have* to use that codec context to decode the stream or we'll get
747 // garbage. ffmpeg_title_scan put a cookie that can be used to get to that
748 // codec context in our codec_param.
749
750 // this routine gets the appropriate context pointer from the ffmpeg
751 // stream reader. it can't be called until we get the first buffer because
752 // we can't guarantee that reader will be called before the our init
753 // routine and if our init is called first we'll get a pointer to the
754 // old scan stream (which has already been closed).
755 static void init_ffmpeg_context( hb_work_object_t *w )
756 {
757     hb_work_private_t *pv = w->private_data;
758     pv->context = hb_ffmpeg_context( w->codec_param );
759
760     // during scan the decoder gets closed & reopened which will
761     // close the codec so reopen it if it's not there
762     if ( ! pv->context->codec )
763     {
764         AVCodec *codec = avcodec_find_decoder( pv->context->codec_id );
765         avcodec_open( pv->context, codec );
766     }
767     // set up our best guess at the frame duration.
768     // the frame rate in the codec is usually bogus but it's sometimes
769     // ok in the stream.
770     AVStream *st = hb_ffmpeg_avstream( w->codec_param );
771
772     if ( st->nb_frames && st->duration )
773     {
774         // compute the average frame duration from the total number
775         // of frames & the total duration.
776         pv->duration = ( (double)st->duration * (double)st->time_base.num ) /
777                        ( (double)st->nb_frames * (double)st->time_base.den );
778     }
779     else
780     {
781         // XXX We don't have a frame count or duration so try to use the
782         // far less reliable time base info in the stream.
783         // Because the time bases are so screwed up, we only take values
784         // in the range 8fps - 64fps.
785         AVRational tb;
786         if ( st->time_base.num * 64 > st->time_base.den &&
787              st->time_base.den > st->time_base.num * 8 )
788         {
789             tb = st->time_base;
790         }
791         else if ( st->r_frame_rate.den * 64 > st->r_frame_rate.num &&
792                   st->r_frame_rate.num > st->r_frame_rate.den * 8 )
793         {
794             tb.num = st->r_frame_rate.den;
795             tb.den = st->r_frame_rate.num;
796         }
797         else
798         {
799             tb.num = 1001;  /*XXX*/
800             tb.den = 24000; /*XXX*/
801         }
802         pv->duration =  (double)tb.num / (double)tb.den;
803     }
804     pv->duration *= 90000.;
805
806     // we have to wrap ffmpeg's get_buffer to be able to set the pts (?!)
807     pv->context->opaque = pv;
808     pv->context->get_buffer = get_frame_buf;
809 }
810
811 static void prepare_ffmpeg_buffer( hb_buffer_t * in )
812 {
813     // ffmpeg requires an extra 8 bytes of zero at the end of the buffer and
814     // will seg fault in odd, data dependent ways if it's not there. (my guess
815     // is this is a case of a local performance optimization creating a global
816     // performance degradation since all the time wasted by extraneous data
817     // copies & memory zeroing has to be huge compared to the minor reduction
818     // in inner-loop instructions this affords - modern cpus bottleneck on
819     // memory bandwidth not instruction bandwidth).
820     if ( in->size + FF_INPUT_BUFFER_PADDING_SIZE > in->alloc )
821     {
822         // have to realloc to add the padding
823         hb_buffer_realloc( in, in->size + FF_INPUT_BUFFER_PADDING_SIZE );
824     }
825     memset( in->data + in->size, 0, FF_INPUT_BUFFER_PADDING_SIZE );
826 }
827
828 static int decavcodecviInit( hb_work_object_t * w, hb_job_t * job )
829 {
830
831     hb_work_private_t *pv = calloc( 1, sizeof( hb_work_private_t ) );
832     w->private_data = pv;
833     pv->job   = job;
834     pv->list = hb_list_init();
835     pv->pts_next = -1;
836     pv->pts = -1;
837     return 0;
838 }
839
840 static int decavcodecviWork( hb_work_object_t * w, hb_buffer_t ** buf_in,
841                              hb_buffer_t ** buf_out )
842 {
843     hb_work_private_t *pv = w->private_data;
844     if ( ! pv->context )
845     {
846         init_ffmpeg_context( w );
847     }
848     hb_buffer_t *in = *buf_in;
849     *buf_in = NULL;
850
851     /* if we got an empty buffer signaling end-of-stream send it downstream */
852     if ( in->size == 0 )
853     {
854         /* flush any frames left in the decoder */
855         while ( decodeFrame( pv, NULL, 0 ) )
856         {
857         }
858         flushDelayQueue( pv );
859         hb_list_add( pv->list, in );
860         *buf_out = link_buf_list( pv );
861         return HB_WORK_DONE;
862     }
863
864     int64_t pts = in->start;
865     if( pts >= 0 )
866     {
867         // use the first timestamp as our 'next expected' pts
868         if ( pv->pts_next < 0 )
869         {
870             pv->pts_next = pts;
871         }
872         pv->pts = pts;
873     }
874
875     if ( in->new_chap )
876     {
877         pv->new_chap = in->new_chap;
878         pv->chap_time = pts >= 0? pts : pv->pts_next;
879     }
880     prepare_ffmpeg_buffer( in );
881     decodeFrame( pv, in->data, in->size );
882     hb_buffer_close( &in );
883     *buf_out = link_buf_list( pv );
884     return HB_WORK_OK;
885 }
886
887 static int decavcodecviInfo( hb_work_object_t *w, hb_work_info_t *info )
888 {
889     if ( decavcodecvInfo( w, info ) )
890     {
891         hb_work_private_t *pv = w->private_data;
892         if ( ! pv->context )
893         {
894             init_ffmpeg_context( w );
895         }
896         // we have the frame duration in units of the 90KHz pts clock but
897         // need it in units of the 27MHz MPEG clock. */
898         info->rate = 27000000;
899         info->rate_base = pv->duration * 300.;
900         return 1;
901     }
902     return 0;
903 }
904
905 static void decodeAudio( hb_work_private_t *pv, uint8_t *data, int size )
906 {
907     AVCodecContext *context = pv->context;
908     int pos = 0;
909
910     while ( pos < size )
911     {
912         int16_t *buffer = pv->buffer;
913         if ( buffer == NULL )
914         {
915             // XXX ffmpeg bug workaround
916             // malloc a buffer for the audio decode. On an x86, ffmpeg
917             // uses mmx/sse instructions on this buffer without checking
918             // that it's 16 byte aligned and this will cause an abort if
919             // the buffer is allocated on our stack. Rather than doing
920             // complicated, machine dependent alignment here we use the
921             // fact that malloc returns an aligned pointer on most architectures.
922             pv->buffer = malloc( AVCODEC_MAX_AUDIO_FRAME_SIZE );
923             buffer = pv->buffer;
924         }
925         int out_size = AVCODEC_MAX_AUDIO_FRAME_SIZE;
926         int len = avcodec_decode_audio2( context, buffer, &out_size,
927                                          data + pos, size - pos );
928         if ( len <= 0 )
929         {
930             return;
931         }
932         pos += len;
933         if( out_size > 0 )
934         {
935             hb_buffer_t *buf = hb_buffer_init( 2 * out_size );
936
937             // convert from bytes to total samples
938             out_size >>= 1;
939
940             double pts = pv->pts_next;
941             buf->start = pts;
942             pts += out_size * pv->duration;
943             buf->stop  = pts;
944             pv->pts_next = pts;
945
946             float *fl32 = (float *)buf->data;
947             int i;
948             for( i = 0; i < out_size; ++i )
949             {
950                 fl32[i] = buffer[i];
951             }
952             hb_list_add( pv->list, buf );
953         }
954     }
955 }
956
957 static int decavcodecaiWork( hb_work_object_t *w, hb_buffer_t **buf_in,
958                     hb_buffer_t **buf_out )
959 {
960     if ( (*buf_in)->size <= 0 )
961     {
962         /* EOF on input stream - send it downstream & say that we're done */
963         *buf_out = *buf_in;
964         *buf_in = NULL;
965         return HB_WORK_DONE;
966     }
967
968     hb_work_private_t *pv = w->private_data;
969     if ( ! pv->context )
970     {
971         init_ffmpeg_context( w );
972         // duration is a scaling factor to go from #bytes in the decoded
973         // frame to frame time (in 90KHz mpeg ticks). 'channels' converts
974         // total samples to per-channel samples. 'sample_rate' converts
975         // per-channel samples to seconds per sample and the 90000
976         // is mpeg ticks per second.
977         pv->duration = 90000. /
978                     (double)( pv->context->sample_rate * pv->context->channels );
979     }
980     hb_buffer_t *in = *buf_in;
981
982     // if the packet has a timestamp use it if we don't have a timestamp yet
983     // or if there's been a timing discontinuity of more than 100ms.
984     if ( in->start >= 0 &&
985          ( pv->pts_next < 0 || ( in->start - pv->pts_next ) > 90*100 ) )
986     {
987         pv->pts_next = in->start;
988     }
989     prepare_ffmpeg_buffer( in );
990     decodeAudio( pv, in->data, in->size );
991     *buf_out = link_buf_list( pv );
992
993     return HB_WORK_OK;
994 }
995
996 hb_work_object_t hb_decavcodecvi =
997 {
998     WORK_DECAVCODECVI,
999     "Video decoder (ffmpeg streams)",
1000     decavcodecviInit,
1001     decavcodecviWork,
1002     decavcodecClose,
1003     decavcodecviInfo,
1004     decavcodecvBSInfo
1005 };
1006
1007 hb_work_object_t hb_decavcodecai =
1008 {
1009     WORK_DECAVCODECAI,
1010     "Audio decoder (ffmpeg streams)",
1011     decavcodecviInit,
1012     decavcodecaiWork,
1013     decavcodecClose,
1014     decavcodecInfo,
1015     decavcodecBSInfo
1016 };