primitive-0.6.2.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 Addr Source # 
Prim (Ptr a) Source # 
Prim (FunPtr a) Source # 

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 #

Prim Addr Source #