module Data.Array.Repa.Repr.ByteString
        ( B, Array (..)
        , fromByteString, toByteString)
where
import Data.Array.Repa.Shape
import Data.Array.Repa.Base
import Data.Array.Repa.Repr.Delayed
import Data.Word
import qualified Data.ByteString        as B
import qualified Data.ByteString.Unsafe as BU
import Data.ByteString                  (ByteString)


-- | Strict ByteStrings arrays are represented as ForeignPtr buffers of Word8
data B
        
-- | Read elements from a `ByteString`.
instance Source B Word8 where
 data Array B sh Word8
        = AByteString !sh !ByteString

 linearIndex :: forall sh. Shape sh => Array B sh Word8 -> Int -> Word8
linearIndex (AByteString sh
_ ByteString
bs) Int
ix
        = ByteString
bs HasCallStack => ByteString -> Int -> Word8
ByteString -> Int -> Word8
`B.index` Int
ix
 {-# INLINE linearIndex #-}

 unsafeLinearIndex :: forall sh. Shape sh => Array B sh Word8 -> Int -> Word8
unsafeLinearIndex (AByteString sh
_ ByteString
bs) Int
ix
        = ByteString
bs ByteString -> Int -> Word8
`BU.unsafeIndex` Int
ix
 {-# INLINE unsafeLinearIndex #-}

 extent :: forall sh. Shape sh => Array B sh Word8 -> sh
extent (AByteString sh
sh ByteString
_)
        = sh
sh
 {-# INLINE extent #-}

 deepSeqArray :: forall sh b. Shape sh => Array B sh Word8 -> b -> b
deepSeqArray (AByteString sh
sh ByteString
bs) b
x 
  = sh
sh sh -> b -> b
forall a. sh -> a -> a
forall sh a. Shape sh => sh -> a -> a
`deepSeq` ByteString
bs ByteString -> b -> b
forall a b. a -> b -> b
`seq` b
x
 {-# INLINE deepSeqArray #-}


deriving instance Show sh
        => Show (Array B sh Word8)

deriving instance Read sh
        => Read (Array B sh Word8)


-- Conversions ----------------------------------------------------------------
-- | O(1). Wrap a `ByteString` as an array.
fromByteString
        :: sh -> ByteString -> Array B sh Word8
fromByteString :: forall sh. sh -> ByteString -> Array B sh Word8
fromByteString sh
sh ByteString
bs
        = sh -> ByteString -> Array B sh Word8
forall sh. sh -> ByteString -> Array B sh Word8
AByteString sh
sh ByteString
bs
{-# INLINE fromByteString #-}


-- | O(1). Unpack a `ByteString` from an array.
toByteString :: Array B sh Word8 -> ByteString
toByteString :: forall sh. Array B sh Word8 -> ByteString
toByteString (AByteString sh
_ ByteString
bs) = ByteString
bs
{-# INLINE toByteString #-}