{-# LANGUAGE Safe #-}
module Data.Bits.Utils(getBytes, fromBytes,
c2w8, s2w8, w82c, w82s)
where
import safe Data.Bits
( Bits((.|.), (.&.), shiftR, bitSizeMaybe, shiftL) )
import safe Data.Word ( Word8 )
getBytes :: (Integral a, Bounded a, Bits a) => a -> [a]
getBytes :: forall a. (Integral a, Bounded a, Bits a) => a -> [a]
getBytes a
input
| Just Int
size <- forall a. Bits a => a -> Maybe Int
bitSizeMaybe a
input, Int
size forall a. Integral a => a -> a -> a
`mod` Int
8 forall a. Eq a => a -> a -> Bool
== Int
0 =
forall a. [a] -> [a]
reverse forall a b. (a -> b) -> a -> b
$ forall {t} {t}. (Bits t, Num t, Num t, Eq t) => t -> t -> [t]
getByte a
input forall a b. (a -> b) -> a -> b
$ Int
size forall a. Integral a => a -> a -> a
`div` Int
8
| Bool
otherwise = forall a. HasCallStack => [Char] -> a
error [Char]
"Input data bit size must be a multiple of 8"
where
getByte :: t -> t -> [t]
getByte t
_ t
0 = []
getByte t
x t
remaining = (t
x forall a. Bits a => a -> a -> a
.&. t
0xff) forall a. a -> [a] -> [a]
: t -> t -> [t]
getByte (forall a. Bits a => a -> Int -> a
shiftR t
x Int
8) (t
remaining forall a. Num a => a -> a -> a
- t
1)
fromBytes :: (Bits a, Num a) => [a] -> a
fromBytes :: forall a. (Bits a, Num a) => [a] -> a
fromBytes [a]
input =
let dofb :: t -> [t] -> t
dofb t
accum [] = t
accum
dofb t
accum (t
x:[t]
xs) = t -> [t] -> t
dofb ((forall a. Bits a => a -> Int -> a
shiftL t
accum Int
8) forall a. Bits a => a -> a -> a
.|. t
x) [t]
xs
in
forall {t}. Bits t => t -> [t] -> t
dofb a
0 [a]
input
c2w8 :: Char -> Word8
c2w8 :: Char -> Word8
c2w8 = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => a -> Int
fromEnum
s2w8 :: String -> [Word8]
s2w8 :: [Char] -> [Word8]
s2w8 = forall a b. (a -> b) -> [a] -> [b]
map Char -> Word8
c2w8
w82c :: Word8 -> Char
w82c :: Word8 -> Char
w82c = forall a. Enum a => Int -> a
toEnum forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral
w82s :: [Word8] -> String
w82s :: [Word8] -> [Char]
w82s = forall a b. (a -> b) -> [a] -> [b]
map Word8 -> Char
w82c