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)
data B
instance Source B Word8 where
data Array B sh Word8
= AByteString !sh !ByteString
linearIndex :: Array B sh Word8 -> Int -> Word8
linearIndex (AByteString _ bs) Int
ix
= ByteString
bs ByteString -> Int -> Word8
`B.index` Int
ix
{-# INLINE linearIndex #-}
unsafeLinearIndex :: Array B sh Word8 -> Int -> Word8
unsafeLinearIndex (AByteString _ bs) Int
ix
= ByteString
bs ByteString -> Int -> Word8
`BU.unsafeIndex` Int
ix
{-# INLINE unsafeLinearIndex #-}
extent :: Array B sh Word8 -> sh
extent (AByteString sh _)
= sh
sh
{-# INLINE extent #-}
deepSeqArray :: Array B sh Word8 -> b -> b
deepSeqArray (AByteString sh bs) b
x
= sh
sh sh -> b -> b
forall sh a. Shape sh => sh -> a -> a
`deepSeq` ByteString
bs ByteString -> 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)
fromByteString
:: sh -> ByteString -> Array B sh Word8
fromByteString :: 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 #-}
toByteString :: Array B sh Word8 -> ByteString
toByteString :: Array B sh Word8 -> ByteString
toByteString (AByteString _ bs) = ByteString
bs
{-# INLINE toByteString #-}