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