primitive-0.6.2.0: Primitive memory-related operations

Copyright(c) Roman Leshchinskiy 2009
LicenseBSD-style
MaintainerRoman Leshchinskiy <rl@cse.unsw.edu.au>
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Primitive

Description

Primitive state-transformer monads

Synopsis

Documentation

class Monad m => PrimMonad m where Source #

Class of monads which can perform primitive state-transformer actions

Minimal complete definition

primitive

Associated Types

type PrimState m Source #

State token type

Methods

primitive :: (State# (PrimState m) -> (#State# (PrimState m), a#)) -> m a Source #

Execute a primitive operation

Instances

PrimMonad IO Source # 

Associated Types

type PrimState (IO :: * -> *) :: * Source #

PrimMonad (ST s) Source # 

Associated Types

type PrimState (ST s :: * -> *) :: * Source #

Methods

primitive :: (State# (PrimState (ST s)) -> (#VoidRep, PtrRepLifted, State# (PrimState (ST s)), a#)) -> ST s a Source #

PrimMonad m => PrimMonad (MaybeT m) Source # 

Associated Types

type PrimState (MaybeT m :: * -> *) :: * Source #

PrimMonad m => PrimMonad (ListT m) Source # 

Associated Types

type PrimState (ListT m :: * -> *) :: * Source #

Methods

primitive :: (State# (PrimState (ListT m)) -> (#VoidRep, PtrRepLifted, State# (PrimState (ListT m)), a#)) -> ListT m a Source #

(Monoid w, PrimMonad m) => PrimMonad (WriterT w m) Source # 

Associated Types

type PrimState (WriterT w m :: * -> *) :: * Source #

Methods

primitive :: (State# (PrimState (WriterT w m)) -> (#VoidRep, PtrRepLifted, State# (PrimState (WriterT w m)), a#)) -> WriterT w m a Source #

(Monoid w, PrimMonad m) => PrimMonad (WriterT w m) Source # 

Associated Types

type PrimState (WriterT w m :: * -> *) :: * Source #

Methods

primitive :: (State# (PrimState (WriterT w m)) -> (#VoidRep, PtrRepLifted, State# (PrimState (WriterT w m)), a#)) -> WriterT w m a Source #

PrimMonad m => PrimMonad (StateT s m) Source # 

Associated Types

type PrimState (StateT s m :: * -> *) :: * Source #

Methods

primitive :: (State# (PrimState (StateT s m)) -> (#VoidRep, PtrRepLifted, State# (PrimState (StateT s m)), a#)) -> StateT s m a Source #

PrimMonad m => PrimMonad (StateT s m) Source # 

Associated Types

type PrimState (StateT s m :: * -> *) :: * Source #

Methods

primitive :: (State# (PrimState (StateT s m)) -> (#VoidRep, PtrRepLifted, State# (PrimState (StateT s m)), a#)) -> StateT s m a Source #

PrimMonad m => PrimMonad (IdentityT * m) Source # 

Associated Types

type PrimState (IdentityT * m :: * -> *) :: * Source #

PrimMonad m => PrimMonad (ExceptT e m) Source # 

Associated Types

type PrimState (ExceptT e m :: * -> *) :: * Source #

Methods

primitive :: (State# (PrimState (ExceptT e m)) -> (#VoidRep, PtrRepLifted, State# (PrimState (ExceptT e m)), a#)) -> ExceptT e m a Source #

(Error e, PrimMonad m) => PrimMonad (ErrorT e m) Source # 

Associated Types

type PrimState (ErrorT e m :: * -> *) :: * Source #

Methods

primitive :: (State# (PrimState (ErrorT e m)) -> (#VoidRep, PtrRepLifted, State# (PrimState (ErrorT e m)), a#)) -> ErrorT e m a Source #

PrimMonad m => PrimMonad (ReaderT * r m) Source # 

Associated Types

type PrimState (ReaderT * r m :: * -> *) :: * Source #

Methods

primitive :: (State# (PrimState (ReaderT * r m)) -> (#VoidRep, PtrRepLifted, State# (PrimState (ReaderT * r m)), a#)) -> ReaderT * r m a Source #

(Monoid w, PrimMonad m) => PrimMonad (RWST r w s m) Source # 

Associated Types

type PrimState (RWST r w s m :: * -> *) :: * Source #

Methods

primitive :: (State# (PrimState (RWST r w s m)) -> (#VoidRep, PtrRepLifted, State# (PrimState (RWST r w s m)), a#)) -> RWST r w s m a Source #

(Monoid w, PrimMonad m) => PrimMonad (RWST r w s m) Source # 

Associated Types

type PrimState (RWST r w s m :: * -> *) :: * Source #

Methods

primitive :: (State# (PrimState (RWST r w s m)) -> (#VoidRep, PtrRepLifted, State# (PrimState (RWST r w s m)), a#)) -> RWST r w s m a Source #

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#.

primitive_ :: PrimMonad m => (State# (PrimState m) -> State# (PrimState m)) -> m () Source #

Execute a primitive operation with no result

class PrimMonad m => PrimBase m where Source #

Class of primitive monads for state-transformer actions.

Unlike PrimMonad, this typeclass requires that the Monad be fully expressed as a state transformer, therefore disallowing other monad transformers on top of the base IO or ST.

Minimal complete definition

internal

Methods

internal :: m a -> State# (PrimState m) -> (#State# (PrimState m), a#) Source #

Expose the internal structure of the monad

liftPrim :: (PrimBase m1, PrimMonad m2, PrimState m1 ~ PrimState m2) => m1 a -> m2 a Source #

Lifts a PrimBase into another PrimMonad with the same underlying state token type.

primToPrim :: (PrimBase m1, PrimMonad m2, PrimState m1 ~ PrimState m2) => m1 a -> m2 a Source #

Convert a PrimBase to another monad with the same state token.

primToIO :: (PrimBase m, PrimState m ~ RealWorld) => m a -> IO a Source #

Convert a PrimBase with a RealWorld state token to IO

primToST :: PrimBase m => m a -> ST (PrimState m) a Source #

Convert a PrimBase to ST

ioToPrim :: (PrimMonad m, PrimState m ~ RealWorld) => IO a -> m a Source #

Convert an IO action to a PrimMonad.

stToPrim :: PrimMonad m => ST (PrimState m) a -> m a Source #

Convert an ST action to a PrimMonad.

unsafePrimToPrim :: (PrimBase m1, PrimMonad m2) => m1 a -> m2 a Source #

Convert a PrimBase to another monad with a possibly different state token. This operation is highly unsafe!

unsafePrimToIO :: PrimBase m => m a -> IO a Source #

Convert any PrimBase to IO. This operation is highly unsafe!

unsafePrimToST :: PrimBase m => m a -> ST s a Source #

Convert any PrimBase to ST with an arbitrary state token. This operation is highly unsafe!

unsafeIOToPrim :: PrimMonad m => IO a -> m a Source #

Convert an IO action to any PrimMonad. This operation is highly unsafe!

unsafeSTToPrim :: PrimMonad m => ST s a -> m a Source #

Convert an ST action with an arbitraty state token to any PrimMonad. This operation is highly unsafe!

touch :: PrimMonad m => a -> m () Source #

evalPrim :: forall a m. PrimMonad m => a -> m a Source #

Create an action to force a value; generalizes evaluate