basement-0.0.11: Foundation scrap box of array & string

LicenseBSD-style
MaintainerVincent Hanquez <vincent@snarc.org>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Basement.Monad

Description

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

Documentation

class (Functor m, Applicative m, Monad m) => PrimMonad m where Source #

Primitive monad that can handle mutation.

For example: IO and ST.

Associated Types

type PrimState m Source #

type of state token associated with the PrimMonad m

type PrimVar m :: * -> * Source #

type of variable associated with the PrimMonad m

Methods

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 # 
Instance details

Defined in Basement.Monad

Associated Types

type PrimState IO :: Type Source #

type PrimVar IO :: Type -> Type Source #

PrimMonad (ST s) Source # 
Instance details

Defined in Basement.Monad

Associated Types

type PrimState (ST s) :: Type Source #

type PrimVar (ST s) :: Type -> Type Source #

Methods

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 #

primVarRead :: PrimVar (ST s) a -> ST s a Source #

primVarWrite :: PrimVar (ST s) a -> a -> ST s () 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

Associated Types

type Failure m Source #

The associated type with the MonadFailure, representing what failure can be encoded in this monad

Methods

mFail :: Failure m -> m () Source #

Raise a Failure through a monad.

Instances
MonadFailure Maybe Source # 
Instance details

Defined in Basement.Monad

Associated Types

type Failure Maybe :: Type Source #

Methods

mFail :: Failure Maybe -> Maybe () Source #

MonadFailure (Either a) Source # 
Instance details

Defined in Basement.Monad

Associated Types

type Failure (Either a) :: Type Source #

Methods

mFail :: Failure (Either a) -> Either a () Source #

Monad state => MonadFailure (Builder collection mutCollection step state err) Source # 
Instance details

Defined in Basement.MutableBuilder

Associated Types

type Failure (Builder collection mutCollection step state err) :: Type Source #

Methods

mFail :: Failure (Builder collection mutCollection step state err) -> 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

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

Touch primitive lifted to any prim monad