getNBits = fromIntegral ∘ UV.unsafeIndex nbitsTable ∘ fromIntegral
where
nbitsTable ∷ UV.Vector Word8
+ {-# NOINLINE nbitsTable #-}
nbitsTable
= UV.fromList
[ 0, 1, 2, 2, 3, 3, 3, 3, 4, 4, 4, 4, 4, 4, 4, 4 -- 0 - 15
getLog2 = fromIntegral ∘ UV.unsafeIndex log2Table ∘ fromIntegral
where
log2Table ∷ UV.Vector Word8
+ {-# NOINLINE log2Table #-}
log2Table
= UV.fromList
[ 0x00, 0x01, 0x03, 0x04, 0x06, 0x07, 0x09, 0x0a, 0x0B, 0x0D, 0x0E, 0x10, 0x11, 0x12, 0x14, 0x15
getExp2 = fromIntegral ∘ UV.unsafeIndex exp2Table ∘ fromIntegral
where
exp2Table ∷ UV.Vector Word8
+ {-# NOINLINE exp2Table #-}
exp2Table
= UV.fromList
[ 0x00, 0x01, 0x01, 0x02, 0x03, 0x03, 0x04, 0x05, 0x06, 0x06, 0x07, 0x08, 0x08, 0x09, 0x0a, 0x0B
{-# LANGUAGE
BangPatterns
+ , UnboxedTuples
, UnicodeSyntax
#-}
module Codec.Audio.WavPack.Unpack
import Data.Bitstream.Generic (Bitstream)
import qualified Data.Bitstream.Generic as B
import Data.Word
+import Prelude.Unicode
-- Read a single unsigned value from the specified bitstream with a
-- value from 0 to maxCode. If there are exactly a power of two number
-- of possible codes then this will read a fixed number of bits;
-- otherwise it reads the minimum number of bits and then determines
-- whether another bit is needed to define the code.
-readCode ∷ Bitstream bs ⇒ bs → Word32 → (Word32, bs)
+readCode ∷ Bitstream bs ⇒ bs → Word32 → (# Word32, bs #)
{-# INLINEABLE readCode #-}
-readCode bs 0 = (0, bs)
-readCode bs 1 = (b2n $ B.head bs, B.tail bs)
+readCode bs 0 = (# 0, bs #)
+readCode bs 1 = (# b2n (B.head bs), B.tail bs #)
readCode bs maxCode
= let !bitCount = countBits maxCode
- !extras = (1 `shiftL` bitCount) - maxCode - 1
+ !extras = bit bitCount - maxCode - 1
+ !code = B.toBits (B.take (bitCount - 1) bs)
+ (# code', bitCount' #)
+ = if code ≥ extras then
+ (# (code `shiftL` 1)
+ - extras
+ + b2n (bs B.!! bitCount)
+ , bitCount #)
+ else
+ (# code, bitCount - 1 #)
+ !bs' = B.drop bitCount' bs
in
- error "unk"
\ No newline at end of file
+ (# code', bs' #)