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