module Sound.Frame.MuLaw (T, cons, decons, fromLinear16, toLinear16, ) where
import qualified Sound.Frame as Frame
import Foreign.Storable.Newtype as Store
import Foreign.Storable (Storable (..), )
import Data.Word (Word8, )
import Data.Int (Int16, )
import Test.QuickCheck (Arbitrary(arbitrary), )
import Prelude hiding (map, )
newtype T = Cons Word8
deriving (Eq)
instance Show T where
showsPrec p x =
showParen (p >= 10)
(showString "MuLaw.cons " . shows (decons x))
instance Arbitrary T where
arbitrary = fmap (cons . fromIntegral :: Int -> T) arbitrary
cons :: Word8 -> T
cons = Cons
decons :: T -> Word8
decons (Cons a) = a
fromLinear16 :: Int16 -> T
fromLinear16 x16 =
let x = fromIntegral x16 :: Int
logi e y =
if y < 16
then e*16 + y
else logi (e+1) (div (y 16) 2)
loga = min 127 . logi 0 . flip div 8
in cons . fromIntegral $
if x >= 2
then 255 loga (x+6)
else 127 loga (5x)
toLinear16 :: T -> Int16
toLinear16 ymu =
let y = fromIntegral (decons ymu) :: Int
(e,m) = divMod y 16
in fromIntegral $
if e>=8
then (2^(15e) * ((15m)*2 + 33) 33) * 4
else (2^ (7e) * ((m15)*2 33) + 33) * 4
instance Storable T where
sizeOf = Store.sizeOf decons
alignment = Store.alignment decons
peek = Store.peek cons
poke = Store.poke decons
instance Frame.C T where
numberOfChannels _ = 1
sizeOfElement = Store.sizeOf decons