| 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 | 
Data.Primitive.Ptr
Description
Primitive operations on machine addresses
Since: 0.6.4.0
- 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 ()
Types
A value 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
| Generic1 k (URec k (Ptr ())) | |
| Eq (Ptr a) | |
| Data a => Data (Ptr a) | Since: 4.8.0.0 | 
| Ord (Ptr a) | |
| Show (Ptr a) | Since: 2.1 | 
| Storable (Ptr a) | Since: 2.1 | 
| Prim (Ptr a) Source # | |
| Functor (URec * (Ptr ())) | |
| Foldable (URec * (Ptr ())) | |
| Traversable (URec * (Ptr ())) | |
| Eq (URec k (Ptr ()) p) | |
| Ord (URec k (Ptr ()) p) | |
| Generic (URec k (Ptr ()) p) | |
| data URec k (Ptr ()) | Used for marking occurrences of  Since: 4.9.0.0 | 
| type Rep1 k (URec k (Ptr ())) | |
| type Rep (URec k (Ptr ()) p) | |
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
Arguments
| :: (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.
Arguments
| :: (PrimMonad m, Prim a) | |
| => Ptr a | destination address | 
| -> Ptr a | source address | 
| -> 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 #
Arguments
| :: (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 is only available when building with GHC 7.8
 or newer.