primitive-unlifted-2.1.0.0: Primitive GHC types with unlifted types inside
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Primitive.Unlifted.Weak

Description

System.Mem.Weak provides weak references from lifted keys to lifted values. Data.IORef, Control.Concurrent.MVar, and Control.Concurrent.STM.TVar provide operations for producing weak references from unlifted keys of specific types to lifted values.

This module fills in the gaps. It offers a type (UnliftedWeak_) for weak references from (lifted or unlifted) keys to unlifted values. It also provides fully general operations for producing weak references from unlifted keys to lifted values.

Usage note: Weak references from lifted types can be fragile in the face of GHC's unboxing optimizations. Weak references from unlifted types are much more reliable. Weak references to boxed types that wrap unlifted types tend to be inefficient, because they keep not only the actual value alive but also its box. Unless it's necessary to create a Weak reference to an unevaluated thunk, it's generally best to create an UnliftedWeak_ reference to the unlifted value instead.

Synopsis

Documentation

data UnliftedWeak_ a (unlifted_a :: UnliftedType) Source #

A weak pointer from a key (which may be lifted or unlifted) to an unlifted value. In UnliftedWeak_ a unlifted_a, it is generally expected that unlifted_a ~ Unlifted a, but enforcing that here would lead to unfortunate type roles. See System.Mem.Weak for detailed information about weak references, including the notes at the end of that module.

Constructors

UnliftedWeak (UnliftedWeak# unlifted_a) 

Instances

Instances details
unlifted_a ~ Unlifted a => PrimUnlifted (UnliftedWeak_ a unlifted_a) Source # 
Instance details

Defined in Data.Primitive.Unlifted.Weak.IO

Associated Types

type Unlifted (UnliftedWeak_ a unlifted_a) :: UnliftedType Source #

Methods

toUnlifted# :: UnliftedWeak_ a unlifted_a -> Unlifted (UnliftedWeak_ a unlifted_a) Source #

fromUnlifted# :: Unlifted (UnliftedWeak_ a unlifted_a) -> UnliftedWeak_ a unlifted_a Source #

type Unlifted (UnliftedWeak_ a unlifted_a) Source # 
Instance details

Defined in Data.Primitive.Unlifted.Weak.IO

type Unlifted (UnliftedWeak_ a unlifted_a) = UnliftedWeak# unlifted_a

type UnliftedWeak a = UnliftedWeak_ a (Unlifted a) Source #

A type synonym for an UnliftedWeak_ containing lifted values of a particular type. As a general rule, this type synonym should not be used in class instances—use UnliftedWeak_ with an equality constraint instead. It also should not be used when defining newtypes or datatypes, unless those will have restrictive type roles regardless—use UnliftedWeak_ instead.

mkWeakFromUnliftedToUnlifted :: (PrimUnlifted k, PrimUnlifted v, PrimMonad m, PrimState m ~ RealWorld) => k -> v -> Maybe (IO ()) -> m (UnliftedWeak v) Source #

Establishes a weak pointer from an unlifted value k to an unlifted value v with an optional finalizer.

mkWeakToUnlifted :: (PrimUnlifted v, PrimMonad m, PrimState m ~ RealWorld) => k -> v -> Maybe (IO ()) -> m (UnliftedWeak v) Source #

Establishes a weak pointer from a lifted value k to an unlifted value v with an optional finalizer.

mkWeakFromUnlifted :: (PrimUnlifted k, PrimMonad m, PrimState m ~ RealWorld) => k -> v -> Maybe (IO ()) -> m (Weak v) Source #

Establishes a weak pointer from an unlifted value k to a lifted value v with an optional finalizer.

deRefUnliftedWeak :: (PrimUnlifted v, PrimMonad m, PrimState m ~ RealWorld) => UnliftedWeak v -> m (Maybe v) Source #

Derefences a weak pointer. If the key is still alive and the pointer has not been finalized with finalizeUnlifted, then Just v is returned, where v is the value in the weak pointer. Otherwise, Nothing is returned.

finalizeUnlifted :: (PrimMonad m, PrimState m ~ RealWorld) => UnliftedWeak v -> m () Source #

Immediately finalize a weak pointer.

mkUnliftedWeakPtr :: (PrimUnlifted k, PrimMonad m, PrimState m ~ RealWorld) => k -> Maybe (IO ()) -> m (UnliftedWeak k) Source #

Make a weak pointer from an unlifted value to itself.

Note: This should generally be preferred to Data.IORef.mkWeakIORef and similar for making weak pointers to IORefs, MVars, TVars, etc, as the values are stored more directly and compactly this way.

addFinalizerUnlifted :: (PrimUnlifted k, PrimMonad m, PrimState m ~ RealWorld) => k -> IO () -> m () Source #

A specialised version of mkUnliftedWeakPtr, where the UnliftedWeak object returned is simply thrown away (however the finalizer will be remembered by the garbage collector, and will still be run when the key becomes unreachable).

addCFinalizerToUnliftedWeak1 :: (PrimMonad m, PrimState m ~ RealWorld) => FunPtr (a -> IO ()) -> Ptr a -> UnliftedWeak b -> m Bool Source #

Add a finalizer written in C to an UnliftedWeak_. Takes a pointer to a C function of one argument and an argument to call it with. Returns True on success, or False if the UnliftedWeak_ is already dead.

addCFinalizerToUnliftedWeak2 :: (PrimMonad m, PrimState m ~ RealWorld) => FunPtr (a -> b -> IO ()) -> Ptr a -> Ptr b -> UnliftedWeak c -> m Bool Source #

Add a finalizer written in C to an UnliftedWeak_. Takes a pointer to a C function of two arguments and arguments to call it with. Returns True on success, or False if the UnliftedWeak_ is already dead.

touchUnlifted :: (PrimUnlifted a, PrimMonad m, PrimState m ~ RealWorld) => a -> m () Source #

Ensure that a value is considered live by the garbage collector at a particular point in the program. Typically, this is used to prevent foreign resources from being finalized while they are still being used.

Considerable care is required when using this operation (see GHC ticket 14346). In particular, if GHC sees that an action m will never complete normally, then it will simplify m >> touchUnlifted a to m, allowing a to die prematurely. For now, functions using touchUnlifted may require careful use of NOINLINE to work around this; in the future, GHC will probably provide a more robust operation for keeping values alive.