module Codec.Utils (
Octet,
msb,
fromTwosComp, toTwosComp,
toOctets, fromOctets,
listFromOctets, listToOctets,
i2osp
) where
import Data.Word
import Data.Bits
powersOf n = 1 : (map (*n) (powersOf n))
toBase x =
map fromIntegral .
reverse .
map (flip mod x) .
takeWhile (/=0) .
iterate (flip div x)
toOctets :: (Integral a, Integral b) => a -> b -> [Octet]
toOctets n x = (toBase n . fromIntegral) x
trimNulls :: [Word8] -> [Word8]
trimNulls = reverse . (dropWhile (== 0)) . reverse
listToOctets :: (Bits a, Integral a) => [a] -> [Octet]
listToOctets x = trimNulls $ concat paddedOctets where
paddedOctets :: [[Octet]]
paddedOctets = map (padTo bytes) rawOctets
rawOctets :: [[Octet]]
rawOctets = map (reverse . toOctets 256) x
padTo :: Int -> [Octet] -> [Octet]
padTo x y = take x $ y ++ repeat 0
bytes :: Int
bytes = bitSize (head x) `div` 8
type Octet = Word8
msb :: Int
msb = bitSize (undefined::Octet) 1
fromOctets :: (Integral a, Integral b) => a -> [Octet] -> b
fromOctets n x =
fromIntegral $
sum $
zipWith (*) (powersOf n) (reverse (map fromIntegral x))
listFromOctets :: (Integral a, Bits a) => [Octet] -> [a]
listFromOctets [] = []
listFromOctets x = result where
result = first : rest
first = fromOctets 256 first'
first' = reverse $ take bytes x
rest = listFromOctets $ drop bytes x
bytes = bitSize first `div` 8
i2osp :: Integral a => Int -> a -> [Octet]
i2osp l y =
pad ++ z
where
pad = replicate (l unPaddedLen) (0x00::Octet)
z = toOctets 256 y
unPaddedLen = length z
fromTwosComp :: Integral a => [Octet] -> a
fromTwosComp x = conv x
where conv [] = 0
conv w@(x:xs) = if (testBit x msb)
then neg w
else pos w
neg w@(x:xs) = let z=(clearBit x msb):xs in
fromIntegral((fromOctets 256 z)
(128*(256^((length w)1))))
pos w = fromIntegral(fromOctets 256 w)
toTwosComp :: Integral a => a -> [Octet]
toTwosComp x
| x < 0 = reverse . plusOne . reverse . (map complement) $ u
| x == 0 = [0x00]
| otherwise = u
where z@(y:ys) = toBase 256 (abs x)
u = if testBit y msb
then 0x00:z
else z
plusOne :: [Octet] -> [Octet]
plusOne [] = [1]
plusOne (x:xs) =
if x == 0xff
then 0x00:(plusOne xs)
else (x+1):xs