module Data.ByteArray (
ByteArray(..)
) where
import Data.Bits ((.&.), unsafeShiftR)
import Data.Data (mkNoRepType, Data(..))
import qualified Data.Foldable as F
import Data.Semigroup
import GHC.Show (intToDigit)
import GHC.Exts
import GHC.ST (ST(..), runST)
import GHC.Word (Word8(..))
data ByteArray = ByteArray ByteArray#
data MutableByteArray s = MutableByteArray (MutableByteArray# s)
newByteArray :: Int -> ST s (MutableByteArray s)
newByteArray (I# n#) =
ST (\s# -> case newByteArray# n# s# of
(# s'#, arr# #) -> (# s'#, MutableByteArray arr# #))
unsafeFreezeByteArray :: MutableByteArray s -> ST s ByteArray
unsafeFreezeByteArray (MutableByteArray arr#) =
ST (\s# -> case unsafeFreezeByteArray# arr# s# of
(# s'#, arr'# #) -> (# s'#, ByteArray arr'# #))
sizeofByteArray :: ByteArray -> Int
sizeofByteArray (ByteArray arr#) = I# (sizeofByteArray# arr#)
indexByteArray :: ByteArray -> Int -> Word8
indexByteArray (ByteArray arr#) (I# i#) = W8# (indexWord8Array# arr# i#)
writeByteArray :: MutableByteArray s -> Int -> Word8 -> ST s ()
writeByteArray (MutableByteArray arr#) (I# i#) (W8# x#) =
ST (\s# -> case writeWord8Array# arr# i# x# s# of
s'# -> (# s'#, () #))
byteArrayToList :: ByteArray -> [Word8]
byteArrayToList arr = go 0
where
go i
| i < maxI = indexByteArray arr i : go (i+1)
| otherwise = []
maxI = sizeofByteArray arr
byteArrayFromListN :: Int -> [Word8] -> ByteArray
byteArrayFromListN n ys = runST $ do
marr <- newByteArray n
let go !ix [] = if ix == n
then return ()
else error $ "Data.ByteArray.byteArrayFromListN: list length less than specified size"
go !ix (x : xs) = if ix < n
then do
writeByteArray marr ix x
go (ix + 1) xs
else error $ "Data.ByteArray.byteArrayFromListN: list length greater than specified size"
go 0 ys
unsafeFreezeByteArray marr
copyByteArray
:: MutableByteArray s
-> Int
-> ByteArray
-> Int
-> Int
-> ST s ()
copyByteArray (MutableByteArray dst#) (I# doff#) (ByteArray src#) (I# soff#) (I# sz#) =
ST (\s# -> case copyByteArray# src# soff# dst# doff# sz# s# of
s'# -> (# s'#, () #))
instance Data ByteArray where
toConstr _ = error "toConstr"
gunfold _ _ = error "gunfold"
dataTypeOf _ = mkNoRepType "Data.ByteArray.ByteArray"
instance Show ByteArray where
showsPrec _ ba =
showString "[" . go 0
where
showW8 :: Word8 -> String -> String
showW8 !w s =
'0'
: 'x'
: intToDigit (fromIntegral (unsafeShiftR w 4))
: intToDigit (fromIntegral (w .&. 0x0F))
: s
go i
| i < sizeofByteArray ba = comma . showW8 (indexByteArray ba i :: Word8) . go (i+1)
| otherwise = showChar ']'
where
comma | i == 0 = id
| otherwise = showString ", "
compareByteArraysFromBeginning :: ByteArray -> ByteArray -> Int -> Ordering
compareByteArraysFromBeginning (ByteArray ba1#) (ByteArray ba2#) (I# n#)
= compare (I# (compareByteArrays# ba1# 0# ba2# 0# n#)) 0
sameByteArray :: ByteArray# -> ByteArray# -> Bool
sameByteArray ba1 ba2 =
case reallyUnsafePtrEquality# (unsafeCoerce# ba1 :: ()) (unsafeCoerce# ba2 :: ()) of
r -> isTrue# r
instance Eq ByteArray where
ba1@(ByteArray ba1#) == ba2@(ByteArray ba2#)
| sameByteArray ba1# ba2# = True
| n1 /= n2 = False
| otherwise = compareByteArraysFromBeginning ba1 ba2 n1 == EQ
where
n1 = sizeofByteArray ba1
n2 = sizeofByteArray ba2
instance Ord ByteArray where
ba1@(ByteArray ba1#) `compare` ba2@(ByteArray ba2#)
| sameByteArray ba1# ba2# = EQ
| n1 /= n2 = n1 `compare` n2
| otherwise = compareByteArraysFromBeginning ba1 ba2 n1
where
n1 = sizeofByteArray ba1
n2 = sizeofByteArray ba2
appendByteArray :: ByteArray -> ByteArray -> ByteArray
appendByteArray a b = runST $ do
marr <- newByteArray (sizeofByteArray a + sizeofByteArray b)
copyByteArray marr 0 a 0 (sizeofByteArray a)
copyByteArray marr (sizeofByteArray a) b 0 (sizeofByteArray b)
unsafeFreezeByteArray marr
concatByteArray :: [ByteArray] -> ByteArray
concatByteArray arrs = runST $ do
let len = calcLength arrs 0
marr <- newByteArray len
pasteByteArrays marr 0 arrs
unsafeFreezeByteArray marr
pasteByteArrays :: MutableByteArray s -> Int -> [ByteArray] -> ST s ()
pasteByteArrays !_ !_ [] = return ()
pasteByteArrays !marr !ix (x : xs) = do
copyByteArray marr ix x 0 (sizeofByteArray x)
pasteByteArrays marr (ix + sizeofByteArray x) xs
calcLength :: [ByteArray] -> Int -> Int
calcLength [] !n = n
calcLength (x : xs) !n = calcLength xs (sizeofByteArray x + n)
emptyByteArray :: ByteArray
emptyByteArray = runST (newByteArray 0 >>= unsafeFreezeByteArray)
replicateByteArray :: Int -> ByteArray -> ByteArray
replicateByteArray n arr = runST $ do
marr <- newByteArray (n * sizeofByteArray arr)
let go i = if i < n
then do
copyByteArray marr (i * sizeofByteArray arr) arr 0 (sizeofByteArray arr)
go (i + 1)
else return ()
go 0
unsafeFreezeByteArray marr
instance Semigroup ByteArray where
(<>) = appendByteArray
sconcat = mconcat . F.toList
stimes i arr
| itgr < 1 = emptyByteArray
| itgr <= (fromIntegral (maxBound :: Int)) = replicateByteArray (fromIntegral itgr) arr
| otherwise = error "Data.ByteArray#stimes: cannot allocate the requested amount of memory"
where itgr = toInteger i :: Integer
instance Monoid ByteArray where
mempty = emptyByteArray
mconcat = concatByteArray
instance IsList ByteArray where
type Item ByteArray = Word8
toList = byteArrayToList
fromList xs = byteArrayFromListN (length xs) xs
fromListN = byteArrayFromListN