stateref-0.3: Abstraction for things that work like IORef.

Data.StateRef.Instances

Description

This module exports no new symbols of its own. It defines several basic class instances for creating, reading, and writing standard reference types, and re-exports the types for which it defines instances.

TODO: add millions of SPECIALIZE INSTANCE pragmas, for IO monad at a minimum.

Synopsis

Documentation

data IORef a

A mutable variable in the IO monad

Instances

Eq (IORef a) 
MonadIO m => NewRef (IORef a) m a 
MonadIO m => ModifyRef (IORef a) m a 
MonadIO m => ReadRef (IORef a) m a 
MonadIO m => WriteRef (IORef a) m a 

data MVar a

An MVar (pronounced "em-var") is a synchronising variable, used for communication between concurrent threads. It can be thought of as a a box, which may be empty or full.

Instances

Eq (MVar a) 
MonadIO m => PutMRef (MVar a) m a 
MonadIO m => TakeMRef (MVar a) m a 
MonadIO m => NewMRef (MVar a) m a 
MonadIO m => NewRef (MVar a) m (Maybe a) 

class Monad m => MonadIO m where

Monads in which IO computations may be embedded. Any monad built by applying a sequence of monad transformers to the IO monad will be an instance of this class.

Instances should satisfy the following laws, which state that liftIO is a transformer of monads:

Methods

liftIO :: IO a -> m a

Lift a computation from the IO monad.

Instances

data STRef s a

a value of type STRef s a is a mutable variable in state thread s, containing a value of type a

Instances

Eq (STRef s a) 
NewRef (STRef RealWorld a) IO a 
ModifyRef (STRef RealWorld a) IO a 
ReadRef (STRef RealWorld a) IO a 
WriteRef (STRef RealWorld a) IO a 
NewRef (STRef s a) (ST s) a 
NewRef (STRef s a) (ST s) a 
ModifyRef (STRef s a) (ST s) a 
ModifyRef (STRef s a) (ST s) a 
ReadRef (STRef s a) (ST s) a 
ReadRef (STRef s a) (ST s) a 
WriteRef (STRef s a) (ST s) a 
WriteRef (STRef s a) (ST s) a 

data ST s a

The strict state-transformer monad. A computation of type ST s a transforms an internal state indexed by s, and returns a value of type a. The s parameter is either

  • an uninstantiated type variable (inside invocations of runST), or
  • RealWorld (inside invocations of Control.Monad.ST.stToIO).

It serves to keep the internal states of different invocations of runST separate from each other and from invocations of Control.Monad.ST.stToIO.

The >>= and >> operations are strict in the state (though not in values stored in the state). For example,

runST (writeSTRef _|_ v >>= f) = _|_

Instances

Monad (ST s) 
Functor (ST s) 
HasRef (ST s) 
Show (ST s a) 
Monad m => NewRef (ST s a) m a 
MonadIO m => ReadRef (ST RealWorld a) m a 
NewRef (STRef s a) (ST s) a 
ModifyRef (STRef s a) (ST s) a 
ReadRef (ST s a) (ST s) a 
ReadRef (STRef s a) (ST s) a 
WriteRef (STRef s a) (ST s) a 

data RealWorld

RealWorld is deeply magical. It is primitive, but it is not unlifted (hence ptrArg). We never manipulate values of type RealWorld; it's only used in the type system, to parameterise State#.

data ForeignPtr a

The type ForeignPtr represents references to objects that are maintained in a foreign language, i.e., that are not part of the data structures usually managed by the Haskell storage manager. The essential difference between ForeignPtrs and vanilla memory references of type Ptr a is that the former may be associated with finalizers. A finalizer is a routine that is invoked when the Haskell storage manager detects that - within the Haskell heap and stack - there are no more references left that are pointing to the ForeignPtr. Typically, the finalizer will, then, invoke routines in the foreign language that free the resources bound by the foreign object.

The ForeignPtr is parameterised in the same way as Ptr. The type argument of ForeignPtr should normally be an instance of class Storable.

data STM a

A monad supporting atomic memory transactions.

Instances

Monad STM 
Functor STM 
Typeable1 STM 
MonadPlus STM 
HasMRef STM 
HasRef STM 
PutMRef (TVar (Maybe a)) STM a 
PutMRef (TMVar a) STM a 
TakeMRef (TVar (Maybe a)) STM a 
TakeMRef (TMVar a) STM a 
NewMRef (TVar (Maybe a)) STM a 
NewMRef (TMVar a) STM a 
NewRef (TVar a) STM a 
ModifyRef (TVar a) STM a 
MonadIO m => ReadRef (STM a) m a 
ReadRef (STM a) STM a 
ReadRef (TVar a) STM a 
WriteRef (TVar a) STM a 
NewRef (TMVar a) STM (Maybe a) 
ReadRef (TMVar a) STM (Maybe a) 
PutMRef (MRef STM a) IO a 
TakeMRef (MRef STM a) IO a 
NewMRef (MRef STM a) IO a 
MonadIO m => NewRef (Ref STM a) m a 
MonadIO m => ModifyRef (Ref STM a) m a 
MonadIO m => ReadRef (Ref STM a) m a 
MonadIO m => WriteRef (Ref STM a) m a 

data TVar a

Shared memory locations that support atomic memory transactions.

Instances

Typeable1 TVar 
Eq (TVar a) 
PutMRef (TVar (Maybe a)) IO a 
PutMRef (TVar (Maybe a)) STM a 
TakeMRef (TVar (Maybe a)) IO a 
TakeMRef (TVar (Maybe a)) STM a 
NewMRef (TVar (Maybe a)) IO a 
NewMRef (TVar (Maybe a)) STM a 
MonadIO m => NewRef (TVar a) m a 
NewRef (TVar a) STM a 
MonadIO m => ModifyRef (TVar a) m a 
ModifyRef (TVar a) STM a 
MonadIO m => ReadRef (TVar a) m a 
ReadRef (TVar a) STM a 
MonadIO m => WriteRef (TVar a) m a 
WriteRef (TVar a) STM a 

data TMVar a

A TMVar is a synchronising variable, used for communication between concurrent threads. It can be thought of as a box, which may be empty or full.

Instances

Typeable1 TMVar 
Eq (TMVar a) 
PutMRef (TMVar a) IO a 
PutMRef (TMVar a) STM a 
TakeMRef (TMVar a) IO a 
TakeMRef (TMVar a) STM a 
NewMRef (TMVar a) IO a 
NewMRef (TMVar a) STM a 
MonadIO m => NewRef (TMVar a) m (Maybe a) 
NewRef (TMVar a) STM (Maybe a) 
MonadIO m => ReadRef (TMVar a) m (Maybe a) 
ReadRef (TMVar a) STM (Maybe a) 

atomically :: STM a -> IO a

Perform a series of STM actions atomically.

You cannot use atomically inside an unsafePerformIO or unsafeInterleaveIO. Any attempt to do so will result in a runtime error. (Reason: allowing this would effectively allow a transaction inside a transaction, depending on exactly when the thunk is evaluated.)

However, see newTVarIO, which can be called inside unsafePerformIO, and which allows top-level TVars to be allocated.

newtype UnsafeModifyRef sr Source

Wrap a state reference that supports reading and writing, and add a potentially thread-unsafe ModifyRef instance.

Constructors

UnsafeModifyRef sr 

Instances

(Monad m, ReadRef sr m a, WriteRef sr m a) => ModifyRef (UnsafeModifyRef sr) m a 
ReadRef sr m a => ReadRef (UnsafeModifyRef sr) m a 
WriteRef sr m a => WriteRef (UnsafeModifyRef sr) m a