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
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 ()
Types
Constructors
Ptr Addr# |
Instances
Generic1 (URec (Ptr ()) :: k -> Type) | |
Eq (Ptr a) | |
Data a => Data (Ptr a) | |
Defined in Data.Data Methods 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) | |
Ord (Ptr a) | |
Show (Ptr a) | |
Storable (Ptr a) | |
Defined in Foreign.Storable Methods peekElemOff :: Ptr (Ptr a) -> Int -> IO (Ptr a) pokeElemOff :: Ptr (Ptr a) -> Int -> Ptr a -> IO () peekByteOff :: Ptr b -> Int -> IO (Ptr a) pokeByteOff :: Ptr b -> Int -> Ptr a -> IO () | |
Prim (Ptr a) Source # | |
Defined in Data.Primitive.Types Methods sizeOf# :: 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 -> Type) | |
Foldable (URec (Ptr ()) :: Type -> Type) | |
Defined in Data.Foldable Methods fold :: Monoid m => URec (Ptr ()) m -> m foldMap :: Monoid m => (a -> m) -> URec (Ptr ()) a -> m foldMap' :: Monoid m => (a -> m) -> URec (Ptr ()) a -> m foldr :: (a -> b -> b) -> b -> URec (Ptr ()) a -> b foldr' :: (a -> b -> b) -> b -> URec (Ptr ()) a -> b foldl :: (b -> a -> b) -> b -> URec (Ptr ()) a -> b foldl' :: (b -> a -> b) -> b -> URec (Ptr ()) a -> b foldr1 :: (a -> a -> a) -> URec (Ptr ()) a -> a foldl1 :: (a -> a -> a) -> URec (Ptr ()) a -> a toList :: URec (Ptr ()) a -> [a] null :: URec (Ptr ()) a -> Bool length :: URec (Ptr ()) a -> Int elem :: Eq a => a -> URec (Ptr ()) a -> Bool maximum :: Ord a => URec (Ptr ()) a -> a minimum :: Ord a => URec (Ptr ()) a -> a | |
Traversable (URec (Ptr ()) :: Type -> Type) | |
Defined in Data.Traversable | |
Eq (URec (Ptr ()) p) | |
Ord (URec (Ptr ()) p) | |
Defined in GHC.Generics Methods 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 | |
Generic (URec (Ptr ()) p) | |
data URec (Ptr ()) (p :: k) | |
Defined in GHC.Generics | |
type Rep1 (URec (Ptr ()) :: k -> Type) | |
Defined in GHC.Generics type Rep1 (URec (Ptr ()) :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UAddr" 'PrefixI 'True) (S1 ('MetaSel ('Just "uAddr#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UAddr :: k -> Type))) | |
type Rep (URec (Ptr ()) p) | |
Defined in GHC.Generics type Rep (URec (Ptr ()) p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UAddr" 'PrefixI 'True) (S1 ('MetaSel ('Just "uAddr#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UAddr :: Type -> Type))) |
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
:: 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.
Arguments
:: forall m a. (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
:: 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 is only available when building with GHC 7.8
or newer.