Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
A version of Data.Primitive.Unlifted.Weak specialized to the IO
type.
Synopsis
- data UnliftedWeak_ a (unlifted_a :: UnliftedType) = UnliftedWeak (UnliftedWeak# unlifted_a)
- type UnliftedWeak a = UnliftedWeak_ a (Unlifted a)
- mkWeakFromUnliftedToUnlifted :: (PrimUnlifted k, PrimUnlifted v) => k -> v -> Maybe (IO ()) -> IO (UnliftedWeak v)
- mkWeakToUnlifted :: PrimUnlifted v => k -> v -> Maybe (IO ()) -> IO (UnliftedWeak v)
- mkWeakFromUnlifted :: PrimUnlifted k => k -> v -> Maybe (IO ()) -> IO (Weak v)
- deRefUnliftedWeak :: PrimUnlifted v => UnliftedWeak v -> IO (Maybe v)
- finalizeUnlifted :: UnliftedWeak v -> IO ()
- mkUnliftedWeakPtr :: PrimUnlifted k => k -> Maybe (IO ()) -> IO (UnliftedWeak k)
- addFinalizerUnlifted :: PrimUnlifted k => k -> IO () -> IO ()
- addCFinalizerToUnliftedWeak1 :: FunPtr (a -> IO ()) -> Ptr a -> UnliftedWeak b -> IO Bool
- addCFinalizerToUnliftedWeak2 :: FunPtr (a -> b -> IO ()) -> Ptr a -> Ptr b -> UnliftedWeak c -> IO Bool
- touchUnlifted :: PrimUnlifted a => a -> IO ()
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 ~
, 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.Unlifted
a
UnliftedWeak (UnliftedWeak# unlifted_a) |
Instances
unlifted_a ~ Unlifted a => PrimUnlifted (UnliftedWeak_ a unlifted_a) Source # | |
Defined in Data.Primitive.Unlifted.Weak.IO type Unlifted (UnliftedWeak_ a unlifted_a) :: UnliftedType Source # 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 # | |
Defined in Data.Primitive.Unlifted.Weak.IO |
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) => k -> v -> Maybe (IO ()) -> IO (UnliftedWeak v) Source #
Establishes a weak pointer from an unlifted value k
to an
unlifted value v
with an optional finalizer.
mkWeakToUnlifted :: PrimUnlifted v => k -> v -> Maybe (IO ()) -> IO (UnliftedWeak v) Source #
Establishes a weak pointer from a lifted value k
to an
unlifted value v
with an optional finalizer.
mkWeakFromUnlifted :: PrimUnlifted k => k -> v -> Maybe (IO ()) -> IO (Weak v) Source #
Establishes a weak pointer from an unlifted value k
to a
lifted value v
with an optional finalizer.
deRefUnliftedWeak :: PrimUnlifted v => UnliftedWeak v -> IO (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 :: UnliftedWeak v -> IO () Source #
Immediately finalize a weak pointer.
mkUnliftedWeakPtr :: PrimUnlifted k => k -> Maybe (IO ()) -> IO (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 IORef
s, MVar
s, TVar
s,
etc, as the values are stored more directly and compactly this way.
addFinalizerUnlifted :: PrimUnlifted k => k -> IO () -> IO () 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 :: FunPtr (a -> IO ()) -> Ptr a -> UnliftedWeak b -> IO 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 :: FunPtr (a -> b -> IO ()) -> Ptr a -> Ptr b -> UnliftedWeak c -> IO 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 => a -> IO () 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.