monad-ste-0.1.0.0: ST monad with efficient explicit errors

Safe HaskellTrustworthy
LanguageHaskell2010

Control.Monad.STE

Synopsis

Documentation

data STE e s a Source #

Instances

Monad (STE e s) Source # 

Methods

(>>=) :: STE e s a -> (a -> STE e s b) -> STE e s b #

(>>) :: STE e s a -> STE e s b -> STE e s b #

return :: a -> STE e s a #

fail :: String -> STE e s a #

Functor (STE e s) Source # 

Methods

fmap :: (a -> b) -> STE e s a -> STE e s b #

(<$) :: a -> STE e s b -> STE e s a #

MonadFix (STE e s) Source # 

Methods

mfix :: (a -> STE e s a) -> STE e s a #

Applicative (STE e s) Source # 

Methods

pure :: a -> STE e s a #

(<*>) :: STE e s (a -> b) -> STE e s a -> STE e s b #

(*>) :: STE e s a -> STE e s b -> STE e s b #

(<*) :: STE e s a -> STE e s b -> STE e s a #

(~) * SomeException err => MonadThrow (STE err s) Source # 

Methods

throwM :: Exception e => e -> STE err s a #

PrimMonad (STE e s) Source # 

Associated Types

type PrimState (STE e s :: * -> *) :: * #

Methods

primitive :: (State# (PrimState (STE e s)) -> (#VoidRep, PtrRepLifted, State# (PrimState (STE e s)), a#)) -> STE e s a #

PrimBase (STE e s) Source # 

Methods

internal :: STE e s a -> State# (PrimState (STE e s)) -> (#VoidRep, PtrRepLifted, State# (PrimState (STE e s)), a#) #

type PrimState (STE e s) Source # 
type PrimState (STE e s) = s

runSTE :: (forall s. STE e s a) -> (Either e a -> b) -> b Source #

runSTE is the workhorse of the STE monad. Runs an STE computation, and also does the toplevel handling of the abortive throwSTE operator. The naive way to handle errors is to simply write handleSTE id md. runSTE does not and cannot (by design) handle pure or async exceptions.

throwSTE :: forall e s a. e -> STE e s a Source #

throwSTE is the STE sibling of throwIO, and its argument must match the e parameter in STE e s a. There is also no Exception e constraint. throwSTE should be thought of as an "abort" operation which is guaranteed to be caught/handled by runSTE.

handleSTE :: (Either e a -> b) -> (forall s. STE e s a) -> b Source #

handleSTE is a flipped convenience function version of runSTE