module Data.ByteArray.View
( View
, view
, takeView
, dropView
) where
import Data.ByteArray.Methods
import Data.ByteArray.Types
import Data.Memory.PtrMethods
import Data.Memory.Internal.Compat
import Foreign.Ptr (plusPtr)
import Prelude hiding (length, take, drop)
data View bytes = View
{ viewOffset :: !Int
, viewSize :: !Int
, unView :: !bytes
}
instance ByteArrayAccess bytes => Eq (View bytes) where
(==) = constEq
instance ByteArrayAccess bytes => Ord (View bytes) where
compare v1 v2 = unsafeDoIO $
withByteArray v1 $ \ptr1 ->
withByteArray v2 $ \ptr2 -> do
ret <- memCompare ptr1 ptr2 (min (viewSize v1) (viewSize v2))
return $ case ret of
EQ | length v1 > length v2 -> GT
| length v1 < length v2 -> LT
| length v1 == length v2 -> EQ
_ -> ret
instance ByteArrayAccess bytes => Show (View bytes) where
showsPrec p v r = showsPrec p (viewUnpackChars v []) r
instance ByteArrayAccess bytes => ByteArrayAccess (View bytes) where
length = viewSize
withByteArray v f = withByteArray (unView v) $ \ptr -> f (ptr `plusPtr` (viewOffset v))
viewUnpackChars :: ByteArrayAccess bytes
=> View bytes
-> String
-> String
viewUnpackChars v xs = chunkLoop 0
where
len = length v
chunkLoop :: Int -> [Char]
chunkLoop idx
| len == idx = []
| (len - idx) > 63 =
bytesLoop idx (idx + 64) (chunkLoop (idx + 64))
| otherwise =
bytesLoop idx (len - idx) xs
bytesLoop :: Int -> Int -> [Char] -> [Char]
bytesLoop idx chunkLenM1 paramAcc =
loop (idx + chunkLenM1 - 1) paramAcc
where
loop i acc
| i == idx = (rChar i : acc)
| otherwise = loop (i - 1) (rChar i : acc)
rChar :: Int -> Char
rChar idx = toEnum $ fromIntegral $ index v idx
view :: ByteArrayAccess bytes
=> bytes
-> Int
-> Int
-> View bytes
view b offset'' size'' = View offset size b
where
offset' :: Int
offset' = max offset'' 0
offset :: Int
offset = min offset' (length b - 1)
size' :: Int
size' = max size'' 0
size :: Int
size = min size' (length b - offset)
takeView :: ByteArrayAccess bytes
=> bytes
-> Int
-> View bytes
takeView b size = view b 0 size
dropView :: ByteArrayAccess bytes
=> bytes
-> Int
-> View bytes
dropView b offset = view b offset (length b - offset)