Copyright | (c) Roman Leshchinskiy 2009-2012 |
---|---|
License | BSD-style |
Maintainer | Roman Leshchinskiy <rl@cse.unsw.edu.au> |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Primitive operations on machine addresses.
Since: 0.6.4.0
Synopsis
- data Ptr a = Ptr Addr#
- nullPtr :: Ptr a
- advancePtr :: forall a. Prim a => Ptr a -> Int -> Ptr a
- subtractPtr :: forall a. Prim a => Ptr a -> Ptr a -> Int
- indexOffPtr :: Prim a => Ptr a -> Int -> a
- readOffPtr :: (Prim a, PrimMonad m) => Ptr a -> Int -> m a
- writeOffPtr :: (Prim a, PrimMonad m) => Ptr a -> Int -> a -> m ()
- copyPtr :: forall m a. (PrimMonad m, Prim a) => Ptr a -> Ptr a -> Int -> m ()
- movePtr :: forall m a. (PrimMonad m, Prim a) => Ptr a -> Ptr a -> Int -> m ()
- setPtr :: (Prim a, PrimMonad m) => Ptr a -> Int -> a -> m ()
- copyPtrToMutablePrimArray :: forall m a. (PrimMonad m, Prim a) => MutablePrimArray (PrimState m) a -> Int -> Ptr a -> Int -> m ()
- copyPtrToMutableByteArray :: forall m a. (PrimMonad m, Prim a) => MutableByteArray (PrimState m) -> Int -> Ptr a -> Int -> m ()
Types
A value of type
represents a pointer to an object, or an
array of objects, which may be marshalled to or from Haskell values
of type Ptr
aa
.
The type a
will often be an instance of class
Storable
which provides the marshalling operations.
However this is not essential, and you can provide your own operations
to access the pointer. For example you might write small foreign
functions to get or set the fields of a C struct
.
Instances
NFData1 Ptr | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Generic1 (URec (Ptr ()) :: k -> Type) | |
Data a => Data (Ptr a) | Since: base-4.8.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ptr a -> c (Ptr a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ptr a) # dataTypeOf :: Ptr a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Ptr a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ptr a)) # gmapT :: (forall b. Data b => b -> b) -> Ptr a -> Ptr a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ptr a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ptr a -> r # gmapQ :: (forall d. Data d => d -> u) -> Ptr a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ptr a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) # | |
Foldable (UAddr :: TYPE LiftedRep -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => UAddr m -> m # foldMap :: Monoid m => (a -> m) -> UAddr a -> m # foldMap' :: Monoid m => (a -> m) -> UAddr a -> m # foldr :: (a -> b -> b) -> b -> UAddr a -> b # foldr' :: (a -> b -> b) -> b -> UAddr a -> b # foldl :: (b -> a -> b) -> b -> UAddr a -> b # foldl' :: (b -> a -> b) -> b -> UAddr a -> b # foldr1 :: (a -> a -> a) -> UAddr a -> a # foldl1 :: (a -> a -> a) -> UAddr a -> a # elem :: Eq a => a -> UAddr a -> Bool # maximum :: Ord a => UAddr a -> a # minimum :: Ord a => UAddr a -> a # | |
Traversable (UAddr :: Type -> Type) | Since: base-4.9.0.0 |
Storable (Ptr a) | Since: base-2.1 |
Show (Ptr a) | Since: base-2.1 |
NFData (Ptr a) | Since: deepseq-1.4.2.0 |
Defined in Control.DeepSeq | |
Eq (Ptr a) | Since: base-2.1 |
Ord (Ptr a) | Since: base-2.1 |
Prim (Ptr a) Source # | |
Defined in Data.Primitive.Types sizeOfType# :: Proxy (Ptr a) -> Int# Source # sizeOf# :: Ptr a -> Int# Source # alignmentOfType# :: Proxy (Ptr a) -> Int# Source # alignment# :: Ptr a -> Int# Source # indexByteArray# :: ByteArray# -> Int# -> Ptr a Source # readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Ptr a #) Source # writeByteArray# :: MutableByteArray# s -> Int# -> Ptr a -> State# s -> State# s Source # setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Ptr a -> State# s -> State# s Source # indexOffAddr# :: Addr# -> Int# -> Ptr a Source # readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Ptr a #) Source # writeOffAddr# :: Addr# -> Int# -> Ptr a -> State# s -> State# s Source # setOffAddr# :: Addr# -> Int# -> Int# -> Ptr a -> State# s -> State# s Source # | |
Functor (URec (Ptr ()) :: TYPE LiftedRep -> Type) | Since: base-4.9.0.0 |
Generic (URec (Ptr ()) p) | |
Eq (URec (Ptr ()) p) | Since: base-4.9.0.0 |
Ord (URec (Ptr ()) p) | Since: base-4.9.0.0 |
Defined in GHC.Generics compare :: URec (Ptr ()) p -> URec (Ptr ()) p -> Ordering # (<) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool # (<=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool # (>) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool # (>=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool # max :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p # min :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p # | |
data URec (Ptr ()) (p :: k) | Used for marking occurrences of Since: base-4.9.0.0 |
type Rep1 (URec (Ptr ()) :: k -> Type) | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec (Ptr ()) p) | Since: base-4.9.0.0 |
Defined in GHC.Generics |
Address arithmetic
advancePtr :: forall a. Prim a => Ptr a -> Int -> Ptr a Source #
Offset a pointer by the given number of elements.
subtractPtr :: forall a. Prim a => Ptr a -> Ptr a -> Int Source #
Subtract a pointer from another pointer. The result represents
the number of elements of type a
that fit in the contiguous
memory range bounded by these two pointers.
Element access
indexOffPtr :: Prim a => Ptr a -> Int -> a Source #
Read a value from a memory position given by a pointer 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.
readOffPtr :: (Prim a, PrimMonad m) => Ptr a -> Int -> m 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.
writeOffPtr :: (Prim a, PrimMonad m) => Ptr a -> Int -> a -> m () 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.
Block operations
:: forall m a. (PrimMonad m, Prim a) | |
=> Ptr a | destination pointer |
-> Ptr a | source pointer |
-> Int | number of elements |
-> m () |
Copy the given number of elements from the second Ptr
to the first. The
areas may not overlap.
:: forall m a. (PrimMonad m, Prim a) | |
=> Ptr a | destination pointer |
-> Ptr a | source pointer |
-> Int | number of elements |
-> m () |
Copy the given number of elements from the second Ptr
to the first. The
areas may overlap.
setPtr :: (Prim a, PrimMonad m) => Ptr a -> Int -> a -> m () Source #
Fill a memory block with the given value. The length is in
elements of type a
rather than in bytes.
copyPtrToMutablePrimArray Source #
:: forall m a. (PrimMonad m, Prim a) | |
=> MutablePrimArray (PrimState m) a | destination array |
-> Int | destination offset |
-> Ptr a | source pointer |
-> Int | number of elements |
-> m () |
Copy from a pointer to a mutable primitive array.
The offset and length are given in elements of type a
.
This function assumes that the Prim
instance of a
agrees with the Storable
instance.
Note: this function does not do bounds or overlap checking.
copyPtrToMutableByteArray Source #
:: forall m a. (PrimMonad m, Prim a) | |
=> MutableByteArray (PrimState m) | destination array |
-> Int | destination offset given in elements of type |
-> Ptr a | source pointer |
-> Int | number of elements |
-> m () |
Copy from an unmanaged pointer address to a byte array. These must not overlap. The offset and length are given in elements, not in bytes.
Note: this function does not do bounds or overlap checking.