Home | History | Annotate | Download | only in src
      1 ; **********
      2 ; *
      3 ; * File Name:  omxVCM4P2_DecodePadMV_PVOP_s.s
      4 ; * OpenMAX DL: v1.0.2
      5 ; * Revision:   9641
      6 ; * Date:       Thursday, February 7, 2008
      7 ; *
      8 ; * (c) Copyright 2007-2008 ARM Limited. All Rights Reserved.
      9 ; *
     10 ; *
     11 ; *
     12 ; **
     13 ; * Function: omxVCM4P2_DecodePadMV_PVOP
     14 ; *
     15 ; * Description:
     16 ; * Decodes and pads four motion vectors of the non-intra macroblock in P-VOP.
     17 ; * The motion vector padding process is specified in subclause 7.6.1.6 of
     18 ; * ISO/IEC 14496-2.
     19 ; *
     20 ; * Remarks:
     21 ; *
     22 ; *
     23 ; * Parameters:
     24 ; * [in]    ppBitStream        pointer to the pointer to the current byte in
     25 ; *                            the bit stream buffer
     26 ; * [in]    pBitOffset         pointer to the bit position in the byte pointed
     27 ; *                            to by *ppBitStream. *pBitOffset is valid within
     28 ; *                            [0-7].
     29 ; * [in]    pSrcMVLeftMB       pointers to the motion vector buffers of the
     30 ; *                           macroblocks specially at the left side of the current macroblock
     31 ; *                     respectively.
     32 ; * [in]    pSrcMVUpperMB      pointers to the motion vector buffers of the
     33 ; *                     macroblocks specially at the upper side of the current macroblock
     34 ; *                     respectively.
     35 ; * [in]    pSrcMVUpperRightMB pointers to the motion vector buffers of the
     36 ; *                     macroblocks specially at the upper-right side of the current macroblock
     37 ; *                     respectively.
     38 ; * [in]    fcodeForward       a code equal to vop_fcode_forward in MPEG-4
     39 ; *                     bit stream syntax
     40 ; * [in]    MBType         the type of the current macroblock. If MBType
     41 ; *                     is not equal to OMX_VC_INTER4V, the destination
     42 ; *                     motion vector buffer is still filled with the
     43 ; *                     same decoded vector.
     44 ; * [out]   ppBitStream         *ppBitStream is updated after the block is decoded,
     45 ; *                     so that it points to the current byte in the bit
     46 ; *                     stream buffer
     47 ; * [out]   pBitOffset         *pBitOffset is updated so that it points to the
     48 ; *                     current bit position in the byte pointed by
     49 ; *                     *ppBitStream
     50 ; * [out]   pDstMVCurMB         pointer to the motion vector buffer of the current
     51 ; *                     macroblock which contains four decoded motion vectors
     52 ; *
     53 ; * Return Value:
     54 ; * OMX_Sts_NoErr -no error
     55 ; *
     56 ; *
     57 ; * OMX_Sts_Err - status error
     58 ; *
     59 ; *
     60 
     61         INCLUDE omxtypes_s.h
     62         INCLUDE armCOMM_s.h
     63         INCLUDE armCOMM_BitDec_s.h
     64         INCLUDE omxVC_s.h
     65 
     66        M_VARIANTS ARM1136JS
     67 
     68 
     69 
     70 
     71         IF ARM1136JS
     72 
     73 ;//Input Arguments
     74 
     75 ppBitStream           RN 0
     76 pBitOffset            RN 1
     77 pSrcMVLeftMB          RN 2
     78 pSrcMVUpperMB         RN 3
     79 pSrcMVUpperRightMB    RN 4
     80 pDstMVCurMB           RN 5
     81 fcodeForward          RN 6
     82 MBType                RN 7
     83 
     84 ;//Local Variables
     85 
     86 zero                  RN 4
     87 one                   RN 4
     88 scaleFactor           RN 1
     89 
     90 
     91 Return                RN 0
     92 
     93 VlcMVD                RN 0
     94 index                 RN 4
     95 Count                 RN 7
     96 
     97 mvHorData             RN 4
     98 mvHorResidual         RN 0
     99 
    100 mvVerData             RN 4
    101 mvVerResidual         RN 0
    102 
    103 temp                  RN 1
    104 
    105 temp1                 RN 3
    106 High                  RN 4
    107 Low                   RN 2
    108 Range                 RN 1
    109 
    110 BlkCount              RN 14
    111 
    112 diffMVdx              RN 0
    113 diffMVdy              RN 1
    114 
    115 ;// Scratch Registers
    116 
    117 RBitStream            RN 8
    118 RBitCount             RN 9
    119 RBitBuffer            RN 10
    120 
    121 T1                    RN 11
    122 T2                    RN 12
    123 LR                    RN 14
    124 
    125        IMPORT          armVCM4P2_aVlcMVD
    126        IMPORT          omxVCM4P2_FindMVpred
    127 
    128        ;// Allocate stack memory
    129 
    130        M_ALLOC4        ppDstMVCurMB,4
    131        M_ALLOC4        pDstMVPredME,4
    132        M_ALLOC4        pBlkCount,4
    133 
    134        M_ALLOC4        pppBitStream,4
    135        M_ALLOC4        ppBitOffset,4
    136        M_ALLOC4        ppSrcMVLeftMB,4
    137        M_ALLOC4        ppSrcMVUpperMB,4
    138 
    139        M_ALLOC4        pdiffMVdx,4
    140        M_ALLOC4        pdiffMVdy,4
    141        M_ALLOC4        pHigh,4
    142 
    143 
    144 
    145 
    146        M_START   omxVCM4P2_DecodePadMV_PVOP,r11
    147 
    148        M_ARG           pSrcMVUpperRightMBonStack,4           ;// pointer to  pSrcMVUpperRightMB on stack
    149        M_ARG           pDstMVCurMBonStack,4                  ;// pointer to pDstMVCurMB on stack
    150        M_ARG           fcodeForwardonStack,4                 ;// pointer to fcodeForward on stack
    151        M_ARG           MBTypeonStack,4                       ;// pointer to MBType on stack
    152 
    153 
    154 
    155 
    156 
    157        ;// Initializing the BitStream Macro
    158 
    159        M_BD_INIT0      ppBitStream, pBitOffset, RBitStream, RBitBuffer, RBitCount
    160        M_LDR           MBType,MBTypeonStack                  ;// Load MBType from stack
    161        M_LDR           pDstMVCurMB,pDstMVCurMBonStack        ;// Load pDstMVCurMB from stack
    162        MOV             zero,#0
    163 
    164        TEQ             MBType,#OMX_VC_INTRA                  ;// Check if MBType=OMX_VC_INTRA
    165        TEQNE           MBType,#OMX_VC_INTRA_Q                ;// check if MBType=OMX_VC_INTRA_Q
    166        STREQ           zero,[pDstMVCurMB]
    167        M_BD_INIT1      T1, T2, T2
    168        STREQ           zero,[pDstMVCurMB,#4]
    169        M_BD_INIT2      T1, T2, T2
    170        STREQ           zero,[pDstMVCurMB,#4]
    171        MOVEQ           Return,#OMX_Sts_NoErr
    172        MOV             BlkCount,#0
    173        STREQ           zero,[pDstMVCurMB,#4]
    174 
    175        BEQ             ExitOK
    176 
    177        TEQ             MBType,#OMX_VC_INTER4V                ;// Check if MBType=OMX_VC_INTER4V
    178        TEQNE           MBType,#OMX_VC_INTER4V_Q              ;// Check if MBType=OMX_VC_INTER4V_Q
    179        MOVEQ           Count,#4
    180 
    181        TEQ             MBType,#OMX_VC_INTER                  ;// Check if MBType=OMX_VC_INTER
    182        TEQNE           MBType,#OMX_VC_INTER_Q                ;// Check if MBType=OMX_VC_INTER_Q
    183        MOVEQ           Count,#1
    184 
    185        M_LDR           fcodeForward,fcodeForwardonStack      ;// Load fcodeForward  from stack
    186 
    187        ;// Storing the values temporarily on stack
    188 
    189        M_STR           ppBitStream,pppBitStream
    190        M_STR           pBitOffset,ppBitOffset
    191 
    192 
    193        SUB             temp,fcodeForward,#1                  ;// temp=fcodeForward-1
    194        MOV             one,#1
    195        M_STR           pSrcMVLeftMB,ppSrcMVLeftMB
    196        LSL             scaleFactor,one,temp                  ;// scaleFactor=1<<(fcodeForward-1)
    197        M_STR           pSrcMVUpperMB,ppSrcMVUpperMB
    198        LSL             scaleFactor,scaleFactor,#5
    199        M_STR           scaleFactor,pHigh                     ;// [pHigh]=32*scaleFactor
    200 
    201        ;// VLD Decoding
    202 
    203 
    204 Loop
    205 
    206        LDR             VlcMVD, =armVCM4P2_aVlcMVD        ;// Load the optimized MVD VLC table
    207 
    208        ;// Horizontal Data and Residual calculation
    209 
    210        LDR             temp,=0xFFF
    211        M_BD_VLD        index,T1,T2,VlcMVD,3,2                ;// variable lenght decoding using the macro
    212 
    213        TEQ             index,temp
    214        BEQ             ExitError                             ;// Exit with an Error Message if the decoded symbol is an invalied symbol
    215 
    216        SUB             mvHorData,index,#32                   ;// mvHorData=index-32
    217        MOV             mvHorResidual,#1                      ;// mvHorResidual=1
    218        CMP             fcodeForward,#1
    219        TEQNE           mvHorData,#0
    220        MOVEQ           diffMVdx,mvHorData                    ;// if scaleFactor=1(fcodeForward=1) or mvHorData=0 diffMVdx=mvHorData
    221        BEQ             VerticalData
    222 
    223        SUB             temp,fcodeForward,#1
    224        M_BD_VREAD8     mvHorResidual,temp,T1,T2              ;// get mvHorResidual from bitstream if fcodeForward>1 and mvHorData!=0
    225 
    226        CMP             mvHorData,#0
    227        RSBLT           mvHorData,mvHorData,#0                ;// mvHorData=abs(mvHorData)
    228        SUB             mvHorResidual,mvHorResidual,fcodeForward
    229        SMLABB          diffMVdx,mvHorData,fcodeForward,mvHorResidual ;// diffMVdx=abs(mvHorData)*fcodeForward+mvHorResidual-fcodeForward
    230        ADD             diffMVdx,diffMVdx,#1
    231        RSBLT           diffMVdx,diffMVdx,#0
    232 
    233        ;// Vertical Data and Residual calculation
    234 
    235 VerticalData
    236 
    237        M_STR           diffMVdx,pdiffMVdx                    ;// Store the diffMVdx on stack
    238        LDR             VlcMVD, =armVCM4P2_aVlcMVD        ;// Loading the address of optimized VLC tables
    239 
    240        LDR             temp,=0xFFF
    241        M_BD_VLD        index,T1,T2,VlcMVD,3,2                ;// VLC decoding using the macro
    242 
    243        TEQ             index,temp
    244        BEQ             ExitError                             ;// Exit with an Error Message if an Invalied Symbol occurs
    245 
    246        SUB             mvVerData,index,#32                   ;// mvVerData=index-32
    247        MOV             mvVerResidual,#1
    248        CMP             fcodeForward,#1
    249        TEQNE           mvVerData,#0
    250        MOVEQ           diffMVdy,mvVerData                    ;// diffMVdy = mvVerData if scaleFactor=1(fcodeForward=1) or mvVerData=0
    251        BEQ             FindMVPred
    252 
    253        SUB             temp,fcodeForward,#1
    254        M_BD_VREAD8     mvVerResidual,temp,T1,T2              ;// Get mvVerResidual from bit stream if fcodeForward>1 and mnVerData!=0
    255 
    256 
    257        CMP             mvVerData,#0
    258        RSBLT           mvVerData,mvVerData,#0
    259        SUB             mvVerResidual,mvVerResidual,fcodeForward
    260        SMLABB          diffMVdy,mvVerData,fcodeForward,mvVerResidual ;// diffMVdy=abs(mvVerData)*fcodeForward+mvVerResidual-fcodeForward
    261        ADD             diffMVdy,diffMVdy,#1
    262        RSBLT           diffMVdy,diffMVdy,#0
    263 
    264        ;//Calling the Function omxVCM4P2_FindMVpred
    265 
    266 FindMVPred
    267 
    268        M_STR           diffMVdy,pdiffMVdy
    269        ADD             temp,pDstMVCurMB,BlkCount,LSL #2      ;// temp=pDstMVCurMB[BlkCount]
    270        M_STR           temp,ppDstMVCurMB                     ;// store temp on stack for passing as an argument to FindMVPred
    271 
    272        MOV             temp,#0
    273        M_STR           temp,pDstMVPredME                     ;// Pass pDstMVPredME=NULL as an argument
    274        M_STR           BlkCount,pBlkCount                    ;// Passs BlkCount as Argument through stack
    275 
    276        MOV             temp,pSrcMVLeftMB                     ;// temp (RN 1)=pSrcMVLeftMB
    277        M_LDR           pSrcMVUpperRightMB,pSrcMVUpperRightMBonStack
    278        MOV             pSrcMVLeftMB,pSrcMVUpperMB            ;// pSrcMVLeftMB ( RN 2) = pSrcMVUpperMB
    279        MOV             ppBitStream,pDstMVCurMB               ;// ppBitStream  ( RN 0) = pDstMVCurMB
    280        MOV             pSrcMVUpperMB,pSrcMVUpperRightMB      ;// pSrcMVUpperMB( RN 3) = pSrcMVUpperRightMB
    281        BL              omxVCM4P2_FindMVpred              ;// Branch to subroutine omxVCM4P2_FindMVpred
    282 
    283        ;// Store Horizontal Motion Vector
    284 
    285        M_LDR           BlkCount,pBlkCount                    ;// Load BlkCount from stack
    286        M_LDR           High,pHigh                            ;// High=32*scaleFactor
    287        LSL             temp1,BlkCount,#2                     ;// temp=BlkCount*4
    288        M_LDR           diffMVdx,pdiffMVdx                    ;// Laad diffMVdx
    289 
    290        LDRSH           temp,[pDstMVCurMB,temp1]              ;// temp=pDstMVCurMB[BlkCount]
    291 
    292 
    293        RSB             Low,High,#0                           ;// Low = -32*scaleFactor
    294        ADD             diffMVdx,temp,diffMVdx                ;// diffMVdx=pDstMVCurMB[BlkCount]+diffMVdx
    295        ADD             Range,High,High                       ;// Range=64*ScaleFactor
    296        SUB             High,High,#1                          ;// High= 32*scaleFactor-1
    297 
    298        CMP             diffMVdx,Low                          ;// If diffMVdx<Low
    299        ADDLT           diffMVdx,diffMVdx,Range               ;// diffMVdx+=Range
    300 
    301        CMP             diffMVdx,High
    302        SUBGT           diffMVdx,diffMVdx,Range               ;// If diffMVdx > High diffMVdx-=Range
    303        STRH            diffMVdx,[pDstMVCurMB,temp1]
    304 
    305        ;// Store Vertical
    306 
    307        ADD             temp1,temp1,#2                        ;// temp1=4*BlkCount+2
    308        M_LDR           diffMVdx,pdiffMVdy                    ;// Laad diffMVdy
    309        LDRSH           temp,[pDstMVCurMB,temp1]              ;// temp=pDstMVCurMB[BlkCount].diffMVdy
    310        ADD             BlkCount,BlkCount,#1                  ;// BlkCount=BlkCount+1
    311        ADD             diffMVdx,temp,diffMVdx
    312        CMP             diffMVdx,Low
    313        ADDLT           diffMVdx,diffMVdx,Range               ;// If diffMVdy<Low  diffMVdy+=Range
    314        CMP             diffMVdx,High
    315        SUBGT           diffMVdx,diffMVdx,Range               ;// If diffMVdy > High diffMVdy-=Range
    316        STRH            diffMVdx,[pDstMVCurMB,temp1]
    317 
    318        CMP             BlkCount,Count
    319        M_LDR           pSrcMVLeftMB,ppSrcMVLeftMB
    320        M_LDR           pSrcMVUpperMB,ppSrcMVUpperMB
    321 
    322        BLT             Loop                                  ;// If BlkCount<Count Continue the Loop
    323 
    324 
    325        ;// If MBType=OMX_VC_INTER or MBtype=OMX_VC_INTER_Q copy pDstMVCurMB[0] to
    326        ;// pDstMVCurMB[1], pDstMVCurMB[2], pDstMVCurMB[3]
    327 
    328        M_LDR           MBType,MBTypeonStack
    329 
    330        TEQ             MBType,#OMX_VC_INTER
    331        TEQNE           MBType,#OMX_VC_INTER_Q
    332        LDREQ           temp,[pDstMVCurMB]
    333        M_LDR           ppBitStream,pppBitStream
    334        STREQ           temp,[pDstMVCurMB,#4]
    335 
    336        STREQ           temp,[pDstMVCurMB,#8]
    337        STREQ           temp,[pDstMVCurMB,#12]
    338 
    339 
    340        M_LDR           pBitOffset,ppBitOffset
    341        ;//Ending the macro
    342        M_BD_FINI       ppBitStream,pBitOffset                 ;// Finishing the Macro
    343 
    344 
    345        MOV             Return,#OMX_Sts_NoErr
    346        B               ExitOK
    347 
    348 ExitError
    349 
    350        M_LDR           ppBitStream,pppBitStream
    351        M_LDR           pBitOffset,ppBitOffset
    352        ;//Ending the macro
    353        M_BD_FINI       ppBitStream,pBitOffset
    354 
    355        MOV             Return,#OMX_Sts_Err
    356 
    357 ExitOK
    358 
    359        M_END
    360        ENDIF
    361        END
    362 
    363 
    364 
    365