primitive-0.6.4.0: Primitive memory-related operations

Copyright(c) Roman Leshchinskiy 2009-2012
LicenseBSD-style
MaintainerRoman Leshchinskiy <rl@cse.unsw.edu.au>
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Primitive.Types

Description

Basic types and classes for primitive array operations

Synopsis

Documentation

class Prim a where Source #

Class of types supporting primitive array operations

Methods

sizeOf# :: a -> Int# Source #

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

Prim Char Source # 
Prim Double Source # 
Prim Float Source # 
Prim Int Source # 
Prim Int8 Source # 
Prim Int16 Source # 
Prim Int32 Source # 
Prim Int64 Source # 
Prim Word Source # 
Prim Word8 Source # 
Prim Word16 Source # 
Prim Word32 Source # 
Prim Word64 Source # 
Prim CDev Source # 
Prim CIno Source # 
Prim CMode Source # 
Prim COff Source # 
Prim CPid Source # 
Prim CSsize Source # 
Prim CGid Source # 
Prim CNlink Source # 
Prim CUid Source # 
Prim CCc Source # 
Prim CSpeed Source # 
Prim CTcflag Source # 
Prim CRLim Source # 
Prim CBlkSize Source # 
Prim CBlkCnt Source # 
Prim CClockId Source # 
Prim CFsBlkCnt Source # 
Prim CFsFilCnt Source # 
Prim CId Source # 
Prim CKey Source # 
Prim CTimer Source # 
Prim Fd Source # 
Prim CChar Source # 
Prim CSChar Source # 
Prim CUChar Source # 
Prim CShort Source # 
Prim CUShort Source # 
Prim CInt Source # 
Prim CUInt Source # 
Prim CLong Source # 
Prim CULong Source # 
Prim CLLong Source # 
Prim CULLong Source # 
Prim CBool Source # 
Prim CFloat Source # 
Prim CDouble Source # 
Prim CPtrdiff Source # 
Prim CSize Source # 
Prim CWchar Source # 
Prim CSigAtomic Source # 
Prim CClock Source # 
Prim CTime Source # 
Prim CUSeconds Source # 
Prim CSUSeconds Source # 
Prim CIntPtr Source # 
Prim CUIntPtr Source # 
Prim CIntMax Source # 
Prim CUIntMax Source # 
Prim Addr Source # 
Prim (Ptr a) Source # 
Prim (FunPtr a) Source # 

sizeOf :: Prim a => a -> Int Source #

Size of values of type a. The argument is not used.

This function has existed since 0.1, but was moved from Primitive to Types in version 0.6.3.0

alignment :: Prim a => a -> Int Source #

Alignment of values of type a. The argument is not used.

This function has existed since 0.1, but was moved from Primitive to Types in version 0.6.3.0

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.

data Addr Source #

A machine address

Constructors

Addr Addr# 

Instances

Eq Addr Source # 

Methods

(==) :: Addr -> Addr -> Bool #

(/=) :: Addr -> Addr -> Bool #

Data Addr Source # 

Methods

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 #

toConstr :: Addr -> Constr #

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 # 

Methods

compare :: Addr -> Addr -> Ordering #

(<) :: Addr -> Addr -> Bool #

(<=) :: Addr -> Addr -> Bool #

(>) :: Addr -> Addr -> Bool #

(>=) :: Addr -> Addr -> Bool #

max :: Addr -> Addr -> Addr #

min :: Addr -> Addr -> Addr #

Show Addr Source # 

Methods

showsPrec :: Int -> Addr -> ShowS #

show :: Addr -> String #

showList :: [Addr] -> ShowS #

Prim Addr 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.

Constructors

PrimStorable 

Fields