{-# LANGUAGE ImportQualifiedPost #-} {-# LANGUAGE BlockArguments, OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables, TypeApplications #-} {-# OPTIONS_GHC -Wall -fno-warn-tabs #-} module Data.ByteString.ToolsYj ( fromBits, fromBits', toBits, toBits', toBitsBE ) where import Data.Bits import Data.Bits.ToolsYj import Data.Bool import Data.ByteString qualified as BS fromBits :: Bits b => b -> BS.ByteString fromBits :: forall b. Bits b => b -> ByteString fromBits = (b -> Maybe (Word8, b)) -> b -> ByteString forall a. (a -> Maybe (Word8, a)) -> a -> ByteString BS.unfoldr \b b -> Maybe (Word8, b) -> Maybe (Word8, b) -> Bool -> Maybe (Word8, b) forall a. a -> a -> Bool -> a bool Maybe (Word8, b) forall a. Maybe a Nothing ((Word8, b) -> Maybe (Word8, b) forall a. a -> Maybe a Just (Int -> b -> Word8 forall a b. (Bits a, Bits b) => Int -> a -> b bitsToBits Int 8 b b, b b b -> Int -> b forall a. Bits a => a -> Int -> a `shiftR` Int 8)) (b b b -> b -> Bool forall a. Eq a => a -> a -> Bool /= b forall a. Bits a => a zeroBits) fromBits' :: FiniteBits b => b -> BS.ByteString fromBits' :: forall b. FiniteBits b => b -> ByteString fromBits' b b0 = Int -> b -> ByteString forall {t} {t}. (Num t, Bits t, Eq t) => t -> t -> ByteString go (b -> Int forall b. FiniteBits b => b -> Int finiteBitSize b b0 Int -> Int -> Int forall a. Integral a => a -> a -> a `div` Int 8) b b0 where go :: t -> t -> ByteString go t 0 t _ = ByteString "" go t n t b = Int -> t -> Word8 forall a b. (Bits a, Bits b) => Int -> a -> b bitsToBits Int 8 t b Word8 -> ByteString -> ByteString `BS.cons` t -> t -> ByteString go (t n t -> t -> t forall a. Num a => a -> a -> a - t 1) (t b t -> Int -> t forall a. Bits a => a -> Int -> a `shiftR` Int 8) toBits :: Bits b => BS.ByteString -> b toBits :: forall b. Bits b => ByteString -> b toBits = (Word8 -> b -> b) -> b -> ByteString -> b forall a. (Word8 -> a -> a) -> a -> ByteString -> a BS.foldr (\Word8 b b s -> Int -> Word8 -> b forall a b. (Bits a, Bits b) => Int -> a -> b bitsToBits Int 8 Word8 b b -> b -> b forall a. Bits a => a -> a -> a .|. b s b -> Int -> b forall a. Bits a => a -> Int -> a `shiftL` Int 8) b forall a. Bits a => a zeroBits toBits' :: forall b . FiniteBits b => BS.ByteString -> Maybe b toBits' :: forall b. FiniteBits b => ByteString -> Maybe b toBits' ByteString bs = Maybe b -> Maybe b -> Bool -> Maybe b forall a. a -> a -> Bool -> a bool Maybe b forall a. Maybe a Nothing (b -> Maybe b forall a. a -> Maybe a Just (b -> Maybe b) -> b -> Maybe b forall a b. (a -> b) -> a -> b $ (Word8 -> b -> b) -> b -> ByteString -> b forall a. (Word8 -> a -> a) -> a -> ByteString -> a BS.foldr (\Word8 b b s -> Int -> Word8 -> b forall a b. (Bits a, Bits b) => Int -> a -> b bitsToBits Int 8 Word8 b b -> b -> b forall a. Bits a => a -> a -> a .|. b s b -> Int -> b forall a. Bits a => a -> Int -> a `shiftL` Int 8) b forall a. Bits a => a zeroBits ByteString bs) (Int 8 Int -> Int -> Int forall a. Num a => a -> a -> a * ByteString -> Int BS.length ByteString bs Int -> Int -> Bool forall a. Ord a => a -> a -> Bool <= forall b. FiniteBits b => b -> Int finiteBitSize @b b forall a. HasCallStack => a undefined) toBitsBE :: Bits b => BS.ByteString -> b toBitsBE :: forall b. Bits b => ByteString -> b toBitsBE = (b -> Word8 -> b) -> b -> ByteString -> b forall a. (a -> Word8 -> a) -> a -> ByteString -> a BS.foldl (\b s Word8 b -> Int -> Word8 -> b forall a b. (Bits a, Bits b) => Int -> a -> b bitsToBits Int 8 Word8 b b -> b -> b forall a. Bits a => a -> a -> a .|. b s b -> Int -> b forall a. Bits a => a -> Int -> a `shiftL` Int 8) b forall a. Bits a => a zeroBits