License | BSD-style |
---|---|
Maintainer | Vincent Hanquez <vincent@snarc.org> |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Allow to run operation in ST and IO, without having to distinguinsh between the two. Most operations exposes the bare nuts and bolts of how IO and ST actually works, and relatively easy to shoot yourself in the foot
this is highly similar to the Control.Monad.Primitive in the primitive package
Synopsis
- class (Functor m, Applicative m, Monad m) => PrimMonad m where
- type PrimState m
- type PrimVar m :: * -> *
- primitive :: (State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a
- primThrow :: Exception e => e -> m a
- unPrimMonad :: m a -> State# (PrimState m) -> (# State# (PrimState m), a #)
- primVarNew :: a -> m (PrimVar m a)
- primVarRead :: PrimVar m a -> m a
- primVarWrite :: PrimVar m a -> a -> m ()
- class Monad m => MonadFailure m where
- unPrimMonad_ :: PrimMonad m => m () -> State# (PrimState m) -> State# (PrimState m)
- unsafePrimCast :: (PrimMonad m1, PrimMonad m2) => m1 a -> m2 a
- unsafePrimToST :: PrimMonad prim => prim a -> ST s a
- unsafePrimToIO :: PrimMonad prim => prim a -> IO a
- unsafePrimFromIO :: PrimMonad prim => IO a -> prim a
- primTouch :: PrimMonad m => a -> m ()
Documentation
class (Functor m, Applicative m, Monad m) => PrimMonad m where Source #
Primitive monad that can handle mutation.
For example: IO and ST.
type of state token associated with the PrimMonad m
type PrimVar m :: * -> * Source #
type of variable associated with the PrimMonad m
primitive :: (State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a Source #
Unwrap the State# token to pass to a function a primitive function that returns an unboxed state and a value.
primThrow :: Exception e => e -> m a Source #
Throw Exception in the primitive monad
unPrimMonad :: m a -> State# (PrimState m) -> (# State# (PrimState m), a #) Source #
Run a Prim monad from a dedicated state#
primVarNew :: a -> m (PrimVar m a) Source #
Build a new variable in the Prim Monad
primVarRead :: PrimVar m a -> m a Source #
Read the variable in the Prim Monad
primVarWrite :: PrimVar m a -> a -> m () Source #
Write the variable in the Prim Monad
Instances
PrimMonad IO Source # | |
Defined in Basement.Monad primitive :: (State# (PrimState IO) -> (# State# (PrimState IO), a #)) -> IO a Source # primThrow :: Exception e => e -> IO a Source # unPrimMonad :: IO a -> State# (PrimState IO) -> (# State# (PrimState IO), a #) Source # primVarNew :: a -> IO (PrimVar IO a) Source # | |
PrimMonad (ST s) Source # | |
Defined in Basement.Monad primitive :: (State# (PrimState (ST s)) -> (# State# (PrimState (ST s)), a #)) -> ST s a Source # primThrow :: Exception e => e -> ST s a Source # unPrimMonad :: ST s a -> State# (PrimState (ST s)) -> (# State# (PrimState (ST s)), a #) Source # primVarNew :: a -> ST s (PrimVar (ST s) a) Source # |
class Monad m => MonadFailure m where Source #
Monad that can represent failure
Similar to MonadFail but with a parametrized Failure linked to the Monad
The associated type with the MonadFailure, representing what failure can be encoded in this monad
Instances
MonadFailure Maybe Source # | |
MonadFailure (Either a) Source # | |
Monad state => MonadFailure (Builder collection mutCollection step state err) Source # | |
unPrimMonad_ :: PrimMonad m => m () -> State# (PrimState m) -> State# (PrimState m) Source #
just like unwrapPrimMonad
but throw away the result and return just the new State#
unsafePrimCast :: (PrimMonad m1, PrimMonad m2) => m1 a -> m2 a Source #
Convert a prim monad to another prim monad.
The net effect is that it coerce the state repr to another, so the runtime representation should be the same, otherwise hilary ensues.
unsafePrimToST :: PrimMonad prim => prim a -> ST s a Source #
Convert any prim monad to an ST monad
unsafePrimToIO :: PrimMonad prim => prim a -> IO a Source #
Convert any prim monad to an IO monad
unsafePrimFromIO :: PrimMonad prim => IO a -> prim a Source #
Convert any IO monad to a prim monad