Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module includes all the features of Control.Concurrent.MVar, except
that the functions in Data.Primitive.Unlifted.Weak subsume the functionality
of mkWeakMV
and addMVarFinalizer
, so we do not include analogues of those
functions.
Documentation
data UnliftedMVar_ s a unlifted_a Source #
UnliftedMVar (UnliftedMVar# s unlifted_a) |
Instances
unlifted_a ~ Unlifted a => Eq (UnliftedMVar_ s a unlifted_a) Source # | |
Defined in Data.Primitive.Unlifted.MVar.ST (==) :: UnliftedMVar_ s a unlifted_a -> UnliftedMVar_ s a unlifted_a -> Bool # (/=) :: UnliftedMVar_ s a unlifted_a -> UnliftedMVar_ s a unlifted_a -> Bool # | |
unlifted_a ~ Unlifted a => PrimUnlifted (UnliftedMVar_ s a unlifted_a) Source # | |
Defined in Data.Primitive.Unlifted.MVar.ST type Unlifted (UnliftedMVar_ s a unlifted_a) :: UnliftedType Source # toUnlifted# :: UnliftedMVar_ s a unlifted_a -> Unlifted (UnliftedMVar_ s a unlifted_a) Source # fromUnlifted# :: Unlifted (UnliftedMVar_ s a unlifted_a) -> UnliftedMVar_ s a unlifted_a Source # | |
type Unlifted (UnliftedMVar_ s a unlifted_a) Source # | |
Defined in Data.Primitive.Unlifted.MVar.ST |
type UnliftedMVar s a = UnliftedMVar_ s a (Unlifted a) Source #
newUnliftedMVar :: PrimUnlifted a => a -> ST s (UnliftedMVar s a) Source #
newEmptyUnliftedMVar :: ST s (UnliftedMVar s a) Source #
takeUnliftedMVar :: PrimUnlifted a => UnliftedMVar s a -> ST s a Source #
tryTakeUnliftedMVar :: PrimUnlifted a => UnliftedMVar s a -> ST s (Maybe a) Source #
putUnliftedMVar :: PrimUnlifted a => UnliftedMVar s a -> a -> ST s () Source #
tryPutUnliftedMVar :: PrimUnlifted a => UnliftedMVar s a -> a -> ST s Bool Source #
readUnliftedMVar :: PrimUnlifted a => UnliftedMVar s a -> ST s a Source #
tryReadUnliftedMVar :: PrimUnlifted a => UnliftedMVar s a -> ST s (Maybe a) Source #
isEmptyUnliftedMVar :: UnliftedMVar s a -> ST s Bool Source #
swapUnliftedMVar :: PrimUnlifted a => UnliftedMVar RealWorld a -> a -> ST RealWorld a Source #
withUnliftedMVar :: PrimUnlifted a => UnliftedMVar RealWorld a -> (a -> ST RealWorld b) -> ST RealWorld b Source #
withUnliftedMVarMasked :: PrimUnlifted a => UnliftedMVar RealWorld a -> (a -> ST RealWorld b) -> ST RealWorld b Source #
modifyUnliftedMVar :: forall a b. PrimUnlifted a => UnliftedMVar RealWorld a -> (a -> ST RealWorld (a, b)) -> ST RealWorld b Source #
modifyUnliftedMVar_ :: PrimUnlifted a => UnliftedMVar RealWorld a -> (a -> ST RealWorld a) -> ST RealWorld () Source #
modifyUnliftedMVarMasked :: forall a b. PrimUnlifted a => UnliftedMVar RealWorld a -> (a -> ST RealWorld (a, b)) -> ST RealWorld b Source #
modifyUnliftedMVarMasked_ :: PrimUnlifted a => UnliftedMVar RealWorld a -> (a -> ST RealWorld a) -> ST RealWorld () Source #