{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE BlockArguments, OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables, TypeApplications #-}
{-# OPTIONS_GHC -Wall -fno-warn-tabs #-}
module Data.ByteString.Lazy.ToolsYj (
fromBits, fromBits', toBits, toBits',
fromBitsBE', toBitsBE,
splitAt'
) where
import Data.Bits
import Data.Bits.ToolsYj
import Data.Bool
import Data.Int
import Data.ByteString.Lazy qualified as LBS
fromBits :: Bits b => b -> LBS.ByteString
fromBits :: forall b. Bits b => b -> ByteString
fromBits = (b -> Maybe (Word8, b)) -> b -> ByteString
forall a. (a -> Maybe (Word8, a)) -> a -> ByteString
LBS.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 -> LBS.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
`LBS.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 => LBS.ByteString -> b
toBits :: forall b. Bits b => ByteString -> b
toBits = (Word8 -> b -> b) -> b -> ByteString -> b
forall a. (Word8 -> a -> a) -> a -> ByteString -> a
LBS.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 => LBS.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
LBS.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)
(Int64
8 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* ByteString -> Int64
LBS.length ByteString
bs Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall b. FiniteBits b => b -> Int
finiteBitSize @b b
forall a. HasCallStack => a
undefined))
toBitsBE :: Bits b => LBS.ByteString -> b
toBitsBE :: forall b. Bits b => ByteString -> b
toBitsBE = (b -> Word8 -> b) -> b -> ByteString -> b
forall a. (a -> Word8 -> a) -> a -> ByteString -> a
LBS.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
fromBitsBE' :: FiniteBits b => b -> LBS.ByteString
fromBitsBE' :: forall b. FiniteBits b => b -> ByteString
fromBitsBE' 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 -> a -> ByteString
go t
0 a
_ = ByteString
""
go t
n a
b = t -> a -> ByteString
go (t
n t -> t -> t
forall a. Num a => a -> a -> a
- t
1) (a
b a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftR` Int
8) ByteString -> Word8 -> ByteString
`LBS.snoc` Int -> a -> Word8
forall a b. (Bits a, Bits b) => Int -> a -> b
bitsToBits Int
8 a
b
splitAt' :: Int64 -> LBS.ByteString -> Maybe (LBS.ByteString, LBS.ByteString)
splitAt' :: Int64 -> ByteString -> Maybe (ByteString, ByteString)
splitAt' Int64
n ByteString
bs
| ByteString -> Int64
LBS.length ByteString
bs Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< Int64
n = Maybe (ByteString, ByteString)
forall a. Maybe a
Nothing
| Bool
otherwise = (ByteString, ByteString) -> Maybe (ByteString, ByteString)
forall a. a -> Maybe a
Just ((ByteString, ByteString) -> Maybe (ByteString, ByteString))
-> (ByteString, ByteString) -> Maybe (ByteString, ByteString)
forall a b. (a -> b) -> a -> b
$ Int64 -> ByteString -> (ByteString, ByteString)
LBS.splitAt Int64
n ByteString
bs