{-# language BangPatterns #-}
{-# language MagicHash #-}
{-# language NamedFieldPuns #-}
{-# language TypeApplications #-}
{-# language UnboxedTuples #-}
module Data.Bytes
(
Bytes
, null
, length
, takeWhile
, dropWhile
, takeWhileEnd
, dropWhileEnd
, foldl
, foldl'
, foldr
, foldr'
, elem
, Byte.split
, Byte.splitInit
, splitFirst
, Byte.count
, isPrefixOf
, isSuffixOf
, stripPrefix
, stripOptionalPrefix
, stripSuffix
, stripOptionalSuffix
, unsafeTake
, unsafeDrop
, unsafeIndex
, copy
, pin
, contents
, touch
, toByteArray
, toByteArrayClone
, fromAsciiString
, fromByteArray
, toLatinString
) where
import Prelude hiding (length,takeWhile,dropWhile,null,foldl,foldr,elem)
import Control.Monad.Primitive (PrimMonad,PrimState,primitive_,unsafeIOToPrim)
import Control.Monad.ST.Run (runByteArrayST)
import Control.Monad.ST (runST)
import Data.Bytes.Types (Bytes(Bytes,array,offset))
import Data.Char (ord)
import Data.Primitive (ByteArray(ByteArray),MutableByteArray)
import GHC.Exts (Int(I#),Char(C#),word2Int#,chr#)
import GHC.Exts (Word#,Int#)
import GHC.Word (Word8(W8#))
import Foreign.Ptr (Ptr,plusPtr)
import qualified Data.Primitive as PM
import qualified Data.Bytes.Byte as Byte
import qualified GHC.Exts as Exts
null :: Bytes -> Bool
null (Bytes _ _ len) = len == 0
length :: Bytes -> Int
length (Bytes _ _ len) = len
isPrefixOf :: Bytes -> Bytes -> Bool
isPrefixOf (Bytes a aOff aLen) (Bytes b bOff bLen) =
if aLen <= bLen
then compareByteArrays a aOff b bOff aLen == EQ
else False
isSuffixOf :: Bytes -> Bytes -> Bool
isSuffixOf (Bytes a aOff aLen) (Bytes b bOff bLen) =
if aLen <= bLen
then compareByteArrays a aOff b (bOff + bLen - aLen) aLen == EQ
else False
stripPrefix :: Bytes -> Bytes -> Maybe Bytes
stripPrefix !pre !str = if pre `isPrefixOf` str
then Just (Bytes (array str) (offset str + length pre) (length str - length pre))
else Nothing
stripOptionalPrefix :: Bytes -> Bytes -> Bytes
stripOptionalPrefix !pre !str = if pre `isPrefixOf` str
then Bytes (array str) (offset str + length pre) (length str - length pre)
else str
stripSuffix :: Bytes -> Bytes -> Maybe Bytes
stripSuffix !suf !str = if suf `isSuffixOf` str
then Just (Bytes (array str) (offset str) (length str - length suf))
else Nothing
stripOptionalSuffix :: Bytes -> Bytes -> Bytes
stripOptionalSuffix !suf !str = if suf `isSuffixOf` str
then Bytes (array str) (offset str) (length str - length suf)
else str
splitFirst :: Word8 -> Bytes -> Maybe (Bytes,Bytes)
{-# inline splitFirst #-}
splitFirst w b@(Bytes arr off len) = case elemIndexLoop# w b of
(-1#) -> Nothing
i# -> let i = I# i# in
Just (Bytes arr off (i - off), Bytes arr (i + 1) (len - (1 + i - off)))
elemIndexLoop# :: Word8 -> Bytes -> Int#
elemIndexLoop# !w (Bytes arr off@(I# off# ) len) = case len of
0 -> (-1#)
_ -> if PM.indexByteArray arr off == w
then off#
else elemIndexLoop# w (Bytes arr (off + 1) (len - 1))
elem :: Word8 -> Bytes -> Bool
elem (W8# w) b = case elemLoop 0# w b of
1# -> True
_ -> False
elemLoop :: Int# -> Word# -> Bytes -> Int#
elemLoop !r !w (Bytes arr@(ByteArray arr# ) off@(I# off# ) len) = case len of
0 -> r
_ -> elemLoop (Exts.orI# r (Exts.eqWord# w (Exts.indexWord8Array# arr# off# ) )) w (Bytes arr (off + 1) (len - 1))
takeWhile :: (Word8 -> Bool) -> Bytes -> Bytes
{-# inline takeWhile #-}
takeWhile k b = unsafeTake (countWhile k b) b
dropWhile :: (Word8 -> Bool) -> Bytes -> Bytes
{-# inline dropWhile #-}
dropWhile k b = unsafeDrop (countWhile k b) b
unsafeIndex :: Bytes -> Int -> Word8
unsafeIndex (Bytes arr off _) ix = PM.indexByteArray arr (off + ix)
dropWhileEnd :: (Word8 -> Bool) -> Bytes -> Bytes
{-# inline dropWhileEnd #-}
dropWhileEnd k !b = unsafeTake (length b - countWhileEnd k b) b
takeWhileEnd :: (Word8 -> Bool) -> Bytes -> Bytes
{-# inline takeWhileEnd #-}
takeWhileEnd k !b =
let n = countWhileEnd k b
in Bytes (array b) (offset b + length b - n) n
unsafeTake :: Int -> Bytes -> Bytes
{-# inline unsafeTake #-}
unsafeTake n (Bytes arr off _) =
Bytes arr off n
unsafeDrop :: Int -> Bytes -> Bytes
{-# inline unsafeDrop #-}
unsafeDrop n (Bytes arr off len) =
Bytes arr (off + n) (len - n)
countWhile :: (Word8 -> Bool) -> Bytes -> Int
{-# inline countWhile #-}
countWhile k (Bytes arr off0 len0) = go off0 len0 0 where
go !off !len !n = if len > 0
then if k (PM.indexByteArray arr off)
then go (off + 1) (len - 1) (n + 1)
else n
else n
countWhileEnd :: (Word8 -> Bool) -> Bytes -> Int
{-# inline countWhileEnd #-}
countWhileEnd k (Bytes arr off0 len0) = go (off0 + len0 - 1) (len0 - 1) 0 where
go !off !len !n = if len >= 0
then if k (PM.indexByteArray arr off)
then go (off - 1) (len - 1) (n + 1)
else n
else n
foldl :: (a -> Word8 -> a) -> a -> Bytes -> a
{-# inline foldl #-}
foldl f a0 (Bytes arr off0 len0) =
go (off0 + len0 - 1) (len0 - 1)
where
go !off !ix = case ix of
(-1) -> a0
_ -> f (go (off - 1) (ix - 1)) (PM.indexByteArray arr off)
foldr :: (Word8 -> a -> a) -> a -> Bytes -> a
{-# inline foldr #-}
foldr f a0 (Bytes arr off0 len0) = go off0 len0 where
go !off !len = case len of
0 -> a0
_ -> f (PM.indexByteArray arr off) (go (off + 1) (len - 1))
foldl' :: (a -> Word8 -> a) -> a -> Bytes -> a
{-# inline foldl' #-}
foldl' f a0 (Bytes arr off0 len0) = go a0 off0 len0 where
go !a !off !len = case len of
0 -> a
_ -> go (f a (PM.indexByteArray arr off)) (off + 1) (len - 1)
foldr' :: (Word8 -> a -> a) -> a -> Bytes -> a
{-# inline foldr' #-}
foldr' f a0 (Bytes arr off0 len0) =
go a0 (off0 + len0 - 1) (len0 - 1)
where
go !a !off !ix = case ix of
(-1) -> a
_ -> go (f (PM.indexByteArray arr off) a) (off - 1) (ix - 1)
toByteArray :: Bytes -> ByteArray
toByteArray b@(Bytes arr off len)
| off /= 0 = toByteArrayClone b
| PM.sizeofByteArray arr /= len = toByteArrayClone b
| otherwise = arr
toByteArrayClone :: Bytes -> ByteArray
toByteArrayClone (Bytes arr off len) = runByteArrayST $ do
m <- PM.newByteArray len
PM.copyByteArray m 0 arr off len
PM.unsafeFreezeByteArray m
fromAsciiString :: String -> Bytes
fromAsciiString = fromByteArray . Exts.fromList . map (fromIntegral @Int @Word8 . ord)
toLatinString :: Bytes -> String
toLatinString = foldr (\(W8# w) xs -> C# (chr# (word2Int# w)) : xs) []
fromByteArray :: ByteArray -> Bytes
fromByteArray b = Bytes b 0 (PM.sizeofByteArray b)
compareByteArrays :: ByteArray -> Int -> ByteArray -> Int -> Int -> Ordering
{-# INLINE compareByteArrays #-}
compareByteArrays (ByteArray ba1#) (I# off1#) (ByteArray ba2#) (I# off2#) (I# n#) =
compare (I# (Exts.compareByteArrays# ba1# off1# ba2# off2# n#)) 0
copy :: PrimMonad m
=> MutableByteArray (PrimState m)
-> Int
-> Bytes
-> m ()
{-# inline copy #-}
copy dst dstIx (Bytes src srcIx len) =
PM.copyByteArray dst dstIx src srcIx len
pin :: Bytes -> Bytes
pin b@(Bytes arr _ len) = case PM.isByteArrayPinned arr of
True -> b
False -> runST $ do
dst <- PM.newPinnedByteArray len
copy dst 0 b
r <- PM.unsafeFreezeByteArray dst
pure (Bytes r 0 len)
contents :: Bytes -> Ptr Word8
contents (Bytes arr off _) = plusPtr (PM.byteArrayContents arr) off
touch :: PrimMonad m => Bytes -> m ()
touch (Bytes (ByteArray arr) _ _) = unsafeIOToPrim
(primitive_ (\s -> Exts.touch# arr s))