]> git.sesse.net Git - x264/blob - common/x86/trellis-64.asm
Bump dates to 2013
[x264] / common / x86 / trellis-64.asm
1 ;*****************************************************************************
2 ;* trellis-64.asm: x86_64 trellis quantization
3 ;*****************************************************************************
4 ;* Copyright (C) 2012-2013 x264 project
5 ;*
6 ;* Authors: Loren Merritt <lorenm@u.washington.edu>
7 ;*
8 ;* This program is free software; you can redistribute it and/or modify
9 ;* it under the terms of the GNU General Public License as published by
10 ;* the Free Software Foundation; either version 2 of the License, or
11 ;* (at your option) any later version.
12 ;*
13 ;* This program is distributed in the hope that it will be useful,
14 ;* but WITHOUT ANY WARRANTY; without even the implied warranty of
15 ;* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
16 ;* GNU General Public License for more details.
17 ;*
18 ;* You should have received a copy of the GNU General Public License
19 ;* along with this program; if not, write to the Free Software
20 ;* Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02111, USA.
21 ;*
22 ;* This program is also available under a commercial proprietary license.
23 ;* For more information, contact us at licensing@x264.com.
24 ;*****************************************************************************
25
26 ; This is a pretty straight-forward translation of the C code, except:
27 ; * simd ssd and psy: 2x parallel, handling the 2 candidate values of abs_level.
28 ; * simd trellis_coef0, ZERO_LEVEL_IDX, and the coef0 part of the main loop:
29 ;   4x parallel, handling 4 node_ctxs of the same coef (even if some of those
30 ;   nodes are invalid).
31 ; * Interprocedural register allocation. Eliminates argument-passing overhead
32 ;   to trellis_coef* subroutines. Also reduces codesize.
33
34 ; Optimizations that I tried, and rejected because they were not faster:
35 ; * Separate loops for node_ctx [4..7] or smaller subsets of [0..3].
36 ;   Costs too much icache compared to the negligible speedup.
37 ; * There are only 21 possible sets of live node_ctxs; we could keep track of
38 ;   exactly which set we're in and feed that (along with abs_level) into a jump
39 ;   table instead of the switch to select a trellis_coef subroutine. This would
40 ;   eliminate all branches about which node_ctxs are live, but costs either a
41 ;   bunch of icache or a bunch of call/ret, and the jump table itself is
42 ;   unpredictable.
43 ; * Separate versions of trellis_coef* depending on whether we're doing the 1st
44 ;   or the 2nd of the two abs_level candidates. This would eliminate some
45 ;   branches about if(score is better).
46 ; * Special case more values of coef. I had a coef2 at some intermediate point
47 ;   in the optimization process, but it didn't end up worthwhile in conjunction
48 ;   with all the other optimizations.
49 ; * Unroll or simd writeback. I don't know why this didn't help.
50
51 %include "x86inc.asm"
52 %include "x86util.asm"
53
54 SECTION_RODATA
55
56 pd_8: times 4 dd 8
57 pd_m16: times 4 dd -16
58 pd_0123: dd 0, 1, 2, 3
59 pd_4567: dd 4, 5, 6, 7
60 sq_1: dq 1, 0
61 pq_128: times 2 dq 128
62 pq_ffffffff: times 2 dq 0xffffffff
63
64 cextern cabac_entropy
65 cextern cabac_transition
66 cextern cabac_size_unary
67 cextern cabac_transition_unary
68 cextern dct4_weight_tab
69 cextern dct8_weight_tab
70 cextern dct4_weight2_tab
71 cextern dct8_weight2_tab
72 cextern last_coeff_flag_offset_8x8
73 cextern significant_coeff_flag_offset_8x8
74 cextern coeff_flag_offset_chroma_422_dc
75
76 SECTION .text
77
78 %define TRELLIS_SCORE_BIAS 1<<60
79 %define SIZEOF_NODE 16
80 %define CABAC_SIZE_BITS 8
81 %define LAMBDA_BITS 4
82
83 %macro SQUARE 2 ; dst, tmp
84     ; could use pmuldq here, to eliminate the abs. but that would involve
85     ; templating a sse4 version of all of trellis, for negligible speedup.
86 %if cpuflag(ssse3)
87     pabsd   m%1, m%1
88     pmuludq m%1, m%1
89 %elif HIGH_BIT_DEPTH
90     ABSD    m%2, m%1
91     SWAP     %1, %2
92     pmuludq m%1, m%1
93 %else
94     pmuludq m%1, m%1
95     pand    m%1, [pq_ffffffff]
96 %endif
97 %endmacro
98
99 ;-----------------------------------------------------------------------------
100 ; int trellis_cabac_4x4_psy(
101 ;     const int *unquant_mf, const uint8_t *zigzag, int lambda2,
102 ;     int last_nnz, dctcoef *orig_coefs, dctcoef *quant_coefs, dctcoef *dct,
103 ;     uint8_t *cabac_state_sig, uint8_t *cabac_state_last,
104 ;     uint64_t level_state0, uint16_t level_state1,
105 ;     int b_ac, dctcoef *fenc_dct, int psy_trellis )
106 ;-----------------------------------------------------------------------------
107 %macro TRELLIS 4
108 %define num_coefs %2
109 %define dc %3
110 %define psy %4
111 cglobal %1, 4,15,9
112     %assign level_tree_size 64*8*2*4 ; could depend on num_coefs, but nonuniform stack size would prevent accessing args from trellis_coef*
113     %assign pad 96 + level_tree_size + 16*SIZEOF_NODE + 16-gprsize-(stack_offset&15)
114     SUB  rsp, pad
115     DEFINE_ARGS unquant_mf, zigzag, lambda2, ii, orig_coefs, quant_coefs, dct, cabac_state_sig, cabac_state_last
116 %if WIN64
117     %define level_statem rsp+stack_offset+80 ; r9m, except that we need to index into it (and r10m) as an array
118 %else
119     %define level_statem rsp+stack_offset+32
120 %endif
121     %define b_acm r11m ; 4x4 only
122     %define b_interlacedm r11m ; 8x8 only
123     %define i_coefsm1 r11m ; dc only
124     %define fenc_dctm r12m
125     %define psy_trellism r13m
126 %if num_coefs == 64
127     shl dword b_interlacedm, 6
128     %define dct_weight1_tab dct8_weight_tab
129     %define dct_weight2_tab dct8_weight2_tab
130 %else
131     %define dct_weight1_tab dct4_weight_tab
132     %define dct_weight2_tab dct4_weight2_tab
133 %endif
134
135     %define stack rsp
136     %define last_nnzm [stack+0]
137     %define zigzagm   [stack+8]
138     mov     last_nnzm, iid
139     mov     zigzagm,   zigzagq
140 %if WIN64 == 0
141     %define orig_coefsm  [stack+16]
142     %define quant_coefsm [stack+24]
143     mov     orig_coefsm,  orig_coefsq
144     mov     quant_coefsm, quant_coefsq
145 %endif
146     %define unquant_mfm   [stack+32]
147     %define levelgt1_ctxm [stack+40]
148     %define ssd            stack+48
149     %define cost_siglast   stack+80
150     %define level_tree     stack+96
151
152     ; trellis_node_t is layed out differently than C.
153     ; struct-of-arrays rather than array-of-structs, for simd.
154     %define nodes_curq r7
155     %define nodes_prevq r8
156     %define node_score(x) x*8
157     %define node_level_idx(x) 64+x*4
158     %define node_cabac_state(x) 96+x*4
159     lea nodes_curq, [level_tree + level_tree_size]
160     lea nodes_prevq, [nodes_curq + 8*SIZEOF_NODE]
161     mov        r6, TRELLIS_SCORE_BIAS
162     mov       [nodes_curq + node_score(0)], r6
163     mov dword [nodes_curq + node_level_idx(0)], 0
164     movd      mm0, [level_statem + 0]
165     punpcklbw mm0, [level_statem + 4]
166     punpcklwd mm0, [level_statem + 8]
167     %define level_state_packed mm0 ; version for copying into node.cabac_state
168     pcmpeqb    m7, m7 ; TRELLIS_SCORE_MAX
169     movq [nodes_curq + node_score(1)], m7
170     mova [nodes_curq + node_score(2)], m7
171
172     %define levels_usedq r4
173     %define levels_usedd r4d
174     mov dword [level_tree], 0
175     mov       levels_usedd, 1
176
177     %define abs_levelq r9
178     %define abs_leveld r9d
179     %define abs_coefq r14
180     %define zigzagiq r5
181     %define zigzagid r5d
182
183 %if num_coefs == 8
184     mov dword levelgt1_ctxm, 8
185 %else
186     mov dword levelgt1_ctxm, 9
187 %endif
188 %if psy
189     movd    m6, psy_trellism
190     %define psy_trellis m6
191 %elif dc
192     movd       m6, [unquant_mfq]
193     paddd      m6, m6
194     punpcklqdq m6, m6
195     %define unquant_mf m6
196 %endif
197 %ifdef PIC
198 %if dc == 0
199     mov unquant_mfm, unquant_mfq
200 %endif
201     ; Keep a single offset register to PICify all global constants.
202     ; They're all relative to "beginning of this asm file's .text section",
203     ; even tables that aren't in this file.
204     ; (Any address in .text would work, this one was just convenient.)
205     lea r0, [$$]
206     %define GLOBAL +r0-$$
207 %else
208     %define GLOBAL
209 %endif
210
211     TRELLIS_LOOP 0 ; node_ctx 0..3
212     TRELLIS_LOOP 1 ; node_ctx 1..7
213
214 .writeback:
215     ; int level = bnode->level_idx;
216     ; for( int i = b_ac; i <= last_nnz; i++ )
217     ;     dct[zigzag[i]] = SIGN(level_tree[level].abs_level, orig_coefs[zigzag[i]]);
218     ;     level = level_tree[level].next;
219     mov    iid, last_nnzm
220     add zigzagq, iiq
221     neg    iiq
222 %if num_coefs == 16 && dc == 0
223     mov    r2d, b_acm
224     add    iiq, r2
225 %endif
226     %define dctq r10
227     mov    r0d, [nodes_curq + node_level_idx(0) + rax*4]
228 .writeback_loop:
229     movzx   r2, byte [zigzagq + iiq]
230 %if cpuflag(ssse3)
231     movd    m0, [level_tree + r0*4]
232     movzx   r0, word [level_tree + r0*4]
233     psrld   m0, 16
234     movd    m1, [dctq + r2*SIZEOF_DCTCOEF]
235 %if HIGH_BIT_DEPTH
236     psignd  m0, m1
237     movd [dctq + r2*SIZEOF_DCTCOEF], m0
238 %else
239     psignw  m0, m1
240     movd   r4d, m0
241     mov  [dctq + r2*SIZEOF_DCTCOEF], r4w
242 %endif
243 %else
244     mov    r5d, [level_tree + r0*4]
245 %if HIGH_BIT_DEPTH
246     mov    r4d, dword [dctq + r2*SIZEOF_DCTCOEF]
247 %else
248     movsx  r4d, word [dctq + r2*SIZEOF_DCTCOEF]
249 %endif
250     movzx  r0d, r5w
251     sar    r4d, 31
252     shr    r5d, 16
253     xor    r5d, r4d
254     sub    r5d, r4d
255 %if HIGH_BIT_DEPTH
256     mov  [dctq + r2*SIZEOF_DCTCOEF], r5d
257 %else
258     mov  [dctq + r2*SIZEOF_DCTCOEF], r5w
259 %endif
260 %endif
261     inc    iiq
262     jle .writeback_loop
263
264     mov eax, 1
265 .return:
266     ADD rsp, pad
267     RET
268
269 %if num_coefs == 16 && dc == 0
270 .return_zero:
271     pxor       m0, m0
272     mova [r10+ 0], m0
273     mova [r10+16], m0
274 %if HIGH_BIT_DEPTH
275     mova [r10+32], m0
276     mova [r10+48], m0
277 %endif
278     jmp .return
279 %endif
280 %endmacro ; TRELLIS
281
282
283
284 %macro TRELLIS_LOOP 1 ; ctx_hi
285 .i_loop%1:
286     ; if( !quant_coefs[i] )
287     mov   r6, quant_coefsm
288 %if HIGH_BIT_DEPTH
289     mov   abs_leveld, dword [r6 + iiq*SIZEOF_DCTCOEF]
290 %else
291     movsx abs_leveld, word [r6 + iiq*SIZEOF_DCTCOEF]
292 %endif
293
294     ; int sigindex  = num_coefs == 64 ? significant_coeff_flag_offset_8x8[b_interlaced][i] :
295     ;                 num_coefs == 8  ? coeff_flag_offset_chroma_422_dc[i] : i;
296     mov    r10, cabac_state_sigm
297 %if num_coefs == 64
298     mov    r6d, b_interlacedm
299 %ifdef PIC
300     add    r6d, iid
301     movzx  r6d, byte [significant_coeff_flag_offset_8x8 + r6 GLOBAL]
302 %else
303     movzx  r6d, byte [significant_coeff_flag_offset_8x8 + r6 + iiq]
304 %endif
305     movzx  r10, byte [r10 + r6]
306 %elif num_coefs == 8
307     movzx  r13, byte [coeff_flag_offset_chroma_422_dc + iiq GLOBAL]
308     movzx  r10, byte [r10 + r13]
309 %else
310     movzx  r10, byte [r10 + iiq]
311 %endif
312
313     test  abs_leveld, abs_leveld
314     jnz %%.nonzero_quant_coef
315
316 %if %1 == 0
317     ; int cost_sig0 = x264_cabac_size_decision_noup2( &cabac_state_sig[sigindex], 0 )
318     ;               * (uint64_t)lambda2 >> ( CABAC_SIZE_BITS - LAMBDA_BITS );
319     ; nodes_cur[0].score -= cost_sig0;
320     movzx  r10, word [cabac_entropy + r10*2 GLOBAL]
321     imul   r10, lambda2q
322     shr    r10, CABAC_SIZE_BITS - LAMBDA_BITS
323     sub   [nodes_curq + node_score(0)], r10
324 %endif
325     ZERO_LEVEL_IDX %1, cur
326     jmp .i_continue%1
327
328 %%.nonzero_quant_coef:
329     ; int sign_coef = orig_coefs[zigzag[i]];
330     ; int abs_coef = abs( sign_coef );
331     ; int q = abs( quant_coefs[i] );
332     movzx   zigzagid, byte [zigzagq+iiq]
333     movd    m0, abs_leveld
334     mov     r6, orig_coefsm
335 %if HIGH_BIT_DEPTH
336     movd    m1, [r6 + zigzagiq*SIZEOF_DCTCOEF]
337 %else
338     movd    m1, [r6 + zigzagiq*SIZEOF_DCTCOEF - 2]
339     psrad   m1, 16
340 %endif
341     punpcklqdq m0, m0 ; quant_coef
342     punpcklqdq m1, m1 ; sign_coef
343 %if cpuflag(ssse3)
344     pabsd   m0, m0
345     pabsd   m2, m1 ; abs_coef
346 %else
347     pxor    m8, m8
348     pcmpgtd m8, m1 ; sign_mask
349     pxor    m0, m8
350     pxor    m2, m1, m8
351     psubd   m0, m8
352     psubd   m2, m8
353 %endif
354     psubd   m0, [sq_1] ; abs_level
355     movd  abs_leveld, m0
356
357     xchg  nodes_curq, nodes_prevq
358
359     ; if( i < num_coefs-1 )
360     ;     int lastindex = num_coefs == 64 ? last_coeff_flag_offset_8x8[i] : i;
361     ;                     num_coefs == 8  ? coeff_flag_offset_chroma_422_dc[i] : i
362     ;     cost_siglast[0] = x264_cabac_size_decision_noup2( &cabac_state_sig[sigindex], 0 );
363     ;     cost_sig1       = x264_cabac_size_decision_noup2( &cabac_state_sig[sigindex], 1 );
364     ;     cost_siglast[1] = x264_cabac_size_decision_noup2( &cabac_state_last[lastindex], 0 ) + cost_sig1;
365     ;     cost_siglast[2] = x264_cabac_size_decision_noup2( &cabac_state_last[lastindex], 1 ) + cost_sig1;
366 %if %1 == 0
367 %if dc && num_coefs != 8
368     cmp    iid, i_coefsm1
369 %else
370     cmp    iid, num_coefs-1
371 %endif
372     je %%.zero_siglast
373 %endif
374     movzx  r11, word [cabac_entropy + r10*2 GLOBAL]
375     xor    r10, 1
376     movzx  r12, word [cabac_entropy + r10*2 GLOBAL]
377     mov   [cost_siglast+0], r11d
378     mov    r10, cabac_state_lastm
379 %if num_coefs == 64
380     movzx  r6d, byte [last_coeff_flag_offset_8x8 + iiq GLOBAL]
381     movzx  r10, byte [r10 + r6]
382 %elif num_coefs == 8
383     movzx  r10, byte [r10 + r13]
384 %else
385     movzx  r10, byte [r10 + iiq]
386 %endif
387     movzx  r11, word [cabac_entropy + r10*2 GLOBAL]
388     add    r11, r12
389     mov   [cost_siglast+4], r11d
390 %if %1 == 0
391     xor    r10, 1
392     movzx  r10, word [cabac_entropy + r10*2 GLOBAL]
393     add    r10, r12
394     mov   [cost_siglast+8], r10d
395 %endif
396 %%.skip_siglast:
397
398     ; int unquant_abs_level = ((unquant_mf[zigzag[i]] * abs_level + 128) >> 8);
399     ; int d = abs_coef - unquant_abs_level;
400     ; uint64_t ssd = (int64_t)d*d * coef_weight[i];
401 %if dc
402     pmuludq m0, unquant_mf
403 %else
404 %ifdef PIC
405     mov    r10, unquant_mfm
406     movd    m3, [r10 + zigzagiq*4]
407 %else
408     movd    m3, [unquant_mfq + zigzagiq*4]
409 %endif
410     punpcklqdq m3, m3
411     pmuludq m0, m3
412 %endif
413     paddd   m0, [pq_128]
414     psrld   m0, 8 ; unquant_abs_level
415 %if psy || dc == 0
416     mova    m4, m0
417 %endif
418     psubd   m0, m2
419     SQUARE   0, 3
420 %if dc
421     psllq   m0, 8
422 %else
423     movd    m5, [dct_weight2_tab + zigzagiq*4 GLOBAL]
424     punpcklqdq m5, m5
425     pmuludq m0, m5
426 %endif
427
428 %if psy
429     test   iid, iid
430     jz %%.dc_rounding
431     ; int predicted_coef = fenc_dct[zigzag[i]] - sign_coef
432     ; int psy_value = abs(unquant_abs_level + SIGN(predicted_coef, sign_coef));
433     ; int psy_weight = dct_weight_tab[zigzag[i]] * h->mb.i_psy_trellis;
434     ; ssd1[k] -= psy_weight * psy_value;
435     mov     r6, fenc_dctm
436 %if HIGH_BIT_DEPTH
437     movd    m3, [r6 + zigzagiq*SIZEOF_DCTCOEF]
438 %else
439     movd    m3, [r6 + zigzagiq*SIZEOF_DCTCOEF - 2]
440     psrad   m3, 16 ; orig_coef
441 %endif
442     punpcklqdq m3, m3
443 %if cpuflag(ssse3)
444     psignd  m4, m1 ; SIGN(unquant_abs_level, sign_coef)
445 %else
446     PSIGN d, m4, m8
447 %endif
448     psubd   m3, m1 ; predicted_coef
449     paddd   m4, m3
450 %if cpuflag(ssse3)
451     pabsd   m4, m4
452 %else
453     ABSD    m3, m4
454     SWAP     4, 3
455 %endif
456     movd    m1, [dct_weight1_tab + zigzagiq*4 GLOBAL]
457     pmuludq m1, psy_trellis
458     punpcklqdq m1, m1
459     pmuludq m4, m1
460     psubq   m0, m4
461 %if %1
462 %%.dc_rounding:
463 %endif
464 %endif
465 %if %1 == 0
466     mova [ssd], m0
467 %endif
468
469 %if dc == 0 && %1 == 0
470     test   iid, iid
471     jnz %%.skip_dc_rounding
472 %%.dc_rounding:
473     ; Optimize rounding for DC coefficients in DC-only luma 4x4/8x8 blocks.
474     ; int d = abs_coef - ((unquant_abs_level + (sign_coef>>31) + 8)&~15);
475     ; uint64_t ssd = (int64_t)d*d * coef_weight[i];
476     psrad   m1, 31 ; sign_coef>>31
477     paddd   m4, [pd_8]
478     paddd   m4, m1
479     pand    m4, [pd_m16] ; (unquant_abs_level + (sign_coef>>31) + 8)&~15
480     psubd   m4, m2 ; d
481     SQUARE   4, 3
482     pmuludq m4, m5
483     mova [ssd], m4
484 %%.skip_dc_rounding:
485 %endif
486     mova [ssd+16], m0
487
488     %assign stack_offset_bak stack_offset
489     cmp abs_leveld, 1
490     jl %%.switch_coef0
491 %if %1 == 0
492     mov    r10, [ssd] ; trellis_coef* args
493 %endif
494     movq   r12, m0
495     ; for( int j = 0; j < 8; j++ )
496     ;     nodes_cur[j].score = TRELLIS_SCORE_MAX;
497 %if cpuflag(ssse3)
498     mova [nodes_curq + node_score(0)], m7
499     mova [nodes_curq + node_score(2)], m7
500 %else ; avoid store-forwarding stalls on k8/k10
501 %if %1 == 0
502     movq [nodes_curq + node_score(0)], m7
503 %endif
504     movq [nodes_curq + node_score(1)], m7
505     movq [nodes_curq + node_score(2)], m7
506     movq [nodes_curq + node_score(3)], m7
507 %endif
508     mova [nodes_curq + node_score(4)], m7
509     mova [nodes_curq + node_score(6)], m7
510     je %%.switch_coef1
511 %%.switch_coefn:
512     call trellis_coefn.entry%1
513     call trellis_coefn.entry%1b
514     jmp .i_continue1
515 %%.switch_coef1:
516     call trellis_coef1.entry%1
517     call trellis_coefn.entry%1b
518     jmp .i_continue1
519 %%.switch_coef0:
520     call trellis_coef0_%1
521     call trellis_coef1.entry%1b
522
523 .i_continue%1:
524     dec iid
525 %if num_coefs == 16 && dc == 0
526     cmp iid, b_acm
527 %endif
528     jge .i_loop%1
529
530     call trellis_bnode_%1
531 %if %1 == 0
532 %if num_coefs == 16 && dc == 0
533     jz .return_zero
534 %else
535     jz .return
536 %endif
537     jmp .writeback
538
539 %%.zero_siglast:
540     xor  r6d, r6d
541     mov [cost_siglast+0], r6
542     mov [cost_siglast+8], r6d
543     jmp %%.skip_siglast
544 %endif
545 %endmacro ; TRELLIS_LOOP
546
547 ; just a synonym for %if
548 %macro IF0 1+
549 %endmacro
550 %macro IF1 1+
551     %1
552 %endmacro
553
554 %macro ZERO_LEVEL_IDX 2 ; ctx_hi, prev
555     ; for( int j = 0; j < 8; j++ )
556     ;     nodes_cur[j].level_idx = levels_used;
557     ;     level_tree[levels_used].next = (trellis_level_t){ .next = nodes_cur[j].level_idx, .abs_level = 0 };
558     ;     levels_used++;
559     add  levels_usedd, 3
560     and  levels_usedd, ~3 ; allow aligned stores
561     movd       m0, levels_usedd
562     pshufd     m0, m0, 0
563     IF%1 mova  m1, m0
564          paddd m0, [pd_0123]
565     IF%1 paddd m1, [pd_4567]
566          mova  m2, [nodes_%2q + node_level_idx(0)]
567     IF%1 mova  m3, [nodes_%2q + node_level_idx(4)]
568          mova [nodes_curq + node_level_idx(0)], m0
569     IF%1 mova [nodes_curq + node_level_idx(4)], m1
570          mova [level_tree + (levels_usedq+0)*4], m2
571     IF%1 mova [level_tree + (levels_usedq+4)*4], m3
572     add  levels_usedd, (1+%1)*4
573 %endmacro
574
575 INIT_XMM sse2
576 TRELLIS trellis_cabac_4x4, 16, 0, 0
577 TRELLIS trellis_cabac_8x8, 64, 0, 0
578 TRELLIS trellis_cabac_4x4_psy, 16, 0, 1
579 TRELLIS trellis_cabac_8x8_psy, 64, 0, 1
580 TRELLIS trellis_cabac_dc, 16, 1, 0
581 TRELLIS trellis_cabac_chroma_422_dc, 8, 1, 0
582 INIT_XMM ssse3
583 TRELLIS trellis_cabac_4x4, 16, 0, 0
584 TRELLIS trellis_cabac_8x8, 64, 0, 0
585 TRELLIS trellis_cabac_4x4_psy, 16, 0, 1
586 TRELLIS trellis_cabac_8x8_psy, 64, 0, 1
587 TRELLIS trellis_cabac_dc, 16, 1, 0
588 TRELLIS trellis_cabac_chroma_422_dc, 8, 1, 0
589
590
591
592 %define stack rsp+gprsize
593 %define scoreq r14
594 %define bitsq r13
595 %define bitsd r13d
596
597 INIT_XMM
598 %macro clocal 1
599     ALIGN 16
600     global mangle(x264_%1)
601     mangle(x264_%1):
602     %1:
603     %assign stack_offset stack_offset_bak+gprsize
604 %endmacro
605
606 %macro TRELLIS_BNODE 1 ; ctx_hi
607 clocal trellis_bnode_%1
608     ; int j = ctx_hi?1:0;
609     ; trellis_node_t *bnode = &nodes_cur[j];
610     ; while( ++j < (ctx_hi?8:4) )
611     ;     if( nodes_cur[j].score < bnode->score )
612     ;         bnode = &nodes_cur[j];
613 %assign j %1
614     mov   rax, [nodes_curq + node_score(j)]
615     lea   rax, [rax*8 + j]
616 %rep 3+3*%1
617 %assign j j+1
618     mov   r11, [nodes_curq + node_score(j)]
619     lea   r11, [r11*8 + j]
620     cmp   rax, r11
621     cmova rax, r11
622 %endrep
623     mov   r10, dctm
624     and   eax, 7
625     ret
626 %endmacro ; TRELLIS_BNODE
627 TRELLIS_BNODE 0
628 TRELLIS_BNODE 1
629
630
631 %macro TRELLIS_COEF0 1 ; ctx_hi
632 clocal trellis_coef0_%1
633     ; ssd1 += (uint64_t)cost_sig * lambda2 >> ( CABAC_SIZE_BITS - LAMBDA_BITS );
634     mov  r11d, [cost_siglast+0]
635     imul  r11, lambda2q
636     shr   r11, CABAC_SIZE_BITS - LAMBDA_BITS
637     add   r11, [ssd+16]
638 %if %1 == 0
639     ; nodes_cur[0].score = nodes_prev[0].score + ssd - ssd1;
640     mov  scoreq, [nodes_prevq + node_score(0)]
641     add  scoreq, [ssd]
642     sub  scoreq, r11
643     mov  [nodes_curq + node_score(0)], scoreq
644 %endif
645     ; memcpy
646     mov  scoreq, [nodes_prevq + node_score(1)]
647     mov  [nodes_curq + node_score(1)], scoreq
648     mova m1, [nodes_prevq + node_score(2)]
649     mova [nodes_curq + node_score(2)], m1
650 %if %1
651     mova m1, [nodes_prevq + node_score(4)]
652     mova [nodes_curq + node_score(4)], m1
653     mova m1, [nodes_prevq + node_score(6)]
654     mova [nodes_curq + node_score(6)], m1
655 %endif
656     mov  r6d, [nodes_prevq + node_cabac_state(3)]
657     mov  [nodes_curq + node_cabac_state(3)], r6d
658 %if %1
659     mova m1, [nodes_prevq + node_cabac_state(4)]
660     mova [nodes_curq + node_cabac_state(4)], m1
661 %endif
662     ZERO_LEVEL_IDX %1, prev
663     ret
664 %endmacro ; TRELLIS_COEF0
665 TRELLIS_COEF0 0
666 TRELLIS_COEF0 1
667
668
669
670 %macro START_COEF 1 ; gt1
671     ; if( (int64_t)nodes_prev[0].score < 0 ) continue;
672     mov  scoreq, [nodes_prevq + node_score(j)]
673 %if j > 0
674     test scoreq, scoreq
675     js .ctx %+ nextj_if_invalid
676 %endif
677
678     ; f8_bits += x264_cabac_size_decision2( &n.cabac_state[coeff_abs_level1_ctx[j]], abs_level > 1 );
679 %if j >= 3
680     movzx r6d, byte [nodes_prevq + node_cabac_state(j) + (coeff_abs_level1_offs>>2)] ; >> because node only stores ctx 0 and 4
681     movzx r11, byte [cabac_transition + r6*2 + %1 GLOBAL]
682 %else
683     movzx r6d, byte [level_statem + coeff_abs_level1_offs]
684 %endif
685 %if %1
686     xor   r6d, 1
687 %endif
688     movzx bitsd, word [cabac_entropy + r6*2 GLOBAL]
689
690     ; n.score += ssd;
691     ; unsigned f8_bits = cost_siglast[ j ? 1 : 2 ];
692 %if j == 0
693     add  scoreq, r10
694     add  bitsd, [cost_siglast+8]
695 %else
696     add  scoreq, r12
697     add  bitsd, [cost_siglast+4]
698 %endif
699 %endmacro ; START_COEF
700
701 %macro END_COEF 1
702     ; n.score += (uint64_t)f8_bits * lambda2 >> ( CABAC_SIZE_BITS - LAMBDA_BITS );
703     imul bitsq, lambda2q
704     shr  bitsq, CABAC_SIZE_BITS - LAMBDA_BITS
705     add  scoreq, bitsq
706
707     ; if( n.score < nodes_cur[node_ctx].score )
708     ;     SET_LEVEL( n, abs_level );
709     ;     nodes_cur[node_ctx] = n;
710     cmp scoreq, [nodes_curq + node_score(node_ctx)]
711     jae .ctx %+ nextj_if_valid
712     mov [nodes_curq + node_score(node_ctx)], scoreq
713 %if j == 2 || (j <= 3 && node_ctx == 4)
714     ; if this node hasn't previously needed to keep track of abs_level cabac_state, import a pristine copy of the input states
715     movd [nodes_curq + node_cabac_state(node_ctx)], level_state_packed
716 %elif j >= 3
717     ; if we have updated before, then copy cabac_state from the parent node
718     mov  r6d, [nodes_prevq + node_cabac_state(j)]
719     mov [nodes_curq + node_cabac_state(node_ctx)], r6d
720 %endif
721 %if j >= 3 ; skip the transition if we're not going to reuse the context
722     mov [nodes_curq + node_cabac_state(node_ctx) + (coeff_abs_level1_offs>>2)], r11b ; delayed from x264_cabac_size_decision2
723 %endif
724 %if %1 && node_ctx == 7
725     mov  r6d, levelgt1_ctxm
726     mov [nodes_curq + node_cabac_state(node_ctx) + coeff_abs_levelgt1_offs-6], r10b
727 %endif
728     mov  r6d, [nodes_prevq + node_level_idx(j)]
729 %if %1
730     mov r11d, abs_leveld
731     shl r11d, 16
732     or   r6d, r11d
733 %else
734     or   r6d, 1<<16
735 %endif
736     mov [level_tree + levels_usedq*4], r6d
737     mov [nodes_curq + node_level_idx(node_ctx)], levels_usedd
738     inc levels_usedd
739 %endmacro ; END_COEF
740
741
742
743 %macro COEF1 2
744     %assign j %1
745     %assign nextj_if_valid %1+1
746     %assign nextj_if_invalid %2
747 %if j < 4
748     %assign coeff_abs_level1_offs j+1
749 %else
750     %assign coeff_abs_level1_offs 0
751 %endif
752 %if j < 3
753     %assign node_ctx j+1
754 %else
755     %assign node_ctx j
756 %endif
757 .ctx %+ j:
758     START_COEF 0
759     add  bitsd, 1 << CABAC_SIZE_BITS
760     END_COEF 0
761 %endmacro ; COEF1
762
763 %macro COEFN 2
764     %assign j %1
765     %assign nextj_if_valid %2
766     %assign nextj_if_invalid %2
767 %if j < 4
768     %assign coeff_abs_level1_offs j+1
769     %assign coeff_abs_levelgt1_offs 5
770 %else
771     %assign coeff_abs_level1_offs 0
772     %assign coeff_abs_levelgt1_offs j+2 ; this is the one used for all block types except 4:2:2 chroma dc
773 %endif
774 %if j < 4
775     %assign node_ctx 4
776 %elif j < 7
777     %assign node_ctx j+1
778 %else
779     %assign node_ctx 7
780 %endif
781 .ctx %+ j:
782     START_COEF 1
783     ; if( abs_level >= 15 )
784     ;     bits += bs_size_ue_big(...)
785     add  bitsd, r5d ; bs_size_ue_big from COEFN_SUFFIX
786     ; n.cabac_state[levelgt1_ctx]
787 %if j == 7 ; && compiling support for 4:2:2
788     mov    r6d, levelgt1_ctxm
789     %define coeff_abs_levelgt1_offs r6
790 %endif
791 %if j == 7
792     movzx  r10, byte [nodes_prevq + node_cabac_state(j) + coeff_abs_levelgt1_offs-6] ; -6 because node only stores ctx 8 and 9
793 %else
794     movzx  r10, byte [level_statem + coeff_abs_levelgt1_offs]
795 %endif
796     ; f8_bits += cabac_size_unary[abs_level-1][n.cabac_state[levelgt1_ctx[j]]];
797     add   r10d, r1d
798     movzx  r6d, word [cabac_size_unary + (r10-128)*2 GLOBAL]
799     add  bitsd, r6d
800 %if node_ctx == 7
801     movzx  r10, byte [cabac_transition_unary + r10-128 GLOBAL]
802 %endif
803     END_COEF 1
804 %endmacro ; COEFN
805
806
807
808 clocal trellis_coef1
809 .entry0b: ; ctx_lo, larger of the two abs_level candidates
810     mov  r10, [ssd+8]
811     sub  r10, r11
812     mov  r12, [ssd+24]
813     sub  r12, r11
814 .entry0: ; ctx_lo, smaller of the two abs_level candidates
815     COEF1 0, 4
816     COEF1 1, 4
817     COEF1 2, 4
818     COEF1 3, 4
819 .ctx4:
820     rep ret
821 .entry1b: ; ctx_hi, larger of the two abs_level candidates
822     mov  r12, [ssd+24]
823     sub  r12, r11
824 .entry1: ; ctx_hi, smaller of the two abs_level candidates
825 trellis_coef1_hi:
826     COEF1 1, 2
827     COEF1 2, 3
828     COEF1 3, 4
829     COEF1 4, 5
830     COEF1 5, 6
831     COEF1 6, 7
832     COEF1 7, 8
833 .ctx8:
834     rep ret
835
836 %macro COEFN_PREFIX 1
837     ; int prefix = X264_MIN( abs_level - 1, 14 );
838     mov  r1d, abs_leveld
839     cmp  abs_leveld, 15
840     jge .level_suffix%1
841     xor  r5d, r5d
842 .skip_level_suffix%1:
843     shl  r1d, 7
844 %endmacro
845
846 %macro COEFN_SUFFIX 1
847 .level_suffix%1:
848     ; bs_size_ue_big( abs_level - 15 ) << CABAC_SIZE_BITS;
849     lea  r5d, [abs_levelq-14]
850     bsr  r5d, r5d
851     shl  r5d, CABAC_SIZE_BITS+1
852     add  r5d, 1<<CABAC_SIZE_BITS
853     ; int prefix = X264_MIN( abs_level - 1, 14 );
854     mov  r1d, 15
855     jmp .skip_level_suffix%1
856 %endmacro
857
858 clocal trellis_coefn
859 .entry0b:
860     mov  r10, [ssd+8]
861     mov  r12, [ssd+24]
862     inc  abs_leveld
863 .entry0:
864     ; I could fully separate the ctx_lo and ctx_hi versions of coefn, and then
865     ; apply return-on-first-failure to ctx_lo. Or I can use multiple entrypoints
866     ; to merge the common portion of ctx_lo and ctx_hi, and thus reduce codesize.
867     ; I can't do both, as return-on-first-failure doesn't work for ctx_hi.
868     ; The C version has to be fully separate since C doesn't support multiple
869     ; entrypoints. But return-on-first-failure isn't very important here (as
870     ; opposed to coef1), so I might as well reduce codesize.
871     COEFN_PREFIX 0
872     COEFN 0, 1
873     COEFN 1, 2
874     COEFN 2, 3
875     COEFN 3, 8
876 .ctx8:
877     mov zigzagq, zigzagm ; unspill since r1 was clobbered
878     ret
879 .entry1b:
880     mov  r12, [ssd+24]
881     inc  abs_leveld
882 .entry1:
883     COEFN_PREFIX 1
884     COEFN 4, 5
885     COEFN 5, 6
886     COEFN 6, 7
887     COEFN 7, 1
888     jmp .ctx1
889     COEFN_SUFFIX 0
890     COEFN_SUFFIX 1