Copyright | (c) Roman Leshchinskiy 2009-2012 |
---|---|
License | BSD-style |
Maintainer | Roman Leshchinskiy <rl@cse.unsw.edu.au> |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Basic types and classes for primitive array operations
Synopsis
- class Prim a where
- sizeOf :: Prim a => a -> Int
- alignment :: Prim a => a -> Int
- defaultSetByteArray# :: Prim a => MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s
- defaultSetOffAddr# :: Prim a => Addr# -> Int# -> Int# -> a -> State# s -> State# s
- data Addr = Addr Addr#
- newtype PrimStorable a = PrimStorable {
- getPrimStorable :: a
Documentation
Class of types supporting primitive array operations
sizeOf#, alignment#, indexByteArray#, readByteArray#, writeByteArray#, setByteArray#, indexOffAddr#, readOffAddr#, writeOffAddr#, setOffAddr#
Size of values of type a
. The argument is not used.
alignment# :: a -> Int# Source #
Alignment of values of type a
. The argument is not used.
indexByteArray# :: ByteArray# -> Int# -> a Source #
Read a value from the array. The offset is in elements of type
a
rather than in bytes.
readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, a#) Source #
Read a value from the mutable array. The offset is in elements of type
a
rather than in bytes.
writeByteArray# :: MutableByteArray# s -> Int# -> a -> State# s -> State# s Source #
Write a value to the mutable array. The offset is in elements of type
a
rather than in bytes.
setByteArray# :: MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s Source #
Fill a slice of the mutable array with a value. The offset and length
of the chunk are in elements of type a
rather than in bytes.
indexOffAddr# :: Addr# -> Int# -> a Source #
Read a value from a memory position given by an address and an offset.
The memory block the address refers to must be immutable. The offset is in
elements of type a
rather than in bytes.
readOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, a#) Source #
Read a value from a memory position given by an address and an offset.
The offset is in elements of type a
rather than in bytes.
writeOffAddr# :: Addr# -> Int# -> a -> State# s -> State# s Source #
Write a value to a memory position given by an address and an offset.
The offset is in elements of type a
rather than in bytes.
setOffAddr# :: Addr# -> Int# -> Int# -> a -> State# s -> State# s Source #
Fill a memory block given by an address, an offset and a length.
The offset and length are in elements of type a
rather than in bytes.
Instances
defaultSetByteArray# :: Prim a => MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s Source #
An implementation of setByteArray#
that calls writeByteArray#
to set each element. This is helpful when writing a Prim
instance
for a multi-word data type for which there is no cpu-accelerated way
to broadcast a value to contiguous memory. It is typically used
alongside defaultSetOffAddr#
. For example:
data Trip = Trip Int Int Int instance Prim Trip sizeOf# _ = 3# *# sizeOf# (undefined :: Int) alignment# _ = alignment# (undefined :: Int) indexByteArray# arr# i# = ... readByteArray# arr# i# = ... writeByteArray# arr# i# (Trip a b c) = \s0 -> case writeByteArray# arr# (3# *# i#) a s0 of s1 -> case writeByteArray# arr# ((3# *# i#) +# 1#) b s1 of s2 -> case writeByteArray# arr# ((3# *# i#) +# 2# ) c s2 of s3 -> s3 setByteArray# = defaultSetByteArray# indexOffAddr# addr# i# = ... readOffAddr# addr# i# = ... writeOffAddr# addr# i# (Trip a b c) = \s0 -> case writeOffAddr# addr# (3# *# i#) a s0 of s1 -> case writeOffAddr# addr# ((3# *# i#) +# 1#) b s1 of s2 -> case writeOffAddr# addr# ((3# *# i#) +# 2# ) c s2 of s3 -> s3 setOffAddr# = defaultSetOffAddr#
defaultSetOffAddr# :: Prim a => Addr# -> Int# -> Int# -> a -> State# s -> State# s Source #
An implementation of setOffAddr#
that calls writeOffAddr#
to set each element. The documentation of defaultSetByteArray#
provides an example of how to use this.
A machine address
Instances
Eq Addr Source # | |
Data Addr Source # | |
Defined in Data.Primitive.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Addr -> c Addr # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Addr # dataTypeOf :: Addr -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Addr) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Addr) # gmapT :: (forall b. Data b => b -> b) -> Addr -> Addr # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Addr -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Addr -> r # gmapQ :: (forall d. Data d => d -> u) -> Addr -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Addr -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Addr -> m Addr # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Addr -> m Addr # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Addr -> m Addr # | |
Ord Addr Source # | |
Show Addr Source # | |
Prim Addr Source # | |
Defined in Data.Primitive.Types sizeOf# :: Addr -> Int# Source # alignment# :: Addr -> Int# Source # indexByteArray# :: ByteArray# -> Int# -> Addr Source # readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Addr#) Source # writeByteArray# :: MutableByteArray# s -> Int# -> Addr -> State# s -> State# s Source # setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Addr -> State# s -> State# s Source # indexOffAddr# :: Addr# -> Int# -> Addr Source # readOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Addr#) Source # writeOffAddr# :: Addr# -> Int# -> Addr -> State# s -> State# s Source # setOffAddr# :: Addr# -> Int# -> Int# -> Addr -> State# s -> State# s Source # |
newtype PrimStorable a Source #
Newtype that uses a Prim
instance to give rise to a Storable
instance.
This type is intended to be used with the DerivingVia
extension available
in GHC 8.6 and up. For example, consider a user-defined Prim
instance for
a multi-word data type.
data Uuid = Uuid Word64 Word64 deriving Storable via (PrimStorable Uuid) instance Prim Uuid where ...
Writing the Prim
instance is tedious and unavoidable, but the Storable
instance comes for free once the Prim
instance is written.
Instances
Prim a => Storable (PrimStorable a) Source # | |
Defined in Data.Primitive.Types sizeOf :: PrimStorable a -> Int # alignment :: PrimStorable a -> Int # peekElemOff :: Ptr (PrimStorable a) -> Int -> IO (PrimStorable a) # pokeElemOff :: Ptr (PrimStorable a) -> Int -> PrimStorable a -> IO () # peekByteOff :: Ptr b -> Int -> IO (PrimStorable a) # pokeByteOff :: Ptr b -> Int -> PrimStorable a -> IO () # peek :: Ptr (PrimStorable a) -> IO (PrimStorable a) # poke :: Ptr (PrimStorable a) -> PrimStorable a -> IO () # |