GHC.Ptr

Copyright (c) The FFI Task Force 2000-2002
License see libraries/base/LICENSE
Maintainer [email protected]
Stability internal
Portability non-portable (GHC Extensions)
Safe Haskell Unsafe
Language Haskell2010

Contents

Description

The Ptr and FunPtr types and operations.

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.

Constructors

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

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

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

Methods

from1 :: forall (a :: k0). URec (Ptr ()) a -> Rep1 (URec (Ptr ())) a Source

to1 :: forall (a :: k0). Rep1 (URec (Ptr ())) a -> URec (Ptr ()) a Source

Eq (Ptr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Methods

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

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

Data a => Data (Ptr a)

Since: base-4.8.0.0

Instance details

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) 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

Ord (Ptr a)

Since: base-2.1

Instance details

Defined in GHC.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

Show (Ptr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Methods

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

show :: Ptr a -> String Source

showList :: [Ptr a] -> ShowS Source

Foldable (UAddr :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in 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 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.1

Instance details

Defined in 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

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

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

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

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

Eq (URec (Ptr ()) p)

Since: base-4.9.0.0

Instance details

Defined in GHC.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.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

Generic (URec (Ptr ()) p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec (Ptr ()) p) :: Type -> Type Source

Methods

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

to :: Rep (URec (Ptr ()) p) x -> 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.Generics

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

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)
Instance details

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)))

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

Constructors

FunPtr Addr#
Instances
Instances details
Eq (FunPtr a)
Instance details

Defined in GHC.Ptr

Methods

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

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

Ord (FunPtr a)
Instance details

Defined in GHC.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

Show (FunPtr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Methods

showsPrec :: Int -> FunPtr a -> ShowS Source

show :: FunPtr a -> String Source

showList :: [FunPtr a] -> ShowS Source

Storable (FunPtr a)

Since: base-2.1

Instance details

Defined in 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

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)

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.

Unsafe functions

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.

© The University of Glasgow and others
Licensed under a BSD-style license (see top of the page).
https://downloads.haskell.org/~ghc/8.10.2/docs/html/libraries/base-4.14.1.0/GHC-Ptr.html