primal-0.3.0.0: Primeval world of Haskell.
Copyright(c) Alexey Kuleshevich 2020
LicenseBSD3
MaintainerAlexey Kuleshevich <alexey@kuleshevi.ch>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Foreign.Prim.StablePtr

Description

 
Synopsis

Documentation

data StablePtr a #

A stable pointer is a reference to a Haskell expression that is guaranteed not to be affected by garbage collection, i.e., it will neither be deallocated nor will the value of the stable pointer itself change during garbage collection (ordinary references may be relocated during garbage collection). Consequently, stable pointers can be passed to foreign code, which can treat it as an opaque reference to a Haskell value.

A value of type StablePtr a is a stable pointer to a Haskell expression of type a.

Constructors

StablePtr (StablePtr# a) 

Instances

Instances details
IArray UArray (StablePtr a) 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i (StablePtr a) -> (i, i) #

numElements :: Ix i => UArray i (StablePtr a) -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, StablePtr a)] -> UArray i (StablePtr a)

unsafeAt :: Ix i => UArray i (StablePtr a) -> Int -> StablePtr a

unsafeReplace :: Ix i => UArray i (StablePtr a) -> [(Int, StablePtr a)] -> UArray i (StablePtr a)

unsafeAccum :: Ix i => (StablePtr a -> e' -> StablePtr a) -> UArray i (StablePtr a) -> [(Int, e')] -> UArray i (StablePtr a)

unsafeAccumArray :: Ix i => (StablePtr a -> e' -> StablePtr a) -> StablePtr a -> (i, i) -> [(Int, e')] -> UArray i (StablePtr a)

Eq (StablePtr a)

Since: base-2.1

Instance details

Defined in GHC.Stable

Methods

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

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

Show (StablePtr a) Source # 
Instance details

Defined in Foreign.Prim.StablePtr

NFData (StablePtr a) Source # 
Instance details

Defined in Foreign.Prim.StablePtr

Methods

rnf :: StablePtr a -> () #

Prim (StablePtr a) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (StablePtr a) Source #

type SizeOf (StablePtr a) :: Nat Source #

type Alignment (StablePtr a) :: Nat Source #

MArray (STUArray s) (StablePtr a) (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i (StablePtr a) -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i (StablePtr a) -> ST s Int

newArray :: Ix i => (i, i) -> StablePtr a -> ST s (STUArray s i (StablePtr a)) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i (StablePtr a)) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i (StablePtr a))

unsafeRead :: Ix i => STUArray s i (StablePtr a) -> Int -> ST s (StablePtr a)

unsafeWrite :: Ix i => STUArray s i (StablePtr a) -> Int -> StablePtr a -> ST s ()

type PrimBase (StablePtr a) Source # 
Instance details

Defined in Data.Prim.Class

type SizeOf (StablePtr a) Source # 
Instance details

Defined in Data.Prim.Class

type SizeOf (StablePtr a) = 8
type Alignment (StablePtr a) Source # 
Instance details

Defined in Data.Prim.Class

type Alignment (StablePtr a) = 8

newStablePtr :: MonadPrim RW m => a -> m (StablePtr a) Source #

Same as newStablePtr, but generalized to MonadPrim

deRefStablePtr :: MonadPrim RW m => StablePtr a -> m a Source #

Same as deRefStablePtr, but generalized to MonadPrim

freeStablePtr :: MonadPrim RW m => StablePtr a -> m () Source #

Same as freeStablePtr, but generalized to MonadPrim

castStablePtrToPtr :: StablePtr a -> Ptr () #

Coerce a stable pointer to an address. No guarantees are made about the resulting value, except that the original stable pointer can be recovered by castPtrToStablePtr. In particular, the address may not refer to an accessible memory location and any attempt to pass it to the member functions of the class Storable leads to undefined behaviour.

castPtrToStablePtr :: Ptr () -> StablePtr a #

The inverse of castStablePtrToPtr, i.e., we have the identity

sp == castPtrToStablePtr (castStablePtrToPtr sp)

for any stable pointer sp on which freeStablePtr has not been executed yet. Moreover, castPtrToStablePtr may only be applied to pointers that have been produced by castStablePtrToPtr.

Orphan instances

Show (StablePtr a) Source # 
Instance details

NFData (StablePtr a) Source # 
Instance details

Methods

rnf :: StablePtr a -> () #