Home | History | Annotate | Download | only in api
      1 ;//
      2 ;//
      3 ;// File Name:  armCOMM_BitDec_s.h
      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 ;// OpenMAX optimized bitstream decode module
     13 ;//
     14 ;// You must include armCOMM_s.h before including this file
     15 ;//
     16 ;// This module provides macros to perform assembly optimized fixed and
     17 ;// variable length decoding from a read-only bitstream. The variable
     18 ;// length decode modules take as input a pointer to a table of 16-bit
     19 ;// entries of the following format.
     20 ;//
     21 ;// VLD Table Entry format
     22 ;//
     23 ;//        15 14 13 12 11 10 09 08 07 06 05 04 03 02 01 00
     24 ;//       +------------------------------------------------+
     25 ;//       |  Len   |               Symbol              | 1 |
     26 ;//       +------------------------------------------------+
     27 ;//       |                Offset                      | 0 |
     28 ;//       +------------------------------------------------+
     29 ;//
     30 ;// If the table entry is a leaf entry then bit 0 set:
     31 ;//    Len    = Number of bits overread (0 to 7)
     32 ;//    Symbol = Symbol payload (unsigned 12 bits)
     33 ;//
     34 ;// If the table entry is an internal node then bit 0 is clear:
     35 ;//    Offset = Number of (16-bit) half words from the table
     36 ;//             start to the next table node
     37 ;//
     38 ;// The table is accessed by successive lookup up on the
     39 ;// next Step bits of the input bitstream until a leaf node
     40 ;// is obtained. The Step sizes are supplied to the VLD macro.
     41 ;//
     42 ;// USAGE:
     43 ;//
     44 ;// To use any of the macros in this package, first call:
     45 ;//
     46 ;//    M_BD_INIT ppBitStream, pBitOffset, pBitStream, RBitBuffer, RBitCount, Tmp
     47 ;//
     48 ;// This caches the current bitstream position and next available
     49 ;// bits in registers pBitStream, RBitBuffer, RBitCount. These registers
     50 ;// are reserved for use by the bitstream decode package until you
     51 ;// call M_BD_FINI.
     52 ;//
     53 ;// Next call the following macro(s) as many times as you need:
     54 ;//
     55 ;//    M_BD_LOOK8       - Look ahead constant 1<=N<=8  bits into the bitstream
     56 ;//    M_BD_LOOK16      - Look ahead constant 1<=N<=16 bits into the bitstream
     57 ;//    M_BD_READ8       - Read constant 1<=N<=8  bits from the bitstream
     58 ;//    M_BD_READ16      - Read constant 1<=N<=16 bits from the bitstream
     59 ;//    M_BD_VREAD8      - Read variable 1<=N<=8  bits from the bitstream
     60 ;//    M_BD_VREAD16     - Read variable 1<=N<=16 bits from the bitstream
     61 ;//    M_BD_VLD         - Perform variable length decode using lookup table
     62 ;//
     63 ;// Finally call the macro:
     64 ;//
     65 ;//    M_BD_FINI ppBitStream, pBitOffset
     66 ;//
     67 ;// This writes the bitstream state back to memory.
     68 ;//
     69 ;// The three bitstream cache register names are assigned to the following global
     70 ;// variables:
     71 ;//
     72 
     73         GBLS    pBitStream  ;// Register name for pBitStream
     74         GBLS    BitBuffer   ;// Register name for BitBuffer
     75         GBLS    BitCount    ;// Register name for BitCount
     76 
     77 ;//
     78 ;// These register variables must have a certain defined state on entry to every bitstream
     79 ;// macro (except M_BD_INIT) and on exit from every bitstream macro (except M_BD_FINI).
     80 ;// The state may depend on implementation.
     81 ;//
     82 ;// For the default (ARM11) implementation the following hold:
     83 ;//    pBitStream - points to the first byte not held in the BitBuffer
     84 ;//    BitBuffer  - is a cache of (4 bytes) 32 bits, bit 31 the first bit
     85 ;//    BitCount   - is offset (from the top bit) to the next unused bitstream bit
     86 ;//    0<=BitCount<=15 (so BitBuffer holds at least 17 unused bits)
     87 ;//
     88 ;//
     89 
     90         ;// Bitstream Decode initialise
     91         ;//
     92         ;// Initialises the bitstream decode global registers from
     93         ;// bitstream pointers. This macro is split into 3 parts to enable
     94         ;// scheduling.
     95         ;//
     96         ;// Input Registers:
     97         ;//
     98         ;// $ppBitStream    - pointer to pointer to the next bitstream byte
     99         ;// $pBitOffset     - pointer to the number of bits used in the current byte (0..7)
    100         ;// $RBitStream     - register to use for pBitStream (can be $ppBitStream)
    101         ;// $RBitBuffer     - register to use for BitBuffer
    102         ;// $RBitCount      - register to use for BitCount   (can be $pBitOffset)
    103         ;//
    104         ;// Output Registers:
    105         ;//
    106         ;// $T1,$T2,$T3     - registers that must be preserved between calls to
    107         ;//                   M_BD_INIT1 and M_BD_INIT2
    108         ;// $pBitStream     \
    109         ;// $BitBuffer       } See description above.
    110         ;// $BitCount       /
    111         ;//
    112         MACRO
    113         M_BD_INIT0  $ppBitStream, $pBitOffset, $RBitStream, $RBitBuffer, $RBitCount
    114 
    115 pBitStream  SETS "$RBitStream"
    116 BitBuffer   SETS "$RBitBuffer"
    117 BitCount    SETS "$RBitCount"
    118 
    119         ;// load inputs
    120         LDR     $pBitStream, [$ppBitStream]
    121         LDR     $BitCount, [$pBitOffset]
    122         MEND
    123 
    124         MACRO
    125         M_BD_INIT1  $T1, $T2, $T3
    126         LDRB    $T2, [$pBitStream, #2]
    127         LDRB    $T1, [$pBitStream, #1]
    128         LDRB    $BitBuffer,  [$pBitStream], #3
    129         ADD     $BitCount, $BitCount, #8
    130         MEND
    131 
    132         MACRO
    133         M_BD_INIT2  $T1, $T2, $T3
    134         ORR     $T2, $T2, $T1, LSL #8
    135         ORR     $BitBuffer, $T2, $BitBuffer, LSL #16
    136         MEND
    137 
    138         ;//
    139         ;// Look ahead fixed 1<=N<=8 bits without consuming any bits
    140         ;// The next bits will be placed at bit 31..24 of destination register
    141         ;//
    142         ;// Input Registers:
    143         ;//
    144         ;// $N              - number of bits to look
    145         ;// $pBitStream     \
    146         ;// $BitBuffer       } See description above.
    147         ;// $BitCount       /
    148         ;//
    149         ;// Output Registers:
    150         ;//
    151         ;// $Symbol         - the next N bits of the bitstream
    152         ;// $T1             - corrupted temp/scratch register
    153         ;// $pBitStream     \
    154         ;// $BitBuffer       } See description above.
    155         ;// $BitCount       /
    156         ;//
    157         MACRO
    158         M_BD_LOOK8  $Symbol, $N
    159         ASSERT  ($N>=1):LAND:($N<=8)
    160         MOV     $Symbol, $BitBuffer, LSL $BitCount
    161         MEND
    162 
    163         ;//
    164         ;// Look ahead fixed 1<=N<=16 bits without consuming any bits
    165         ;// The next bits will be placed at bit 31..16 of destination register
    166         ;//
    167         ;// Input Registers:
    168         ;//
    169         ;// $N              - number of bits to look
    170         ;// $pBitStream     \
    171         ;// $BitBuffer       } See description above.
    172         ;// $BitCount       /
    173         ;//
    174         ;// Output Registers:
    175         ;//
    176         ;// $Symbol         - the next N bits of the bitstream
    177         ;// $T1             - corrupted temp/scratch register
    178         ;// $pBitStream     \
    179         ;// $BitBuffer       } See description above.
    180         ;// $BitCount       /
    181         ;//
    182         MACRO
    183         M_BD_LOOK16  $Symbol, $N, $T1
    184         ASSERT  ($N >= 1):LAND:($N <= 16)
    185         MOV     $Symbol, $BitBuffer, LSL $BitCount
    186         MEND
    187 
    188         ;//
    189         ;// Skips fixed 1<=N<=8 bits from the bitstream, advancing the bitstream pointer
    190         ;//
    191         ;// Input Registers:
    192         ;//
    193         ;// $N              - number of bits
    194         ;// $pBitStream     \
    195         ;// $BitBuffer       } See description above.
    196         ;// $BitCount       /
    197         ;//
    198         ;// Output Registers:
    199         ;//
    200         ;// $T1             - corrupted temp/scratch register
    201         ;// $pBitStream     \
    202         ;// $BitBuffer       } See description above.
    203         ;// $BitCount       /
    204         ;//
    205         MACRO
    206         M_BD_SKIP8 $N, $T1
    207         ASSERT  ($N>=1):LAND:($N<=8)
    208         SUBS    $BitCount, $BitCount, #(8-$N)
    209         LDRCSB  $T1, [$pBitStream], #1
    210         ADDCC   $BitCount, $BitCount, #8
    211         ORRCS   $BitBuffer, $T1, $BitBuffer, LSL #8
    212         MEND
    213 
    214 
    215         ;//
    216         ;// Read fixed 1<=N<=8 bits from the bitstream, advancing the bitstream pointer
    217         ;//
    218         ;// Input Registers:
    219         ;//
    220         ;// $N              - number of bits to read
    221         ;// $pBitStream     \
    222         ;// $BitBuffer       } See description above.
    223         ;// $BitCount       /
    224         ;//
    225         ;// Output Registers:
    226         ;//
    227         ;// $Symbol         - the next N bits of the bitstream
    228         ;// $T1             - corrupted temp/scratch register
    229         ;// $pBitStream     \
    230         ;// $BitBuffer       } See description above.
    231         ;// $BitCount       /
    232         ;//
    233         MACRO
    234         M_BD_READ8 $Symbol, $N, $T1
    235         ASSERT  ($N>=1):LAND:($N<=8)
    236         MOVS    $Symbol, $BitBuffer, LSL $BitCount
    237         SUBS    $BitCount, $BitCount, #(8-$N)
    238         LDRCSB  $T1, [$pBitStream], #1
    239         ADDCC   $BitCount, $BitCount, #8
    240         MOV     $Symbol, $Symbol, LSR #(32-$N)
    241         ORRCS   $BitBuffer, $T1, $BitBuffer, LSL #8
    242         MEND
    243 
    244         ;//
    245         ;// Read fixed 1<=N<=16 bits from the bitstream, advancing the bitstream pointer
    246         ;//
    247         ;// Input Registers:
    248         ;//
    249         ;// $N              - number of bits to read
    250         ;// $pBitStream     \
    251         ;// $BitBuffer       } See description above.
    252         ;// $BitCount       /
    253         ;//
    254         ;// Output Registers:
    255         ;//
    256         ;// $Symbol         - the next N bits of the bitstream
    257         ;// $T1             - corrupted temp/scratch register
    258         ;// $T2             - corrupted temp/scratch register
    259         ;// $pBitStream     \
    260         ;// $BitBuffer       } See description above.
    261         ;// $BitCount       /
    262         ;//
    263         MACRO
    264         M_BD_READ16 $Symbol, $N, $T1, $T2
    265         ASSERT  ($N>=1):LAND:($N<=16)
    266         ASSERT  $Symbol<>$T1
    267         IF ($N<=8)
    268             M_BD_READ8  $Symbol, $N, $T1
    269         ELSE
    270             ;// N>8 so we will be able to refill at least one byte
    271             LDRB    $T1, [$pBitStream], #1
    272             MOVS    $Symbol, $BitBuffer, LSL $BitCount
    273             ORR     $BitBuffer, $T1, $BitBuffer, LSL #8
    274             SUBS    $BitCount, $BitCount, #(16-$N)
    275             LDRCSB  $T1, [$pBitStream], #1
    276             MOV     $Symbol, $Symbol, LSR #(32-$N)
    277             ADDCC   $BitCount, $BitCount, #8
    278             ORRCS   $BitBuffer, $T1, $BitBuffer, LSL #8
    279         ENDIF
    280         MEND
    281 
    282         ;//
    283         ;// Skip variable 1<=N<=8 bits from the bitstream, advancing the bitstream pointer.
    284         ;//
    285         ;// Input Registers:
    286         ;//
    287         ;// $N              - number of bits. 1<=N<=8
    288         ;// $pBitStream     \
    289         ;// $BitBuffer       } See description above.
    290         ;// $BitCount       /
    291         ;//
    292         ;// Output Registers:
    293         ;//
    294         ;// $T1             - corrupted temp/scratch register
    295         ;// $T2             - corrupted temp/scratch register
    296         ;// $pBitStream     \
    297         ;// $BitBuffer       } See description above.
    298         ;// $BitCount       /
    299         ;//
    300         MACRO
    301         M_BD_VSKIP8 $N, $T1
    302         ADD     $BitCount, $BitCount, $N
    303         SUBS    $BitCount, $BitCount, #8
    304         LDRCSB  $T1, [$pBitStream], #1
    305         ADDCC   $BitCount, $BitCount, #8
    306         ORRCS   $BitBuffer, $T1, $BitBuffer, LSL #8
    307         MEND
    308 
    309         ;//
    310         ;// Skip variable 1<=N<=16 bits from the bitstream, advancing the bitstream pointer.
    311         ;//
    312         ;// Input Registers:
    313         ;//
    314         ;// $N              - number of bits. 1<=N<=16
    315         ;// $pBitStream     \
    316         ;// $BitBuffer       } See description above.
    317         ;// $BitCount       /
    318         ;//
    319         ;// Output Registers:
    320         ;//
    321         ;// $T1             - corrupted temp/scratch register
    322         ;// $T2             - corrupted temp/scratch register
    323         ;// $pBitStream     \
    324         ;// $BitBuffer       } See description above.
    325         ;// $BitCount       /
    326         ;//
    327         MACRO
    328         M_BD_VSKIP16 $N, $T1, $T2
    329         ADD     $BitCount, $BitCount, $N
    330         SUBS    $BitCount, $BitCount, #8
    331         LDRCSB  $T1, [$pBitStream], #1
    332         ORRCS   $BitBuffer, $T1, $BitBuffer, LSL #8
    333         SUBCSS  $BitCount, $BitCount, #8
    334         LDRCSB  $T1, [$pBitStream], #1
    335         ADDCC   $BitCount, $BitCount, #8
    336         ORRCS   $BitBuffer, $T1, $BitBuffer, LSL #8
    337         MEND
    338 
    339         ;//
    340         ;// Read variable 1<=N<=8 bits from the bitstream, advancing the bitstream pointer.
    341         ;//
    342         ;// Input Registers:
    343         ;//
    344         ;// $N              - number of bits to read. 1<=N<=8
    345         ;// $pBitStream     \
    346         ;// $BitBuffer       } See description above.
    347         ;// $BitCount       /
    348         ;//
    349         ;// Output Registers:
    350         ;//
    351         ;// $Symbol         - the next N bits of the bitstream
    352         ;// $T1             - corrupted temp/scratch register
    353         ;// $T2             - corrupted temp/scratch register
    354         ;// $pBitStream     \
    355         ;// $BitBuffer       } See description above.
    356         ;// $BitCount       /
    357         ;//
    358         MACRO
    359         M_BD_VREAD8 $Symbol, $N, $T1, $T2
    360         MOV     $Symbol, $BitBuffer, LSL $BitCount
    361         ADD     $BitCount, $BitCount, $N
    362         SUBS    $BitCount, $BitCount, #8
    363         LDRCSB  $T1, [$pBitStream], #1
    364         RSB     $T2, $N, #32
    365         ADDCC   $BitCount, $BitCount, #8
    366         MOV     $Symbol, $Symbol, LSR $T2
    367         ORRCS   $BitBuffer, $T1, $BitBuffer, LSL #8
    368         MEND
    369 
    370 
    371         ;//
    372         ;// Read variable 1<=N<=16 bits from the bitstream, advancing the bitstream pointer.
    373         ;//
    374         ;// Input Registers:
    375         ;//
    376         ;// $N              - number of bits to read. 1<=N<=16
    377         ;// $pBitStream     \
    378         ;// $BitBuffer       } See description above.
    379         ;// $BitCount       /
    380         ;//
    381         ;// Output Registers:
    382         ;//
    383         ;// $Symbol         - the next N bits of the bitstream
    384         ;// $T1             - corrupted temp/scratch register
    385         ;// $T2             - corrupted temp/scratch register
    386         ;// $pBitStream     \
    387         ;// $BitBuffer       } See description above.
    388         ;// $BitCount       /
    389         ;//
    390         MACRO
    391         M_BD_VREAD16 $Symbol, $N, $T1, $T2
    392         MOV     $Symbol, $BitBuffer, LSL $BitCount
    393         ADD     $BitCount, $BitCount, $N
    394         SUBS    $BitCount, $BitCount, #8
    395         LDRCSB  $T1, [$pBitStream], #1
    396         RSB     $T2, $N, #32
    397         ORRCS   $BitBuffer, $T1, $BitBuffer, LSL #8
    398         SUBCSS  $BitCount, $BitCount, #8
    399         LDRCSB  $T1, [$pBitStream], #1
    400         ADDCC   $BitCount, $BitCount, #8
    401         MOV     $Symbol, $Symbol, LSR $T2
    402         ORRCS   $BitBuffer, $T1, $BitBuffer, LSL #8
    403         MEND
    404 
    405 
    406         ;//
    407         ;// Decode a code of the form 0000...001 where there
    408         ;// are N zeros before the 1 and N<=15 (code length<=16)
    409         ;//
    410         ;// Input Registers:
    411         ;//
    412         ;// $pBitStream     \
    413         ;// $BitBuffer       } See description above.
    414         ;// $BitCount       /
    415         ;//
    416         ;// Output Registers:
    417         ;//
    418         ;// $Symbol         - the number of zeros before the next 1
    419         ;//                   >=16 is an illegal code
    420         ;// $T1             - corrupted temp/scratch register
    421         ;// $T2             - corrupted temp/scratch register
    422         ;// $pBitStream     \
    423         ;// $BitBuffer       } See description above.
    424         ;// $BitCount       /
    425         ;//
    426         MACRO
    427         M_BD_CLZ16 $Symbol, $T1, $T2
    428         MOVS    $Symbol, $BitBuffer, LSL $BitCount
    429         CLZ     $Symbol, $Symbol
    430         ADD     $BitCount, $BitCount, $Symbol
    431         SUBS    $BitCount, $BitCount, #7        ;// length is Symbol+1
    432         LDRCSB  $T1, [$pBitStream], #1
    433         ORRCS   $BitBuffer, $T1, $BitBuffer, LSL #8
    434         SUBCSS  $BitCount, $BitCount, #8
    435         LDRCSB  $T1, [$pBitStream], #1
    436         ADDCC   $BitCount, $BitCount, #8
    437         ORRCS   $BitBuffer, $T1, $BitBuffer, LSL #8
    438         MEND
    439 
    440         ;//
    441         ;// Decode a code of the form 1111...110 where there
    442         ;// are N ones before the 0 and N<=15 (code length<=16)
    443         ;//
    444         ;// Input Registers:
    445         ;//
    446         ;// $pBitStream     \
    447         ;// $BitBuffer       } See description above.
    448         ;// $BitCount       /
    449         ;//
    450         ;// Output Registers:
    451         ;//
    452         ;// $Symbol         - the number of zeros before the next 1
    453         ;//                   >=16 is an illegal code
    454         ;// $T1             - corrupted temp/scratch register
    455         ;// $T2             - corrupted temp/scratch register
    456         ;// $pBitStream     \
    457         ;// $BitBuffer       } See description above.
    458         ;// $BitCount       /
    459         ;//
    460         MACRO
    461         M_BD_CLO16 $Symbol, $T1, $T2
    462         MOV     $Symbol, $BitBuffer, LSL $BitCount
    463         MVN     $Symbol, $Symbol
    464         CLZ     $Symbol, $Symbol
    465         ADD     $BitCount, $BitCount, $Symbol
    466         SUBS    $BitCount, $BitCount, #7        ;// length is Symbol+1
    467         LDRCSB  $T1, [$pBitStream], #1
    468         ORRCS   $BitBuffer, $T1, $BitBuffer, LSL #8
    469         SUBCSS  $BitCount, $BitCount, #8
    470         LDRCSB  $T1, [$pBitStream], #1
    471         ADDCC   $BitCount, $BitCount, #8
    472         ORRCS   $BitBuffer, $T1, $BitBuffer, LSL #8
    473         MEND
    474 
    475 
    476         ;//
    477         ;// Variable Length Decode module
    478         ;//
    479         ;// Decodes one VLD Symbol from a bitstream and refill the bitstream
    480         ;// buffer.
    481         ;//
    482         ;// Input Registers:
    483         ;//
    484         ;// $pVLDTable      - pointer to VLD decode table of 16-bit entries.
    485         ;//                   The format is described above at the start of
    486         ;//                   this file.
    487         ;// $S0             - The number of bits to look up for the first step
    488         ;//                   1<=$S0<=8
    489         ;// $S1             - The number of bits to look up for each subsequent
    490         ;//                   step 1<=$S1<=$S0.
    491         ;//
    492         ;// $pBitStream     \
    493         ;// $BitBuffer       } See description above.
    494         ;// $BitCount       /
    495         ;//
    496         ;// Output Registers:
    497         ;//
    498         ;// $Symbol         - decoded VLD symbol value
    499         ;// $T1             - corrupted temp/scratch register
    500         ;// $T2             - corrupted temp/scratch register
    501         ;// $pBitStream     \
    502         ;// $BitBuffer       } See description above.
    503         ;// $BitCount       /
    504         ;//
    505         MACRO
    506         M_BD_VLD $Symbol, $T1, $T2, $pVLDTable, $S0, $S1
    507         ASSERT (1<=$S0):LAND:($S0<=8)
    508         ASSERT (1<=$S1):LAND:($S1<=$S0)
    509 
    510         ;// Note 0<=BitCount<=15 on entry and exit
    511 
    512         MOVS    $T1, $BitBuffer, LSL $BitCount       ;// left align next bits
    513         MOVS    $Symbol, #(2<<$S0)-2                 ;// create mask
    514         AND     $Symbol, $Symbol, $T1, LSR #(31-$S0) ;// 2*(next $S0 bits)
    515         SUBS    $BitCount, $BitCount, #8             ;// CS if buffer can be filled
    516 01
    517         LDRCSB  $T1, [$pBitStream], #1               ;// load refill byte
    518         LDRH    $Symbol, [$pVLDTable, $Symbol]       ;// load table entry
    519         ADDCC   $BitCount, $BitCount, #8             ;// refill not possible
    520         ADD     $BitCount, $BitCount, #$S0           ;// assume $S0 bits used
    521         ORRCS   $BitBuffer, $T1, $BitBuffer, LSL #8  ;// merge in refill byte
    522         MOVS    $T1, $Symbol, LSR #1                 ;// CS=leaf entry
    523         BCS     %FT02
    524 
    525         MOVS    $T1, $BitBuffer, LSL $BitCount       ;// left align next bit
    526         IF (2*$S0-$S1<=8)
    527             ;// Can combine refill check and -S0+S1 and keep $BitCount<=15
    528             SUBS    $BitCount, $BitCount, #8+($S0-$S1)
    529         ELSE
    530             ;// Separate refill check and -S0+S1 offset
    531             SUBS  $BitCount, $BitCount, #8
    532             SUB   $BitCount, $BitCount, #($S0-$S1)
    533         ENDIF
    534         ADD     $Symbol, $Symbol, $T1, LSR #(31-$S1) ;// add 2*(next $S1 bits) to
    535         BIC     $Symbol, $Symbol, #1                 ;//   table offset
    536         B       %BT01                                ;// load next table entry
    537 02
    538         ;// BitCount range now depend on the route here
    539         ;// if (first step)       S0 <= BitCount <= 7+S0        <=15
    540         ;// else if (2*S0-S1<=8)  S0 <= BitCount <= 7+(2*S0-S1) <=15
    541         ;// else                  S1 <= BitCount <= 7+S1        <=15
    542 
    543         SUB     $BitCount, $BitCount, $Symbol, LSR#13
    544         BIC     $Symbol, $T1, #0xF000
    545         MEND
    546 
    547 
    548         ;// Add an offset number of bits
    549         ;//
    550         ;// Outputs destination byte and bit index values which corresponds to an offset number of bits
    551         ;// from the current location. This is used to compare bitstream positions using. M_BD_CMP.
    552         ;//
    553         ;// Input Registers:
    554         ;//
    555         ;// $Offset         - Offset to be added in bits.
    556         ;// $pBitStream     \
    557         ;// $BitBuffer       } See description above.
    558         ;// $BitCount       /
    559         ;//
    560         ;// Output Registers:
    561         ;//
    562         ;// $ByteIndex      - Destination pBitStream pointer after adding the Offset.
    563         ;//                   This value will be 4 byte ahead and needs to subtract by 4 to get exact
    564         ;//                   pointer (as in M_BD_FINI). But for using with M_BD_CMP subtract is not needed.
    565         ;// $BitIndex       - Destination BitCount after the addition of Offset number of bits
    566         ;//
    567         MACRO
    568         M_BD_ADD  $ByteIndex, $BitIndex, $Offset
    569 
    570         ;// ($ByteIndex,$BitIndex) = Current position + $Offset bits
    571         ADD     $Offset, $Offset, $BitCount
    572         AND     $BitIndex, $Offset, #7
    573         ADD     $ByteIndex, $pBitStream, $Offset, ASR #3
    574         MEND
    575 
    576         ;// Move bitstream pointers to the location given
    577         ;//
    578         ;// Outputs destination byte and bit index values which corresponds to
    579         ;// the current location given (calculated using M_BD_ADD).
    580         ;//
    581         ;// Input Registers:
    582         ;//
    583         ;// $pBitStream     \
    584         ;// $BitBuffer       } See description above.
    585         ;// $BitCount       /
    586         ;// $ByteIndex      - Destination pBitStream pointer after move.
    587         ;//                   This value will be 4 byte ahead and needs to subtract by 4 to get exact
    588         ;//                   pointer (as in M_BD_FINI).
    589         ;// $BitIndex       - Destination BitCount after the move
    590         ;//
    591         ;// Output Registers:
    592         ;//
    593         ;// $pBitStream     \
    594         ;//                  } See description above.
    595         ;// $BitCount       /
    596         ;//
    597         MACRO
    598         M_BD_MOV  $ByteIndex, $BitIndex
    599 
    600         ;// ($pBitStream, $Offset) = ($ByteIndex,$BitIndex)
    601         MOV     $BitCount, $BitIndex
    602         MOV     $pBitStream, $ByteIndex
    603         MEND
    604 
    605         ;// Bitstream Compare
    606         ;//
    607         ;// Compares bitstream position with that of a destination position. Destination position
    608         ;// is held in two input registers which are calculated using M_BD_ADD macro
    609         ;//
    610         ;// Input Registers:
    611         ;//
    612         ;// $ByteIndex      - Destination pBitStream pointer, (4 byte ahead as described in M_BD_ADD)
    613         ;// $BitIndex       - Destination BitCount
    614         ;// $pBitStream     \
    615         ;// $BitBuffer       } See description above.
    616         ;// $BitCount       /
    617         ;//
    618         ;// Output Registers:
    619         ;//
    620         ;// FLAGS           - GE if destination is reached, LT = is destination is ahead
    621         ;// $T1             - corrupted temp/scratch register
    622         ;//
    623         MACRO
    624         M_BD_CMP  $ByteIndex, $BitIndex, $T1
    625 
    626         ;// Return flags set by (current positon)-($ByteIndex,$BitIndex)
    627         ;// so GE means that we have reached the indicated position
    628 
    629         ADD         $T1, $pBitStream, $BitCount, LSR #3
    630         CMP         $T1, $ByteIndex
    631         AND         $T1, $BitCount, #7
    632         CMPEQ       $T1, $BitIndex
    633         MEND
    634 
    635 
    636         ;// Bitstream Decode finalise
    637         ;//
    638         ;// Writes back the bitstream state to the bitstream pointers
    639         ;//
    640         ;// Input Registers:
    641         ;//
    642         ;// $pBitStream     \
    643         ;// $BitBuffer       } See description above.
    644         ;// $BitCount       /
    645         ;//
    646         ;// Output Registers:
    647         ;//
    648         ;// $ppBitStream    - pointer to pointer to the next bitstream byte
    649         ;// $pBitOffset     - pointer to the number of bits used in the current byte (0..7)
    650         ;// $pBitStream     \
    651         ;// $BitBuffer       } these register are corrupted
    652         ;// $BitCount       /
    653         ;//
    654         MACRO
    655         M_BD_FINI  $ppBitStream, $pBitOffset
    656 
    657         ;// Advance pointer by the number of free bits in the buffer
    658         ADD     $pBitStream, $pBitStream, $BitCount, LSR#3
    659         AND     $BitCount, $BitCount, #7
    660 
    661         ;// Now move back 32 bits to reach the first usued bit
    662         SUB     $pBitStream, $pBitStream, #4
    663 
    664         ;// Store out bitstream state
    665         STR     $BitCount, [$pBitOffset]
    666         STR     $pBitStream, [$ppBitStream]
    667         MEND
    668 
    669         END
    670