interprocess-0.2.1.0: Shared memory and control structures for IPC
Safe HaskellNone
LanguageHaskell2010

Foreign.SharedPtr

Synopsis

Documentation

data SharedPtr a Source #

Special pointer format to pass between memory spaces of processes.

Instances

Instances details
Eq (SharedPtr a) Source # 
Instance details

Defined in Foreign.SharedPtr.C

Methods

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

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

Data a => Data (SharedPtr a) Source # 
Instance details

Defined in Foreign.SharedPtr.C

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SharedPtr a -> c (SharedPtr a) #

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

toConstr :: SharedPtr a -> Constr #

dataTypeOf :: SharedPtr a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord (SharedPtr a) Source # 
Instance details

Defined in Foreign.SharedPtr.C

Show (SharedPtr a) Source # 
Instance details

Defined in Foreign.SharedPtr.C

Generic (SharedPtr a) Source # 
Instance details

Defined in Foreign.SharedPtr.C

Associated Types

type Rep (SharedPtr a) :: Type -> Type #

Methods

from :: SharedPtr a -> Rep (SharedPtr a) x #

to :: Rep (SharedPtr a) x -> SharedPtr a #

Storable (SharedPtr a) Source # 
Instance details

Defined in Foreign.SharedPtr.C

Methods

sizeOf :: SharedPtr a -> Int #

alignment :: SharedPtr a -> Int #

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

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

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

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

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

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

type Rep (SharedPtr a) Source # 
Instance details

Defined in Foreign.SharedPtr.C

type Rep (SharedPtr a) = D1 ('MetaData "SharedPtr" "Foreign.SharedPtr.C" "interprocess-0.2.1.0-30Otn9jPGYlABlDsfE0e5S" 'True) (C1 ('MetaCons "SharedPtr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ptr a))))

toSharedPtr :: Allocator -> Ptr a -> SharedPtr a Source #

Make a portable shared pointer out of a regular pointer. The result can be transfered to another process and re-created using the shared Allocator.

fromSharedPtr :: Allocator -> SharedPtr a -> Ptr a Source #

Reconstruct a regular pointer from a portable shared pointer. Returns NULL if shared pointer or allocator are not valid.

type Allocator = Ptr AllocatorT Source #

Opaque pointer to the allocator type defined in C code.

lookupAllocator :: SOName Allocator -> IO Allocator Source #

Lookup a Allocator by its name. Use this to share one allocator between multiple processes.

destroyAllocator :: Allocator -> IO () Source #

Destroy allocator instance. Note: memory is fully unlinked and released only after the last allocator sharing the memory is destroyed.

realloc :: Allocator -> Ptr a -> Int -> IO (Ptr a) Source #

free :: Allocator -> Ptr a -> IO () Source #