]> git.sesse.net Git - x264/blob - encoder/rdo.c
e613298967ac04b432a588015d05dc1b563a2a3f
[x264] / encoder / rdo.c
1 /*****************************************************************************
2  * rdo.c: rate-distortion optimization
3  *****************************************************************************
4  * Copyright (C) 2005-2010 x264 project
5  *
6  * Authors: Loren Merritt <lorenm@u.washington.edu>
7  *          Fiona Glaser <fiona@x264.com>
8  *
9  * This program is free software; you can redistribute it and/or modify
10  * it under the terms of the GNU General Public License as published by
11  * the Free Software Foundation; either version 2 of the License, or
12  * (at your option) any later version.
13  *
14  * This program is distributed in the hope that it will be useful,
15  * but WITHOUT ANY WARRANTY; without even the implied warranty of
16  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
17  * GNU General Public License for more details.
18  *
19  * You should have received a copy of the GNU General Public License
20  * along with this program; if not, write to the Free Software
21  * Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02111, USA.
22  *
23  * This program is also available under a commercial proprietary license.
24  * For more information, contact us at licensing@x264.com.
25  *****************************************************************************/
26
27 /* duplicate all the writer functions, just calculating bit cost
28  * instead of writing the bitstream.
29  * TODO: use these for fast 1st pass too. */
30
31 #define RDO_SKIP_BS 1
32
33 /* Transition and size tables for abs<9 MVD and residual coding */
34 /* Consist of i_prefix-2 1s, one zero, and a bypass sign bit */
35 static uint8_t cabac_transition_unary[15][128];
36 static uint16_t cabac_size_unary[15][128];
37 /* Transition and size tables for abs>9 MVD */
38 /* Consist of 5 1s and a bypass sign bit */
39 static uint8_t cabac_transition_5ones[128];
40 static uint16_t cabac_size_5ones[128];
41
42 /* CAVLC: produces exactly the same bit count as a normal encode */
43 /* this probably still leaves some unnecessary computations */
44 #define bs_write1(s,v)     ((s)->i_bits_encoded += 1)
45 #define bs_write(s,n,v)    ((s)->i_bits_encoded += (n))
46 #define bs_write_ue(s,v)   ((s)->i_bits_encoded += bs_size_ue(v))
47 #define bs_write_se(s,v)   ((s)->i_bits_encoded += bs_size_se(v))
48 #define bs_write_te(s,v,l) ((s)->i_bits_encoded += bs_size_te(v,l))
49 #define x264_macroblock_write_cavlc  static x264_macroblock_size_cavlc
50 #include "cavlc.c"
51
52 /* CABAC: not exactly the same. x264_cabac_size_decision() keeps track of
53  * fractional bits, but only finite precision. */
54 #undef  x264_cabac_encode_decision
55 #undef  x264_cabac_encode_decision_noup
56 #undef  x264_cabac_encode_bypass
57 #undef  x264_cabac_encode_terminal
58 #define x264_cabac_encode_decision(c,x,v) x264_cabac_size_decision(c,x,v)
59 #define x264_cabac_encode_decision_noup(c,x,v) x264_cabac_size_decision_noup(c,x,v)
60 #define x264_cabac_encode_terminal(c)     ((c)->f8_bits_encoded += 7)
61 #define x264_cabac_encode_bypass(c,v)     ((c)->f8_bits_encoded += 256)
62 #define x264_cabac_encode_ue_bypass(c,e,v) ((c)->f8_bits_encoded += (bs_size_ue_big(v+(1<<e)-1)-e)<<8)
63 #define x264_macroblock_write_cabac  static x264_macroblock_size_cabac
64 #include "cabac.c"
65
66 #define COPY_CABAC h->mc.memcpy_aligned( &cabac_tmp.f8_bits_encoded, &h->cabac.f8_bits_encoded, \
67         sizeof(x264_cabac_t) - offsetof(x264_cabac_t,f8_bits_encoded) )
68 #define COPY_CABAC_PART( pos, size )\
69         memcpy( &cb->state[pos], &h->cabac.state[pos], size )
70
71 static ALWAYS_INLINE uint64_t cached_hadamard( x264_t *h, int size, int x, int y )
72 {
73     static const uint8_t hadamard_shift_x[4] = {4,   4,   3,   3};
74     static const uint8_t hadamard_shift_y[4] = {4-0, 3-0, 4-1, 3-1};
75     static const uint8_t  hadamard_offset[4] = {0,   1,   3,   5};
76     int cache_index = (x >> hadamard_shift_x[size]) + (y >> hadamard_shift_y[size])
77                     + hadamard_offset[size];
78     uint64_t res = h->mb.pic.fenc_hadamard_cache[cache_index];
79     if( res )
80         return res - 1;
81     else
82     {
83         pixel *fenc = h->mb.pic.p_fenc[0] + x + y*FENC_STRIDE;
84         res = h->pixf.hadamard_ac[size]( fenc, FENC_STRIDE );
85         h->mb.pic.fenc_hadamard_cache[cache_index] = res + 1;
86         return res;
87     }
88 }
89
90 static ALWAYS_INLINE int cached_satd( x264_t *h, int size, int x, int y )
91 {
92     static const uint8_t satd_shift_x[3] = {3,   2,   2};
93     static const uint8_t satd_shift_y[3] = {2-1, 3-2, 2-2};
94     static const uint8_t  satd_offset[3] = {0,   8,   16};
95     ALIGNED_16( static pixel zero[16] );
96     int cache_index = (x >> satd_shift_x[size - PIXEL_8x4]) + (y >> satd_shift_y[size - PIXEL_8x4])
97                     + satd_offset[size - PIXEL_8x4];
98     int res = h->mb.pic.fenc_satd_cache[cache_index];
99     if( res )
100         return res - 1;
101     else
102     {
103         pixel *fenc = h->mb.pic.p_fenc[0] + x + y*FENC_STRIDE;
104         int dc = h->pixf.sad[size]( fenc, FENC_STRIDE, zero, 0 ) >> 1;
105         res = h->pixf.satd[size]( fenc, FENC_STRIDE, zero, 0 ) - dc;
106         h->mb.pic.fenc_satd_cache[cache_index] = res + 1;
107         return res;
108     }
109 }
110
111 /* Psy RD distortion metric: SSD plus "Absolute Difference of Complexities" */
112 /* SATD and SA8D are used to measure block complexity. */
113 /* The difference between SATD and SA8D scores are both used to avoid bias from the DCT size.  Using SATD */
114 /* only, for example, results in overusage of 8x8dct, while the opposite occurs when using SA8D. */
115
116 /* FIXME:  Is there a better metric than averaged SATD/SA8D difference for complexity difference? */
117 /* Hadamard transform is recursive, so a SATD+SA8D can be done faster by taking advantage of this fact. */
118 /* This optimization can also be used in non-RD transform decision. */
119
120 static inline int ssd_plane( x264_t *h, int size, int p, int x, int y )
121 {
122     ALIGNED_16(static pixel zero[16]);
123     int satd = 0;
124     pixel *fdec = h->mb.pic.p_fdec[p] + x + y*FDEC_STRIDE;
125     pixel *fenc = h->mb.pic.p_fenc[p] + x + y*FENC_STRIDE;
126     if( p == 0 && h->mb.i_psy_rd )
127     {
128         /* If the plane is smaller than 8x8, we can't do an SA8D; this probably isn't a big problem. */
129         if( size <= PIXEL_8x8 )
130         {
131             uint64_t fdec_acs = h->pixf.hadamard_ac[size]( fdec, FDEC_STRIDE );
132             uint64_t fenc_acs = cached_hadamard( h, size, x, y );
133             satd = abs((int32_t)fdec_acs - (int32_t)fenc_acs)
134                  + abs((int32_t)(fdec_acs>>32) - (int32_t)(fenc_acs>>32));
135             satd >>= 1;
136         }
137         else
138         {
139             int dc = h->pixf.sad[size]( fdec, FDEC_STRIDE, zero, 0 ) >> 1;
140             satd = abs(h->pixf.satd[size]( fdec, FDEC_STRIDE, zero, 0 ) - dc - cached_satd( h, size, x, y ));
141         }
142         satd = (satd * h->mb.i_psy_rd * h->mb.i_psy_rd_lambda + 128) >> 8;
143     }
144     return h->pixf.ssd[size](fenc, FENC_STRIDE, fdec, FDEC_STRIDE) + satd;
145 }
146
147 static inline int ssd_mb( x264_t *h )
148 {
149     int chromassd = ssd_plane(h, PIXEL_8x8, 1, 0, 0) + ssd_plane(h, PIXEL_8x8, 2, 0, 0);
150     chromassd = ((uint64_t)chromassd * h->mb.i_chroma_lambda2_offset + 128) >> 8;
151     return ssd_plane(h, PIXEL_16x16, 0, 0, 0) + chromassd;
152 }
153
154 static int x264_rd_cost_mb( x264_t *h, int i_lambda2 )
155 {
156     int b_transform_bak = h->mb.b_transform_8x8;
157     int i_ssd;
158     int i_bits;
159     int type_bak = h->mb.i_type;
160
161     x264_macroblock_encode( h );
162
163     if( h->mb.b_deblock_rdo )
164         x264_macroblock_deblock( h );
165
166     i_ssd = ssd_mb( h );
167
168     if( IS_SKIP( h->mb.i_type ) )
169     {
170         i_bits = (1 * i_lambda2 + 128) >> 8;
171     }
172     else if( h->param.b_cabac )
173     {
174         x264_cabac_t cabac_tmp;
175         COPY_CABAC;
176         x264_macroblock_size_cabac( h, &cabac_tmp );
177         i_bits = ( (uint64_t)cabac_tmp.f8_bits_encoded * i_lambda2 + 32768 ) >> 16;
178     }
179     else
180     {
181         x264_macroblock_size_cavlc( h );
182         i_bits = ( h->out.bs.i_bits_encoded * i_lambda2 + 128 ) >> 8;
183     }
184
185     h->mb.b_transform_8x8 = b_transform_bak;
186     h->mb.i_type = type_bak;
187
188     return i_ssd + i_bits;
189 }
190
191 /* For small partitions (i.e. those using at most one DCT category's worth of CABAC states),
192  * it's faster to copy the individual parts than to perform a whole CABAC_COPY. */
193 static ALWAYS_INLINE void x264_copy_cabac_part( x264_t *h, x264_cabac_t *cb, int cat, int intra )
194 {
195     if( intra )
196         COPY_CABAC_PART( 68, 2 );  //intra pred mode
197     else
198         COPY_CABAC_PART( 40, 16 ); //mvd, rounded up to 16 bytes
199
200     /* 8x8dct writes CBP, while non-8x8dct writes CBF */
201     if( cat != DCT_LUMA_8x8 )
202         COPY_CABAC_PART( 85 + cat * 4, 4 );
203     else
204         COPY_CABAC_PART( 73, 4 );
205
206     /* Really should be 15 bytes, but rounding up a byte saves some
207      * instructions and is faster, and copying extra data doesn't hurt. */
208     COPY_CABAC_PART( significant_coeff_flag_offset[h->mb.b_interlaced][cat], 16 );
209     COPY_CABAC_PART( last_coeff_flag_offset[h->mb.b_interlaced][cat], 16 );
210     COPY_CABAC_PART( coeff_abs_level_m1_offset[cat], 10 );
211     cb->f8_bits_encoded = 0;
212 }
213
214 /* partition RD functions use 8 bits more precision to avoid large rounding errors at low QPs */
215
216 static uint64_t x264_rd_cost_subpart( x264_t *h, int i_lambda2, int i4, int i_pixel )
217 {
218     uint64_t i_ssd, i_bits;
219
220     x264_macroblock_encode_p4x4( h, i4 );
221     if( i_pixel == PIXEL_8x4 )
222         x264_macroblock_encode_p4x4( h, i4+1 );
223     if( i_pixel == PIXEL_4x8 )
224         x264_macroblock_encode_p4x4( h, i4+2 );
225
226     i_ssd = ssd_plane( h, i_pixel, 0, block_idx_x[i4]*4, block_idx_y[i4]*4 );
227
228     if( h->param.b_cabac )
229     {
230         x264_cabac_t cabac_tmp;
231         x264_copy_cabac_part( h, &cabac_tmp, DCT_LUMA_4x4, 0 );
232         x264_subpartition_size_cabac( h, &cabac_tmp, i4, i_pixel );
233         i_bits = ( (uint64_t)cabac_tmp.f8_bits_encoded * i_lambda2 + 128 ) >> 8;
234     }
235     else
236         i_bits = x264_subpartition_size_cavlc( h, i4, i_pixel );
237
238     return (i_ssd<<8) + i_bits;
239 }
240
241 uint64_t x264_rd_cost_part( x264_t *h, int i_lambda2, int i4, int i_pixel )
242 {
243     uint64_t i_ssd, i_bits;
244     int i8 = i4 >> 2;
245     int chromassd;
246
247     if( i_pixel == PIXEL_16x16 )
248     {
249         int i_cost = x264_rd_cost_mb( h, i_lambda2 );
250         return i_cost;
251     }
252
253     if( i_pixel > PIXEL_8x8 )
254         return x264_rd_cost_subpart( h, i_lambda2, i4, i_pixel );
255
256     h->mb.i_cbp_luma = 0;
257
258     x264_macroblock_encode_p8x8( h, i8 );
259     if( i_pixel == PIXEL_16x8 )
260         x264_macroblock_encode_p8x8( h, i8+1 );
261     if( i_pixel == PIXEL_8x16 )
262         x264_macroblock_encode_p8x8( h, i8+2 );
263
264     chromassd = ssd_plane( h, i_pixel+3, 1, (i8&1)*4, (i8>>1)*4 )
265               + ssd_plane( h, i_pixel+3, 2, (i8&1)*4, (i8>>1)*4 );
266     chromassd = ((uint64_t)chromassd * h->mb.i_chroma_lambda2_offset + 128) >> 8;
267     i_ssd = ssd_plane( h, i_pixel,   0, (i8&1)*8, (i8>>1)*8 ) + chromassd;
268
269     if( h->param.b_cabac )
270     {
271         x264_cabac_t cabac_tmp;
272         COPY_CABAC;
273         x264_partition_size_cabac( h, &cabac_tmp, i8, i_pixel );
274         i_bits = ( (uint64_t)cabac_tmp.f8_bits_encoded * i_lambda2 + 128 ) >> 8;
275     }
276     else
277         i_bits = x264_partition_size_cavlc( h, i8, i_pixel ) * i_lambda2;
278
279     return (i_ssd<<8) + i_bits;
280 }
281
282 static uint64_t x264_rd_cost_i8x8( x264_t *h, int i_lambda2, int i8, int i_mode )
283 {
284     uint64_t i_ssd, i_bits;
285     h->mb.i_cbp_luma &= ~(1<<i8);
286     h->mb.b_transform_8x8 = 1;
287
288     x264_mb_encode_i8x8( h, i8, h->mb.i_qp );
289     i_ssd = ssd_plane( h, PIXEL_8x8, 0, (i8&1)*8, (i8>>1)*8 );
290
291     if( h->param.b_cabac )
292     {
293         x264_cabac_t cabac_tmp;
294         x264_copy_cabac_part( h, &cabac_tmp, DCT_LUMA_8x8, 1 );
295         x264_partition_i8x8_size_cabac( h, &cabac_tmp, i8, i_mode );
296         i_bits = ( (uint64_t)cabac_tmp.f8_bits_encoded * i_lambda2 + 128 ) >> 8;
297     }
298     else
299         i_bits = x264_partition_i8x8_size_cavlc( h, i8, i_mode ) * i_lambda2;
300
301     return (i_ssd<<8) + i_bits;
302 }
303
304 static uint64_t x264_rd_cost_i4x4( x264_t *h, int i_lambda2, int i4, int i_mode )
305 {
306     uint64_t i_ssd, i_bits;
307
308     x264_mb_encode_i4x4( h, i4, h->mb.i_qp );
309     i_ssd = ssd_plane( h, PIXEL_4x4, 0, block_idx_x[i4]*4, block_idx_y[i4]*4 );
310
311     if( h->param.b_cabac )
312     {
313         x264_cabac_t cabac_tmp;
314         x264_copy_cabac_part( h, &cabac_tmp, DCT_LUMA_4x4, 1 );
315         x264_partition_i4x4_size_cabac( h, &cabac_tmp, i4, i_mode );
316         i_bits = ( (uint64_t)cabac_tmp.f8_bits_encoded * i_lambda2 + 128 ) >> 8;
317     }
318     else
319         i_bits = x264_partition_i4x4_size_cavlc( h, i4, i_mode ) * i_lambda2;
320
321     return (i_ssd<<8) + i_bits;
322 }
323
324 static uint64_t x264_rd_cost_i8x8_chroma( x264_t *h, int i_lambda2, int i_mode, int b_dct )
325 {
326     uint64_t i_ssd, i_bits;
327
328     if( b_dct )
329         x264_mb_encode_8x8_chroma( h, 0, h->mb.i_chroma_qp );
330     i_ssd = ssd_plane( h, PIXEL_8x8, 1, 0, 0 ) +
331             ssd_plane( h, PIXEL_8x8, 2, 0, 0 );
332
333     h->mb.i_chroma_pred_mode = i_mode;
334
335     if( h->param.b_cabac )
336     {
337         x264_cabac_t cabac_tmp;
338         COPY_CABAC;
339         x264_i8x8_chroma_size_cabac( h, &cabac_tmp );
340         i_bits = ( (uint64_t)cabac_tmp.f8_bits_encoded * i_lambda2 + 128 ) >> 8;
341     }
342     else
343         i_bits = x264_i8x8_chroma_size_cavlc( h ) * i_lambda2;
344
345     return (i_ssd<<8) + i_bits;
346 }
347 /****************************************************************************
348  * Trellis RD quantization
349  ****************************************************************************/
350
351 #define TRELLIS_SCORE_MAX ((uint64_t)1<<50)
352 #define CABAC_SIZE_BITS 8
353 #define SSD_WEIGHT_BITS 5
354 #define LAMBDA_BITS 4
355
356 /* precalculate the cost of coding various combinations of bits in a single context */
357 void x264_rdo_init( void )
358 {
359     for( int i_prefix = 0; i_prefix < 15; i_prefix++ )
360     {
361         for( int i_ctx = 0; i_ctx < 128; i_ctx++ )
362         {
363             int f8_bits = 0;
364             uint8_t ctx = i_ctx;
365
366             for( int i = 1; i < i_prefix; i++ )
367                 f8_bits += x264_cabac_size_decision2( &ctx, 1 );
368             if( i_prefix > 0 && i_prefix < 14 )
369                 f8_bits += x264_cabac_size_decision2( &ctx, 0 );
370             f8_bits += 1 << CABAC_SIZE_BITS; //sign
371
372             cabac_size_unary[i_prefix][i_ctx] = f8_bits;
373             cabac_transition_unary[i_prefix][i_ctx] = ctx;
374         }
375     }
376     for( int i_ctx = 0; i_ctx < 128; i_ctx++ )
377     {
378         int f8_bits = 0;
379         uint8_t ctx = i_ctx;
380
381         for( int i = 0; i < 5; i++ )
382             f8_bits += x264_cabac_size_decision2( &ctx, 1 );
383         f8_bits += 1 << CABAC_SIZE_BITS; //sign
384
385         cabac_size_5ones[i_ctx] = f8_bits;
386         cabac_transition_5ones[i_ctx] = ctx;
387     }
388 }
389
390 typedef struct {
391     int64_t score;
392     int level_idx; // index into level_tree[]
393     uint8_t cabac_state[10]; //just the contexts relevant to coding abs_level_m1
394 } trellis_node_t;
395
396 // TODO:
397 // save cabac state between blocks?
398 // use trellis' RD score instead of x264_mb_decimate_score?
399 // code 8x8 sig/last flags forwards with deadzone and save the contexts at
400 //   each position?
401 // change weights when using CQMs?
402
403 // possible optimizations:
404 // make scores fit in 32bit
405 // save quantized coefs during rd, to avoid a duplicate trellis in the final encode
406 // if trellissing all MBRD modes, finish SSD calculation so we can skip all of
407 //   the normal dequant/idct/ssd/cabac
408
409 // the unquant_mf here is not the same as dequant_mf:
410 // in normal operation (dct->quant->dequant->idct) the dct and idct are not
411 // normalized. quant/dequant absorb those scaling factors.
412 // in this function, we just do (quant->unquant) and want the output to be
413 // comparable to the input. so unquant is the direct inverse of quant,
414 // and uses the dct scaling factors, not the idct ones.
415
416 static ALWAYS_INLINE
417 int quant_trellis_cabac( x264_t *h, dctcoef *dct,
418                          const uint16_t *quant_mf, const int *unquant_mf,
419                          const int *coef_weight, const uint8_t *zigzag,
420                          int i_ctxBlockCat, int i_lambda2, int b_ac,
421                          int dc, int i_coefs, int idx )
422 {
423     int abs_coefs[64], signs[64];
424     trellis_node_t nodes[2][8];
425     trellis_node_t *nodes_cur = nodes[0];
426     trellis_node_t *nodes_prev = nodes[1];
427     trellis_node_t *bnode;
428     const int b_interlaced = h->mb.b_interlaced;
429     uint8_t *cabac_state_sig = &h->cabac.state[ significant_coeff_flag_offset[b_interlaced][i_ctxBlockCat] ];
430     uint8_t *cabac_state_last = &h->cabac.state[ last_coeff_flag_offset[b_interlaced][i_ctxBlockCat] ];
431     const int f = 1 << 15; // no deadzone
432     int i_last_nnz;
433     int i;
434
435     // (# of coefs) * (# of ctx) * (# of levels tried) = 1024
436     // we don't need to keep all of those: (# of coefs) * (# of ctx) would be enough,
437     // but it takes more time to remove dead states than you gain in reduced memory.
438     struct {
439         uint16_t abs_level;
440         uint16_t next;
441     } level_tree[64*8*2];
442     int i_levels_used = 1;
443
444     /* init coefs */
445     for( i = i_coefs-1; i >= b_ac; i-- )
446         if( (unsigned)(dct[zigzag[i]] * (dc?quant_mf[0]>>1:quant_mf[zigzag[i]]) + f-1) >= 2*f )
447             break;
448
449     if( i < b_ac )
450     {
451         /* We only need to zero an empty 4x4 block. 8x8 can be
452            implicitly emptied via zero nnz, as can dc. */
453         if( i_coefs == 16 && !dc )
454             memset( dct, 0, 16 * sizeof(dctcoef) );
455         return 0;
456     }
457
458     i_last_nnz = i;
459
460     for( ; i >= b_ac; i-- )
461     {
462         int coef = dct[zigzag[i]];
463         abs_coefs[i] = abs(coef);
464         signs[i] = coef < 0 ? -1 : 1;
465     }
466
467     /* init trellis */
468     for( int j = 1; j < 8; j++ )
469         nodes_cur[j].score = TRELLIS_SCORE_MAX;
470     nodes_cur[0].score = 0;
471     nodes_cur[0].level_idx = 0;
472     level_tree[0].abs_level = 0;
473     level_tree[0].next = 0;
474
475     // coefs are processed in reverse order, because that's how the abs value is coded.
476     // last_coef and significant_coef flags are normally coded in forward order, but
477     // we have to reverse them to match the levels.
478     // in 4x4 blocks, last_coef and significant_coef use a separate context for each
479     // position, so the order doesn't matter, and we don't even have to update their contexts.
480     // in 8x8 blocks, some positions share contexts, so we'll just have to hope that
481     // cabac isn't too sensitive.
482
483     memcpy( nodes_cur[0].cabac_state, &h->cabac.state[ coeff_abs_level_m1_offset[i_ctxBlockCat] ], 10 );
484
485     for( i = i_last_nnz; i >= b_ac; i-- )
486     {
487         int i_coef = abs_coefs[i];
488         int q = ( f + i_coef * (dc?quant_mf[0]>>1:quant_mf[zigzag[i]]) ) >> 16;
489         int cost_sig[2], cost_last[2];
490         trellis_node_t n;
491
492         // skip 0s: this doesn't affect the output, but saves some unnecessary computation.
493         if( q == 0 )
494         {
495             // no need to calculate ssd of 0s: it's the same in all nodes.
496             // no need to modify level_tree for ctx=0: it starts with an infinite loop of 0s.
497             int sigindex = i_coefs == 64 ? significant_coeff_flag_offset_8x8[b_interlaced][i] : i;
498             const uint32_t cost_sig0 = x264_cabac_size_decision_noup2( &cabac_state_sig[sigindex], 0 )
499                                      * (uint64_t)i_lambda2 >> ( CABAC_SIZE_BITS - LAMBDA_BITS );
500             for( int j = 1; j < 8; j++ )
501             {
502                 if( nodes_cur[j].score != TRELLIS_SCORE_MAX )
503                 {
504 #define SET_LEVEL(n,l) \
505                     level_tree[i_levels_used].abs_level = l; \
506                     level_tree[i_levels_used].next = n.level_idx; \
507                     n.level_idx = i_levels_used; \
508                     i_levels_used++;
509
510                     SET_LEVEL( nodes_cur[j], 0 );
511                     nodes_cur[j].score += cost_sig0;
512                 }
513             }
514             continue;
515         }
516
517         XCHG( trellis_node_t*, nodes_cur, nodes_prev );
518
519         for( int j = 0; j < 8; j++ )
520             nodes_cur[j].score = TRELLIS_SCORE_MAX;
521
522         if( i < i_coefs-1 )
523         {
524             int sigindex = i_coefs == 64 ? significant_coeff_flag_offset_8x8[b_interlaced][i] : i;
525             int lastindex = i_coefs == 64 ? last_coeff_flag_offset_8x8[i] : i;
526             cost_sig[0] = x264_cabac_size_decision_noup2( &cabac_state_sig[sigindex], 0 );
527             cost_sig[1] = x264_cabac_size_decision_noup2( &cabac_state_sig[sigindex], 1 );
528             cost_last[0] = x264_cabac_size_decision_noup2( &cabac_state_last[lastindex], 0 );
529             cost_last[1] = x264_cabac_size_decision_noup2( &cabac_state_last[lastindex], 1 );
530         }
531         else
532         {
533             cost_sig[0] = cost_sig[1] = 0;
534             cost_last[0] = cost_last[1] = 0;
535         }
536
537         // there are a few cases where increasing the coeff magnitude helps,
538         // but it's only around .003 dB, and skipping them ~doubles the speed of trellis.
539         // could also try q-2: that sometimes helps, but also sometimes decimates blocks
540         // that are better left coded, especially at QP > 40.
541         for( int abs_level = q; abs_level >= q-1; abs_level-- )
542         {
543             int unquant_abs_level = (((dc?unquant_mf[0]<<1:unquant_mf[zigzag[i]]) * abs_level + 128) >> 8);
544             int d = i_coef - unquant_abs_level;
545             int64_t ssd;
546             /* Psy trellis: bias in favor of higher AC coefficients in the reconstructed frame. */
547             if( h->mb.i_psy_trellis && i && !dc && i_ctxBlockCat != DCT_CHROMA_AC )
548             {
549                 int orig_coef = (i_coefs == 64) ? h->mb.pic.fenc_dct8[idx][zigzag[i]] : h->mb.pic.fenc_dct4[idx][zigzag[i]];
550                 int predicted_coef = orig_coef - i_coef * signs[i];
551                 int psy_value = h->mb.i_psy_trellis * abs(predicted_coef + unquant_abs_level * signs[i]);
552                 int psy_weight = (i_coefs == 64) ? x264_dct8_weight_tab[zigzag[i]] : x264_dct4_weight_tab[zigzag[i]];
553                 ssd = (int64_t)d*d * coef_weight[i] - psy_weight * psy_value;
554             }
555             else
556             /* FIXME: for i16x16 dc is this weight optimal? */
557                 ssd = (int64_t)d*d * (dc?256:coef_weight[i]);
558
559             for( int j = 0; j < 8; j++ )
560             {
561                 int node_ctx = j;
562                 if( nodes_prev[j].score == TRELLIS_SCORE_MAX )
563                     continue;
564                 n = nodes_prev[j];
565
566                 /* code the proposed level, and count how much entropy it would take */
567                 if( abs_level || node_ctx )
568                 {
569                     unsigned f8_bits = cost_sig[ abs_level != 0 ];
570                     if( abs_level )
571                     {
572                         const int i_prefix = X264_MIN( abs_level - 1, 14 );
573                         f8_bits += cost_last[ node_ctx == 0 ];
574                         f8_bits += x264_cabac_size_decision2( &n.cabac_state[coeff_abs_level1_ctx[node_ctx]], i_prefix > 0 );
575                         if( i_prefix > 0 )
576                         {
577                             uint8_t *ctx = &n.cabac_state[coeff_abs_levelgt1_ctx[node_ctx]];
578                             f8_bits += cabac_size_unary[i_prefix][*ctx];
579                             *ctx = cabac_transition_unary[i_prefix][*ctx];
580                             if( abs_level >= 15 )
581                                 f8_bits += bs_size_ue_big( abs_level - 15 ) << CABAC_SIZE_BITS;
582                             node_ctx = coeff_abs_level_transition[1][node_ctx];
583                         }
584                         else
585                         {
586                             f8_bits += 1 << CABAC_SIZE_BITS;
587                             node_ctx = coeff_abs_level_transition[0][node_ctx];
588                         }
589                     }
590                     n.score += (uint64_t)f8_bits * i_lambda2 >> ( CABAC_SIZE_BITS - LAMBDA_BITS );
591                 }
592
593                 if( j || i || dc )
594                     n.score += ssd;
595                 /* Optimize rounding for DC coefficients in DC-only luma 4x4/8x8 blocks. */
596                 else
597                 {
598                     d = i_coef * signs[0] - ((unquant_abs_level * signs[0] + 8)&~15);
599                     n.score += (int64_t)d*d * coef_weight[i];
600                 }
601
602                 /* save the node if it's better than any existing node with the same cabac ctx */
603                 if( n.score < nodes_cur[node_ctx].score )
604                 {
605                     SET_LEVEL( n, abs_level );
606                     nodes_cur[node_ctx] = n;
607                 }
608             }
609         }
610     }
611
612     /* output levels from the best path through the trellis */
613     bnode = &nodes_cur[0];
614     for( int j = 1; j < 8; j++ )
615         if( nodes_cur[j].score < bnode->score )
616             bnode = &nodes_cur[j];
617
618     if( bnode == &nodes_cur[0] )
619     {
620         if( i_coefs == 16 && !dc )
621             memset( dct, 0, 16 * sizeof(dctcoef) );
622         return 0;
623     }
624
625     int level = bnode->level_idx;
626     for( i = b_ac; level; i++ )
627     {
628         dct[zigzag[i]] = level_tree[level].abs_level * signs[i];
629         level = level_tree[level].next;
630     }
631     for( ; i < i_coefs; i++ )
632         dct[zigzag[i]] = 0;
633
634     return 1;
635 }
636
637 /* FIXME: This is a gigantic hack.  See below.
638  *
639  * CAVLC is much more difficult to trellis than CABAC.
640  *
641  * CABAC has only three states to track: significance map, last, and the
642  * level state machine.
643  * CAVLC, by comparison, has five: coeff_token (trailing + total),
644  * total_zeroes, zero_run, and the level state machine.
645  *
646  * I know of no paper that has managed to design a close-to-optimal trellis
647  * that covers all five of these and isn't exponential-time.  As a result, this
648  * "trellis" isn't: it's just a QNS search.  Patches welcome for something better.
649  * It's actually surprisingly fast, albeit not quite optimal.  It's pretty close
650  * though; since CAVLC only has 2^16 possible rounding modes (assuming only two
651  * roundings as options), a bruteforce search is feasible.  Testing shows
652  * that this QNS is reasonably close to optimal in terms of compression.
653  *
654  * TODO:
655  *  Don't bother changing large coefficients when it wouldn't affect bit cost
656  *  (e.g. only affecting bypassed suffix bits).
657  *  Don't re-run all parts of CAVLC bit cost calculation when not necessary.
658  *  e.g. when changing a coefficient from one non-zero value to another in
659  *  such a way that trailing ones and suffix length isn't affected. */
660 static ALWAYS_INLINE
661 int quant_trellis_cavlc( x264_t *h, dctcoef *dct,
662                          const uint16_t *quant_mf, const int *unquant_mf,
663                          const int *coef_weight, const uint8_t *zigzag,
664                          int i_ctxBlockCat, int i_lambda2, int b_ac,
665                          int dc, int i_coefs, int idx, int b_8x8 )
666 {
667     ALIGNED_16( dctcoef quant_coefs[2][16] );
668     ALIGNED_16( dctcoef coefs[16] ) = {0};
669     int delta_distortion[16];
670     int64_t score = 1ULL<<62;
671     int i, j;
672     const int f = 1<<15;
673     int nC = i_ctxBlockCat == DCT_CHROMA_DC ? 4 : ct_index[x264_mb_predict_non_zero_code( h, i_ctxBlockCat == DCT_LUMA_DC ? 0 : idx )];
674
675     /* Code for handling 8x8dct -> 4x4dct CAVLC munging.  Input/output use a different
676      * step/start/end than internal processing. */
677     int step = 1;
678     int start = b_ac;
679     int end = i_coefs - 1;
680     if( b_8x8 )
681     {
682         start = idx&3;
683         end = 60 + start;
684         step = 4;
685     }
686
687     i_lambda2 <<= LAMBDA_BITS;
688
689     /* Find last non-zero coefficient. */
690     for( i = end; i >= start; i -= step )
691         if( (unsigned)(dct[zigzag[i]] * (dc?quant_mf[0]>>1:quant_mf[zigzag[i]]) + f-1) >= 2*f )
692             break;
693
694     if( i < start )
695         goto zeroblock;
696
697     /* Prepare for QNS search: calculate distortion caused by each DCT coefficient
698      * rounding to be searched.
699      *
700      * We only search two roundings (nearest and nearest-1) like in CABAC trellis,
701      * so we just store the difference in distortion between them. */
702     int i_last_nnz = b_8x8 ? i >> 2 : i;
703     int coef_mask = 0;
704     int round_mask = 0;
705     for( i = b_ac, j = start; i <= i_last_nnz; i++, j += step )
706     {
707         int coef = dct[zigzag[j]];
708         int abs_coef = abs(coef);
709         int sign = coef < 0 ? -1 : 1;
710         int nearest_quant = ( f + abs_coef * (dc?quant_mf[0]>>1:quant_mf[zigzag[j]]) ) >> 16;
711         quant_coefs[1][i] = quant_coefs[0][i] = sign * nearest_quant;
712         coefs[i] = quant_coefs[1][i];
713         if( nearest_quant )
714         {
715             /* We initialize the trellis with a deadzone halfway between nearest rounding
716              * and always-round-down.  This gives much better results than initializing to either
717              * extreme.
718              * FIXME: should we initialize to the deadzones used by deadzone quant? */
719             int deadzone_quant = ( f/2 + abs_coef * (dc?quant_mf[0]>>1:quant_mf[zigzag[j]]) ) >> 16;
720             int unquant1 = (((dc?unquant_mf[0]<<1:unquant_mf[zigzag[j]]) * (nearest_quant-0) + 128) >> 8);
721             int unquant0 = (((dc?unquant_mf[0]<<1:unquant_mf[zigzag[j]]) * (nearest_quant-1) + 128) >> 8);
722             int d1 = abs_coef - unquant1;
723             int d0 = abs_coef - unquant0;
724             delta_distortion[i] = (d0*d0 - d1*d1) * (dc?256:coef_weight[j]);
725
726             /* Psy trellis: bias in favor of higher AC coefficients in the reconstructed frame. */
727             if( h->mb.i_psy_trellis && j && !dc && i_ctxBlockCat != DCT_CHROMA_AC )
728             {
729                 int orig_coef = b_8x8 ? h->mb.pic.fenc_dct8[idx>>2][zigzag[j]] : h->mb.pic.fenc_dct4[idx][zigzag[j]];
730                 int predicted_coef = orig_coef - coef;
731                 int psy_weight = b_8x8 ? x264_dct8_weight_tab[zigzag[j]] : x264_dct4_weight_tab[zigzag[j]];
732                 int psy_value0 = h->mb.i_psy_trellis * abs(predicted_coef + unquant0 * sign);
733                 int psy_value1 = h->mb.i_psy_trellis * abs(predicted_coef + unquant1 * sign);
734                 delta_distortion[i] += (psy_value0 - psy_value1) * psy_weight;
735             }
736
737             quant_coefs[0][i] = sign * (nearest_quant-1);
738             if( deadzone_quant != nearest_quant )
739                 coefs[i] = quant_coefs[0][i];
740             else
741                 round_mask |= 1 << i;
742         }
743         else
744             delta_distortion[i] = 0;
745         coef_mask |= (!!coefs[i]) << i;
746     }
747
748     /* Calculate the cost of the starting state. */
749     h->out.bs.i_bits_encoded = 0;
750     if( !coef_mask )
751         bs_write_vlc( &h->out.bs, x264_coeff0_token[nC] );
752     else
753         block_residual_write_cavlc_internal( h, i_ctxBlockCat, coefs + b_ac, nC );
754     score = (int64_t)h->out.bs.i_bits_encoded * i_lambda2;
755
756     /* QNS loop: pick the change that improves RD the most, apply it, repeat.
757      * coef_mask and round_mask are used to simplify tracking of nonzeroness
758      * and rounding modes chosen. */
759     while( 1 )
760     {
761         int64_t iter_score = score;
762         int iter_distortion_delta = 0;
763         int iter_coef = -1;
764         int iter_mask = coef_mask;
765         int iter_round = round_mask;
766         for( i = b_ac; i <= i_last_nnz; i++ )
767         {
768             if( !delta_distortion[i] )
769                 continue;
770
771             /* Set up all the variables for this iteration. */
772             int cur_round = round_mask ^ (1 << i);
773             int round_change = (cur_round >> i)&1;
774             int old_coef = coefs[i];
775             int new_coef = quant_coefs[round_change][i];
776             int cur_mask = (coef_mask&~(1 << i))|(!!new_coef << i);
777             int cur_distortion_delta = delta_distortion[i] * (round_change ? -1 : 1);
778             int64_t cur_score = cur_distortion_delta;
779             coefs[i] = new_coef;
780
781             /* Count up bits. */
782             h->out.bs.i_bits_encoded = 0;
783             if( !cur_mask )
784                 bs_write_vlc( &h->out.bs, x264_coeff0_token[nC] );
785             else
786                 block_residual_write_cavlc_internal( h, i_ctxBlockCat, coefs + b_ac, nC );
787             cur_score += (int64_t)h->out.bs.i_bits_encoded * i_lambda2;
788
789             coefs[i] = old_coef;
790             if( cur_score < iter_score )
791             {
792                 iter_score = cur_score;
793                 iter_coef = i;
794                 iter_mask = cur_mask;
795                 iter_round = cur_round;
796                 iter_distortion_delta = cur_distortion_delta;
797             }
798         }
799         if( iter_coef >= 0 )
800         {
801             score = iter_score - iter_distortion_delta;
802             coef_mask = iter_mask;
803             round_mask = iter_round;
804             coefs[iter_coef] = quant_coefs[((round_mask >> iter_coef)&1)][iter_coef];
805             /* Don't try adjusting coefficients we've already adjusted.
806              * Testing suggests this doesn't hurt results -- and sometimes actually helps. */
807             delta_distortion[iter_coef] = 0;
808         }
809         else
810             break;
811     }
812
813     if( coef_mask )
814     {
815         for( i = b_ac, j = start; i <= i_last_nnz; i++, j += step )
816             dct[zigzag[j]] = coefs[i];
817         for( ; j <= end; j += step )
818             dct[zigzag[j]] = 0;
819         return 1;
820     }
821
822 zeroblock:
823     if( !dc )
824     {
825         if( b_8x8 )
826             for( i = start; i <= end; i+=step )
827                 dct[zigzag[i]] = 0;
828         else
829             memset( dct, 0, 16*sizeof(dctcoef) );
830     }
831     return 0;
832 }
833
834 const static uint8_t x264_zigzag_scan2[4] = {0,1,2,3};
835
836 int x264_quant_dc_trellis( x264_t *h, dctcoef *dct, int i_quant_cat,
837                            int i_qp, int i_ctxBlockCat, int b_intra, int b_chroma )
838 {
839     if( h->param.b_cabac )
840         return quant_trellis_cabac( h, dct,
841             h->quant4_mf[i_quant_cat][i_qp], h->unquant4_mf[i_quant_cat][i_qp],
842             NULL, i_ctxBlockCat==DCT_CHROMA_DC ? x264_zigzag_scan2 : x264_zigzag_scan4[h->mb.b_interlaced],
843             i_ctxBlockCat, h->mb.i_trellis_lambda2[b_chroma][b_intra], 0, 1, i_ctxBlockCat==DCT_CHROMA_DC ? 4 : 16, 0 );
844
845     return quant_trellis_cavlc( h, dct,
846         h->quant4_mf[i_quant_cat][i_qp], h->unquant4_mf[i_quant_cat][i_qp],
847         NULL, i_ctxBlockCat==DCT_CHROMA_DC ? x264_zigzag_scan2 : x264_zigzag_scan4[h->mb.b_interlaced],
848         i_ctxBlockCat, h->mb.i_trellis_lambda2[b_chroma][b_intra], 0, 1, i_ctxBlockCat==DCT_CHROMA_DC ? 4 : 16, 0, 0 );
849 }
850
851 int x264_quant_4x4_trellis( x264_t *h, dctcoef *dct, int i_quant_cat,
852                             int i_qp, int i_ctxBlockCat, int b_intra, int b_chroma, int idx )
853 {
854     int b_ac = (i_ctxBlockCat == DCT_LUMA_AC || i_ctxBlockCat == DCT_CHROMA_AC);
855     if( h->param.b_cabac )
856         return quant_trellis_cabac( h, dct,
857             h->quant4_mf[i_quant_cat][i_qp], h->unquant4_mf[i_quant_cat][i_qp],
858             x264_dct4_weight2_zigzag[h->mb.b_interlaced],
859             x264_zigzag_scan4[h->mb.b_interlaced],
860             i_ctxBlockCat, h->mb.i_trellis_lambda2[b_chroma][b_intra], b_ac, 0, 16, idx );
861
862     return quant_trellis_cavlc( h, dct,
863             h->quant4_mf[i_quant_cat][i_qp], h->unquant4_mf[i_quant_cat][i_qp],
864             x264_dct4_weight2_zigzag[h->mb.b_interlaced],
865             x264_zigzag_scan4[h->mb.b_interlaced],
866             i_ctxBlockCat, h->mb.i_trellis_lambda2[b_chroma][b_intra], b_ac, 0, 16, idx, 0 );
867 }
868
869 int x264_quant_8x8_trellis( x264_t *h, dctcoef *dct, int i_quant_cat,
870                             int i_qp, int b_intra, int idx )
871 {
872     if( h->param.b_cabac )
873     {
874         return quant_trellis_cabac( h, dct,
875             h->quant8_mf[i_quant_cat][i_qp], h->unquant8_mf[i_quant_cat][i_qp],
876             x264_dct8_weight2_zigzag[h->mb.b_interlaced],
877             x264_zigzag_scan8[h->mb.b_interlaced],
878             DCT_LUMA_8x8, h->mb.i_trellis_lambda2[0][b_intra], 0, 0, 64, idx );
879     }
880
881     /* 8x8 CAVLC is split into 4 4x4 blocks */
882     int nzaccum = 0;
883     for( int i = 0; i < 4; i++ )
884     {
885         int nz = quant_trellis_cavlc( h, dct,
886             h->quant8_mf[i_quant_cat][i_qp], h->unquant8_mf[i_quant_cat][i_qp],
887             x264_dct8_weight2_zigzag[h->mb.b_interlaced],
888             x264_zigzag_scan8[h->mb.b_interlaced],
889             DCT_LUMA_4x4, h->mb.i_trellis_lambda2[0][b_intra], 0, 0, 16, idx*4+i, 1 );
890         /* Set up nonzero count for future calls */
891         h->mb.cache.non_zero_count[x264_scan8[idx*4+i]] = nz;
892         nzaccum |= nz;
893     }
894     return nzaccum;
895 }