haskus-binary-1.5: Haskus binary format manipulation

Safe HaskellNone
LanguageHaskell2010

Haskus.Memory.Ptr

Contents

Description

Pointers

A pointer is a number: an offset into a memory. This is the `Addr#` type.

We want the type-system to help us avoid errors when we use pointers, hence we decorate them with phantom types describing the memory layout at the pointed address. This is the `Ptr a` data type that wraps an `Addr#`.

We often want to associate finalizers to pointers, i.e., actions to be run when the pointer is collected by the GC. These actions take the pointer as a parameter. This is the `ForeignPtr a` data type.

A `ForeignPtr a` cannot be manipulated like a number because somehow we need to keep the pointer value that will be passed to the finalizers. Moreover we don't want finalizers to be executed too early, so we can't easily create a new ForeignPtr from another (it would require a way to disable the existing finalizers of a ForeignPtr, which would in turn open a whole can of worms). Hence we use the `FinalizedPtr a` pointer type, which has an additional offset field.

Synopsis

Documentation

data Pointer (mut :: Mutability) (fin :: Finalization) where Source #

A pointer in memory

Constructors

PtrI :: !RawPtr -> PtrI 
PtrM :: !RawPtr -> PtrM 
PtrIF :: !FinPtr -> !Int -> PtrIF 
PtrMF :: !FinPtr -> !Int -> PtrMF 
Instances
Show (Pointer mut fin) Source # 
Instance details

Defined in Haskus.Memory.Ptr

Methods

showsPrec :: Int -> Pointer mut fin -> ShowS #

show :: Pointer mut fin -> String #

showList :: [Pointer mut fin] -> ShowS #

newtype AnyPointer Source #

Wrapper containing any kind of buffer

Constructors

AnyPointer (forall mut fin. Pointer mut fin) 

type RawPtr = Ptr () Source #

isNullPtr :: Pointer mut fin -> Bool Source #

Test if a pointer is Null

nullPtrI :: PtrI Source #

Null pointer

nullPtrM :: PtrM Source #

Null pointer

indexPtr :: Pointer mut fin -> Int -> Pointer mut fin Source #

Index a pointer

distancePtr :: Pointer mut0 fin0 -> Pointer mut1 fin1 -> Int Source #

Distance between two pointers

withPtr :: MonadInIO m => Pointer mut fin -> (Pointer mut NotFinalized -> m b) -> m b Source #

Use a pointer (finalized or not) as a non finalized pointer

withFinalizedPtr :: MonadInIO m => Pointer mut Finalized -> (Pointer mut NotFinalized -> m b) -> m b Source #

Use a finalized pointer as a non finalized pointer

allocFinalizedPtr :: MonadIO m => Word -> m PtrMF Source #

Alloc mutable finalized memory

allocPtr :: MonadIO m => Word -> m PtrM Source #

Alloc mutable non-finalized memory

freePtr :: MonadIO m => Pointer mut NotFinalized -> m () Source #

Free a non-finalized memory

Function pointer

data FunPtr a #

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
Eq (FunPtr a) 
Instance details

Defined in GHC.Ptr

Methods

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

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

Ord (FunPtr a) 
Instance details

Defined in GHC.Ptr

Methods

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

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

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

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

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

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

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

Show (FunPtr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Methods

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

show :: FunPtr a -> String #

showList :: [FunPtr a] -> ShowS #

Storable (FunPtr a)

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: FunPtr a -> Int #

alignment :: FunPtr a -> Int #

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

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

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

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

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

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

nullFunPtr :: FunPtr a #

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

castPtrToFunPtr :: Ptr a -> FunPtr b #

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.

castFunPtrToPtr :: FunPtr a -> Ptr b #

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.

Pointer as a Word

data WordPtr #

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.

Instances
Bounded WordPtr 
Instance details

Defined in Foreign.Ptr

Enum WordPtr 
Instance details

Defined in Foreign.Ptr

Eq WordPtr 
Instance details

Defined in Foreign.Ptr

Methods

(==) :: WordPtr -> WordPtr -> Bool #

(/=) :: WordPtr -> WordPtr -> Bool #

Integral WordPtr 
Instance details

Defined in Foreign.Ptr

Data WordPtr

Since: base-4.11.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) -> WordPtr -> c WordPtr #

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

toConstr :: WordPtr -> Constr #

dataTypeOf :: WordPtr -> DataType #

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

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

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

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

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

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

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

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

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

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

Num WordPtr 
Instance details

Defined in Foreign.Ptr

Ord WordPtr 
Instance details

Defined in Foreign.Ptr

Read WordPtr 
Instance details

Defined in Foreign.Ptr

Real WordPtr 
Instance details

Defined in Foreign.Ptr

Show WordPtr 
Instance details

Defined in Foreign.Ptr

Storable WordPtr 
Instance details

Defined in Foreign.Ptr

Bits WordPtr 
Instance details

Defined in Foreign.Ptr

FiniteBits WordPtr 
Instance details

Defined in Foreign.Ptr

Storable WordPtr Source # 
Instance details

Defined in Haskus.Binary.Storable

wordPtrToPtr :: WordPtr -> Ptr a #

casts a WordPtr to a Ptr

ptrToWordPtr :: Ptr a -> WordPtr #

casts a Ptr to a WordPtr