Blame Data/ByteArray/View.hs

Packit c1c4f9
-- |
Packit c1c4f9
-- Module      : Data.ByteArray.View
Packit c1c4f9
-- License     : BSD-style
Packit c1c4f9
-- Maintainer  : Nicolas DI PRIMA <nicolas@di-prima.fr>
Packit c1c4f9
-- Stability   : stable
Packit c1c4f9
-- Portability : Good
Packit c1c4f9
--
Packit c1c4f9
-- a View on a given ByteArrayAccess
Packit c1c4f9
--
Packit c1c4f9
Packit c1c4f9
module Data.ByteArray.View
Packit c1c4f9
    ( View
Packit c1c4f9
    , view
Packit c1c4f9
    , takeView
Packit c1c4f9
    , dropView
Packit c1c4f9
    ) where
Packit c1c4f9
Packit c1c4f9
import Data.ByteArray.Methods
Packit c1c4f9
import Data.ByteArray.Types
Packit c1c4f9
import Data.Memory.PtrMethods
Packit c1c4f9
import Data.Memory.Internal.Compat
Packit c1c4f9
import Foreign.Ptr (plusPtr)
Packit c1c4f9
Packit c1c4f9
import Prelude hiding (length, take, drop)
Packit c1c4f9
Packit c1c4f9
-- | a view on a given bytes
Packit c1c4f9
--
Packit c1c4f9
-- Equality test in constant time
Packit c1c4f9
data View bytes = View
Packit c1c4f9
    { viewOffset :: !Int
Packit c1c4f9
    , viewSize   :: !Int
Packit c1c4f9
    , unView     :: !bytes
Packit c1c4f9
    }
Packit c1c4f9
Packit c1c4f9
instance ByteArrayAccess bytes => Eq (View bytes) where
Packit c1c4f9
    (==) = constEq
Packit c1c4f9
Packit c1c4f9
instance ByteArrayAccess bytes => Ord (View bytes) where
Packit c1c4f9
    compare v1 v2 = unsafeDoIO $
Packit c1c4f9
        withByteArray v1 $ \ptr1 ->
Packit c1c4f9
        withByteArray v2 $ \ptr2 -> do
Packit c1c4f9
            ret <- memCompare ptr1 ptr2 (min (viewSize v1) (viewSize v2))
Packit c1c4f9
            return $ case ret of
Packit c1c4f9
                EQ | length v1 >  length v2 -> GT
Packit c1c4f9
                   | length v1 <  length v2 -> LT
Packit c1c4f9
                   | length v1 == length v2 -> EQ
Packit c1c4f9
                _                           -> ret
Packit c1c4f9
Packit c1c4f9
instance ByteArrayAccess bytes => Show (View bytes) where
Packit c1c4f9
    showsPrec p v r = showsPrec p (viewUnpackChars v []) r
Packit c1c4f9
Packit c1c4f9
instance ByteArrayAccess bytes => ByteArrayAccess (View bytes) where
Packit c1c4f9
    length = viewSize
Packit c1c4f9
    withByteArray v f = withByteArray (unView v) $ \ptr -> f (ptr `plusPtr` (viewOffset v))
Packit c1c4f9
Packit c1c4f9
viewUnpackChars :: ByteArrayAccess bytes
Packit c1c4f9
                => View bytes
Packit c1c4f9
                -> String
Packit c1c4f9
                -> String
Packit c1c4f9
viewUnpackChars v xs = chunkLoop 0
Packit c1c4f9
  where
Packit c1c4f9
    len = length v
Packit c1c4f9
Packit c1c4f9
    chunkLoop :: Int -> [Char]
Packit c1c4f9
    chunkLoop idx
Packit c1c4f9
        | len == idx = []
Packit c1c4f9
        | (len - idx) > 63 =
Packit c1c4f9
            bytesLoop idx (idx + 64) (chunkLoop (idx + 64))
Packit c1c4f9
        | otherwise =
Packit c1c4f9
            bytesLoop idx (len - idx) xs
Packit c1c4f9
Packit c1c4f9
    bytesLoop :: Int -> Int -> [Char] -> [Char]
Packit c1c4f9
    bytesLoop idx chunkLenM1 paramAcc =
Packit c1c4f9
        loop (idx + chunkLenM1 - 1) paramAcc
Packit c1c4f9
      where
Packit c1c4f9
        loop i acc
Packit c1c4f9
            | i == idx  = (rChar i : acc)
Packit c1c4f9
            | otherwise = loop (i - 1) (rChar i : acc)
Packit c1c4f9
Packit c1c4f9
    rChar :: Int -> Char
Packit c1c4f9
    rChar idx = toEnum $ fromIntegral $ index v idx
Packit c1c4f9
Packit c1c4f9
-- | create a view on a given bytearray
Packit c1c4f9
--
Packit c1c4f9
-- This function update the offset and the size in order to guarantee:
Packit c1c4f9
--
Packit c1c4f9
-- * offset >= 0
Packit c1c4f9
-- * size >= 0
Packit c1c4f9
-- * offset < length
Packit c1c4f9
-- * size =< length - offset
Packit c1c4f9
--
Packit c1c4f9
view :: ByteArrayAccess bytes
Packit c1c4f9
     => bytes -- ^ the byte array we put a view on
Packit c1c4f9
     -> Int   -- ^ the offset to start the byte array on
Packit c1c4f9
     -> Int   -- ^ the size of the view
Packit c1c4f9
     -> View bytes
Packit c1c4f9
view b offset'' size'' = View offset size b
Packit c1c4f9
  where
Packit c1c4f9
    -- make sure offset is not negative
Packit c1c4f9
    offset' :: Int
Packit c1c4f9
    offset' = max offset'' 0
Packit c1c4f9
Packit c1c4f9
    -- make sure the offset is not out of bound
Packit c1c4f9
    offset :: Int
Packit c1c4f9
    offset = min offset' (length b - 1)
Packit c1c4f9
Packit c1c4f9
    -- make sure length is not negative
Packit c1c4f9
    size' :: Int
Packit c1c4f9
    size' = max size'' 0
Packit c1c4f9
Packit c1c4f9
    -- make sure the length is not out of the bound
Packit c1c4f9
    size :: Int
Packit c1c4f9
    size = min size' (length b - offset)
Packit c1c4f9
Packit c1c4f9
-- | create a view from the given bytearray
Packit c1c4f9
takeView :: ByteArrayAccess bytes
Packit c1c4f9
         => bytes -- ^ byte aray
Packit c1c4f9
         -> Int   -- ^ size of the view
Packit c1c4f9
         -> View bytes
Packit c1c4f9
takeView b size = view b 0 size
Packit c1c4f9
Packit c1c4f9
-- | create a view from the given byte array
Packit c1c4f9
-- starting after having dropped the fist n bytes
Packit c1c4f9
dropView :: ByteArrayAccess bytes
Packit c1c4f9
         => bytes -- ^ byte array
Packit c1c4f9
         -> Int   -- ^ the number of bytes do dropped before creating the view
Packit c1c4f9
         -> View bytes
Packit c1c4f9
dropView b offset = view b offset (length b - offset)