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

Safe HaskellUnsafe
LanguageHaskell2010

Control.Monad.STE.Internal

Synopsis

Documentation

newtype STE e s a Source #

Constructors

STE (STERep s a) 

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

unSTE :: STE e s a -> STERep s a Source #

type STERep s a = State# s -> (#State# s, a#) Source #

data STEret s a Source #

Constructors

STEret (State# s) a 

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

unsafeInterleaveSTE :: STE e s a -> STE e s a Source #

liftSTE :: STE e s a -> State# s -> STEret s a Source #

fixSTE :: (a -> STE e s a) -> STE e s a Source #

Allow the result of a state transformer computation to be used (lazily) inside the computation. Note that if f is strict, fixSTE f = _|_.

runBasicSTE :: (forall s. STE e s a) -> 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#.

unsafeIOToSTE :: IO a -> STE e s a Source #

unsafeSTEToIO :: STE e s a -> IO a Source #