| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell98 |
Data.MRef.Types
Description
This module defines the "MRef" abstraction, which is a set of
type-classes for things that behave like MVars.
See the documentation there for more info.
This interface may be subject to future expansion. Presently, rather
than providing something like tryTakeMVar,
instances for "ReadRef sr m (Maybe a)" are
provided, giving readReference the same type
tryTakeMRef would have if it existed. There is currently nothing like
tryPutMVar, though. Perhaps there should be.
Or, perhaps this is the sort of thing the weird (to me) signature of
atomicModifyIORef is for, and an argument for a similar
signature for modifyStateRef or the addition of
a new atomicModifyStateRef function.
I would like to resolve these questions in version 0.3 of this package.
Documentation
data MRef (m :: Type -> Type) a where Source #
Constructors
| MRef :: forall sr (m :: Type -> Type) a. (TakeMRef sr m a, PutMRef sr m a) => !sr -> MRef m a |
class Monad m => NewMRef sr (m :: Type -> Type) a | sr -> a where Source #
Methods
newMReference :: a -> m sr Source #
See newMVar
newEmptyMReference :: m sr Source #
See newEmptyMVar
Instances
| NewMRef (TVar (Maybe a)) STM a Source # | |
Defined in Data.MRef.Instances.STM | |
| NewMRef (TVar (Maybe a)) IO a Source # | |
Defined in Data.MRef.Instances.STM | |
| MonadIO m => NewMRef (MVar a) m a Source # | |
Defined in Data.MRef.Instances | |
| NewMRef (TMVar a) STM a Source # | |
Defined in Data.MRef.Instances.STM | |
| NewMRef (TMVar a) IO a Source # | |
Defined in Data.MRef.Instances.STM | |
| NewMRef (MRef STM a) IO a Source # | |
Defined in Data.MRef.Instances.STM | |
class Monad m => TakeMRef sr (m :: Type -> Type) a | sr -> a where Source #
Instances
| TakeMRef (TVar (Maybe a)) STM a Source # | |
Defined in Data.MRef.Instances.STM | |
| TakeMRef (TVar (Maybe a)) IO a Source # | |
Defined in Data.MRef.Instances.STM | |
| MonadIO m => TakeMRef (MVar a) m a Source # | |
Defined in Data.MRef.Instances Methods takeMReference :: MVar a -> m a Source # | |
| TakeMRef (TMVar a) STM a Source # | |
Defined in Data.MRef.Instances.STM Methods takeMReference :: TMVar a -> STM a Source # | |
| TakeMRef (TMVar a) IO a Source # | |
Defined in Data.MRef.Instances.STM Methods takeMReference :: TMVar a -> IO a Source # | |
| TakeMRef (MRef STM a) IO a Source # | |
Defined in Data.MRef.Instances.STM | |
class Monad m => PutMRef sr (m :: Type -> Type) a | sr -> a where Source #
Instances
| PutMRef (TVar (Maybe a)) STM a Source # | |
Defined in Data.MRef.Instances.STM | |
| PutMRef (TVar (Maybe a)) IO a Source # | |
Defined in Data.MRef.Instances.STM | |
| MonadIO m => PutMRef (MVar a) m a Source # | |
Defined in Data.MRef.Instances Methods putMReference :: MVar a -> a -> m () Source # | |
| PutMRef (TMVar a) STM a Source # | |
Defined in Data.MRef.Instances.STM Methods putMReference :: TMVar a -> a -> STM () Source # | |
| PutMRef (TMVar a) IO a Source # | |
Defined in Data.MRef.Instances.STM Methods putMReference :: TMVar a -> a -> IO () Source # | |
| PutMRef (MRef STM a) IO a Source # | |
Defined in Data.MRef.Instances.STM | |