base-4.20.0.0: Core data structures and operations
Copyright(c) The FFI task force 2001
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerffi@haskell.org
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Foreign.Ptr

Description

This module provides typed pointers to foreign data. It is part of the Foreign Function Interface (FFI) and will normally be imported via the Foreign module.

Synopsis

Data pointers

data Ptr a Source #

A value of type Ptr a represents a pointer to an object, or an array of objects, which may be marshalled to or from Haskell values of type a.

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

Instances details
Generic1 (URec (Ptr ()) :: k -> Type) 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 (URec (Ptr ()) :: k -> Type)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (URec (Ptr ()) :: k -> Type) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UAddr" 'PrefixI 'True) (S1 ('MetaSel ('Just "uAddr#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UAddr :: k -> Type)))

Methods

from1 :: forall (a :: k). URec (Ptr ()) a -> Rep1 (URec (Ptr ()) :: k -> Type) a Source #

to1 :: forall (a :: k). Rep1 (URec (Ptr ()) :: k -> Type) a -> URec (Ptr ()) a Source #

Data a => Data (Ptr a)

@since base-4.8.0.0

Instance details

Defined in GHC.Internal.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) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ptr a) Source #

toConstr :: Ptr a -> Constr Source #

dataTypeOf :: Ptr a -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Ptr a)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ptr a)) Source #

gmapT :: (forall b. Data b => b -> b) -> Ptr a -> Ptr a Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ptr a -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ptr a -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Ptr a -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Ptr a -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) Source #

Foldable (UAddr :: Type -> Type)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Foldable

Methods

fold :: Monoid m => UAddr m -> m Source #

foldMap :: Monoid m => (a -> m) -> UAddr a -> m Source #

foldMap' :: Monoid m => (a -> m) -> UAddr a -> m Source #

foldr :: (a -> b -> b) -> b -> UAddr a -> b Source #

foldr' :: (a -> b -> b) -> b -> UAddr a -> b Source #

foldl :: (b -> a -> b) -> b -> UAddr a -> b Source #

foldl' :: (b -> a -> b) -> b -> UAddr a -> b Source #

foldr1 :: (a -> a -> a) -> UAddr a -> a Source #

foldl1 :: (a -> a -> a) -> UAddr a -> a Source #

toList :: UAddr a -> [a] Source #

null :: UAddr a -> Bool Source #

length :: UAddr a -> Int Source #

elem :: Eq a => a -> UAddr a -> Bool Source #

maximum :: Ord a => UAddr a -> a Source #

minimum :: Ord a => UAddr a -> a Source #

sum :: Num a => UAddr a -> a Source #

product :: Num a => UAddr a -> a Source #

Traversable (UAddr :: Type -> Type)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UAddr a -> f (UAddr b) Source #

sequenceA :: Applicative f => UAddr (f a) -> f (UAddr a) Source #

mapM :: Monad m => (a -> m b) -> UAddr a -> m (UAddr b) Source #

sequence :: Monad m => UAddr (m a) -> m (UAddr a) Source #

Storable (Ptr a)

@since base-2.01

Instance details

Defined in GHC.Internal.Foreign.Storable

Methods

sizeOf :: Ptr a -> Int Source #

alignment :: Ptr a -> Int Source #

peekElemOff :: Ptr (Ptr a) -> Int -> IO (Ptr a) Source #

pokeElemOff :: Ptr (Ptr a) -> Int -> Ptr a -> IO () Source #

peekByteOff :: Ptr b -> Int -> IO (Ptr a) Source #

pokeByteOff :: Ptr b -> Int -> Ptr a -> IO () Source #

peek :: Ptr (Ptr a) -> IO (Ptr a) Source #

poke :: Ptr (Ptr a) -> Ptr a -> IO () Source #

Show (Ptr a)

@since base-2.01

Instance details

Defined in GHC.Internal.Ptr

Methods

showsPrec :: Int -> Ptr a -> ShowS Source #

show :: Ptr a -> String Source #

showList :: [Ptr a] -> ShowS Source #

Eq (Ptr a)

@since base-2.01

Instance details

Defined in GHC.Internal.Ptr

Methods

(==) :: Ptr a -> Ptr a -> Bool Source #

(/=) :: Ptr a -> Ptr a -> Bool Source #

Ord (Ptr a)

@since base-2.01

Instance details

Defined in GHC.Internal.Ptr

Methods

compare :: Ptr a -> Ptr a -> Ordering Source #

(<) :: Ptr a -> Ptr a -> Bool Source #

(<=) :: Ptr a -> Ptr a -> Bool Source #

(>) :: Ptr a -> Ptr a -> Bool Source #

(>=) :: Ptr a -> Ptr a -> Bool Source #

max :: Ptr a -> Ptr a -> Ptr a Source #

min :: Ptr a -> Ptr a -> Ptr a Source #

Functor (URec (Ptr ()) :: Type -> Type)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

fmap :: (a -> b) -> URec (Ptr ()) a -> URec (Ptr ()) b Source #

(<$) :: a -> URec (Ptr ()) b -> URec (Ptr ()) a Source #

Generic (URec (Ptr ()) p) 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep (URec (Ptr ()) p)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep (URec (Ptr ()) p) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UAddr" 'PrefixI 'True) (S1 ('MetaSel ('Just "uAddr#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UAddr :: Type -> Type)))

Methods

from :: URec (Ptr ()) p -> Rep (URec (Ptr ()) p) x Source #

to :: Rep (URec (Ptr ()) p) x -> URec (Ptr ()) p Source #

Eq (URec (Ptr ()) p)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

(==) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source #

(/=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source #

Ord (URec (Ptr ()) p)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

compare :: URec (Ptr ()) p -> URec (Ptr ()) p -> Ordering Source #

(<) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source #

(<=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source #

(>) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source #

(>=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source #

max :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p Source #

min :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p Source #

data URec (Ptr ()) (p :: k)

Used for marking occurrences of Addr#

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

data URec (Ptr ()) (p :: k) = UAddr {}
type Rep1 (URec (Ptr ()) :: k -> Type)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (URec (Ptr ()) :: k -> Type) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UAddr" 'PrefixI 'True) (S1 ('MetaSel ('Just "uAddr#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UAddr :: k -> Type)))
type Rep (URec (Ptr ()) p)

@since base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep (URec (Ptr ()) p) = D1 ('MetaData "URec" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons "UAddr" 'PrefixI 'True) (S1 ('MetaSel ('Just "uAddr#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UAddr :: Type -> Type)))

nullPtr :: Ptr a Source #

The constant nullPtr contains a distinguished value of Ptr that is not associated with a valid memory location.

castPtr :: Ptr a -> Ptr b Source #

The castPtr function casts a pointer from one type to another.

plusPtr :: Ptr a -> Int -> Ptr b Source #

Advances the given address by the given offset in bytes.

alignPtr :: Ptr a -> Int -> Ptr a Source #

Given an arbitrary address and an alignment constraint, alignPtr yields the next higher address that fulfills the alignment constraint. An alignment constraint x is fulfilled by any address divisible by x. This operation is idempotent.

minusPtr :: Ptr a -> Ptr b -> Int Source #

Computes the offset required to get from the second to the first argument. We have

p2 == p1 `plusPtr` (p2 `minusPtr` p1)

Function pointers

data FunPtr a Source #

A value of type FunPtr a is a pointer to a function callable from foreign code. The type a will normally be a foreign type, a function type with zero or more arguments where

A value of type FunPtr a may be a pointer to a foreign function, either returned by another foreign function or imported with a a static address import like

foreign import ccall "stdlib.h &free"
  p_free :: FunPtr (Ptr a -> IO ())

or a pointer to a Haskell function created using a wrapper stub declared to produce a FunPtr of the correct type. For example:

type Compare = Int -> Int -> Bool
foreign import ccall "wrapper"
  mkCompare :: Compare -> IO (FunPtr Compare)

Calls to wrapper stubs like mkCompare allocate storage, which should be released with freeHaskellFunPtr when no longer required.

To convert FunPtr values to corresponding Haskell functions, one can define a dynamic stub for the specific foreign type, e.g.

type IntFunction = CInt -> IO ()
foreign import ccall "dynamic"
  mkFun :: FunPtr IntFunction -> IntFunction

Instances

Instances details
Storable (FunPtr a)

@since base-2.01

Instance details

Defined in GHC.Internal.Foreign.Storable

Methods

sizeOf :: FunPtr a -> Int Source #

alignment :: FunPtr a -> Int Source #

peekElemOff :: Ptr (FunPtr a) -> Int -> IO (FunPtr a) Source #

pokeElemOff :: Ptr (FunPtr a) -> Int -> FunPtr a -> IO () Source #

peekByteOff :: Ptr b -> Int -> IO (FunPtr a) Source #

pokeByteOff :: Ptr b -> Int -> FunPtr a -> IO () Source #

peek :: Ptr (FunPtr a) -> IO (FunPtr a) Source #

poke :: Ptr (FunPtr a) -> FunPtr a -> IO () Source #

Show (FunPtr a)

@since base-2.01

Instance details

Defined in GHC.Internal.Ptr

Eq (FunPtr a) 
Instance details

Defined in GHC.Internal.Ptr

Methods

(==) :: FunPtr a -> FunPtr a -> Bool Source #

(/=) :: FunPtr a -> FunPtr a -> Bool Source #

Ord (FunPtr a) 
Instance details

Defined in GHC.Internal.Ptr

Methods

compare :: FunPtr a -> FunPtr a -> Ordering Source #

(<) :: FunPtr a -> FunPtr a -> Bool Source #

(<=) :: FunPtr a -> FunPtr a -> Bool Source #

(>) :: FunPtr a -> FunPtr a -> Bool Source #

(>=) :: FunPtr a -> FunPtr a -> Bool Source #

max :: FunPtr a -> FunPtr a -> FunPtr a Source #

min :: FunPtr a -> FunPtr a -> FunPtr a Source #

nullFunPtr :: FunPtr a Source #

The constant nullFunPtr contains a distinguished value of FunPtr that is not associated with a valid memory location.

castFunPtr :: FunPtr a -> FunPtr b Source #

Casts a FunPtr to a FunPtr of a different type.

castFunPtrToPtr :: FunPtr a -> Ptr b Source #

Casts a FunPtr to a Ptr.

Note: this is valid only on architectures where data and function pointers range over the same set of addresses, and should only be used for bindings to external libraries whose interface already relies on this assumption.

castPtrToFunPtr :: Ptr a -> FunPtr b Source #

Casts a Ptr to a FunPtr.

Note: this is valid only on architectures where data and function pointers range over the same set of addresses, and should only be used for bindings to external libraries whose interface already relies on this assumption.

freeHaskellFunPtr :: FunPtr a -> IO () Source #

Release the storage associated with the given FunPtr, which must have been obtained from a wrapper stub. This should be called whenever the return value from a foreign import wrapper function is no longer required; otherwise, the storage it uses will leak.

Integral types with lossless conversion to and from pointers

newtype IntPtr Source #

A signed integral type that can be losslessly converted to and from Ptr. This type is also compatible with the C99 type intptr_t, and can be marshalled to and from that type safely.

Constructors

IntPtr Int 

Instances

Instances details
Bits IntPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

FiniteBits IntPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Data IntPtr

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IntPtr -> c IntPtr Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IntPtr Source #

toConstr :: IntPtr -> Constr Source #

dataTypeOf :: IntPtr -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IntPtr) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IntPtr) Source #

gmapT :: (forall b. Data b => b -> b) -> IntPtr -> IntPtr Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IntPtr -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IntPtr -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> IntPtr -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IntPtr -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IntPtr -> m IntPtr Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IntPtr -> m IntPtr Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IntPtr -> m IntPtr Source #

Bounded IntPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Enum IntPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Storable IntPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Ix IntPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Num IntPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Read IntPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Integral IntPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Real IntPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Show IntPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Eq IntPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Ord IntPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

ptrToIntPtr :: Ptr a -> IntPtr Source #

casts a Ptr to an IntPtr

intPtrToPtr :: IntPtr -> Ptr a Source #

casts an IntPtr to a Ptr

newtype WordPtr Source #

An unsigned integral type that can be losslessly converted to and from Ptr. This type is also compatible with the C99 type uintptr_t, and can be marshalled to and from that type safely.

Constructors

WordPtr Word 

Instances

Instances details
Bits WordPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

FiniteBits WordPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Data WordPtr

@since base-4.11.0.0

Instance details

Defined in GHC.Internal.Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WordPtr -> c WordPtr Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WordPtr Source #

toConstr :: WordPtr -> Constr Source #

dataTypeOf :: WordPtr -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c WordPtr) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WordPtr) Source #

gmapT :: (forall b. Data b => b -> b) -> WordPtr -> WordPtr Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WordPtr -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WordPtr -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> WordPtr -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WordPtr -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WordPtr -> m WordPtr Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WordPtr -> m WordPtr Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WordPtr -> m WordPtr Source #

Bounded WordPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Enum WordPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Storable WordPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Ix WordPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Num WordPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Read WordPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Integral WordPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Real WordPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Show WordPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Eq WordPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Ord WordPtr 
Instance details

Defined in GHC.Internal.Foreign.Ptr

ptrToWordPtr :: Ptr a -> WordPtr Source #

casts a Ptr to a WordPtr

wordPtrToPtr :: WordPtr -> Ptr a Source #

casts a WordPtr to a Ptr