what4-1.1: Solver-agnostic symbolic values support for issuing queries
Copyright(c) Galois Inc 2014-2020
LicenseBSD3
MaintainerJoe Hendrix <jhendrix@galois.com>
Stabilityprovisional
Safe HaskellSafe-Inferred
LanguageHaskell2010

What4.Utils.MonadST

Description

This module defines the MonadST class, which contains the ST and IO monads and a small collection of moand transformers over them.

Synopsis

Documentation

class Monad m => MonadST s m | m -> s where Source #

Methods

liftST :: ST s a -> m a Source #

Instances

Instances details
MonadST RealWorld IO Source # 
Instance details

Defined in What4.Utils.MonadST

Methods

liftST :: ST RealWorld a -> IO a Source #

MonadST s (ST s) Source # 
Instance details

Defined in What4.Utils.MonadST

Methods

liftST :: ST s a -> ST s a Source #

(MonadST s m, Monoid w) => MonadST s (WriterT w m) Source # 
Instance details

Defined in What4.Utils.MonadST

Methods

liftST :: ST s a -> WriterT w m a Source #

(MonadST s m, Monoid w) => MonadST s (WriterT w m) Source # 
Instance details

Defined in What4.Utils.MonadST

Methods

liftST :: ST s a -> WriterT w m a Source #

MonadST s m => MonadST s (StateT u m) Source # 
Instance details

Defined in What4.Utils.MonadST

Methods

liftST :: ST s a -> StateT u m a Source #

MonadST s m => MonadST s (StateT u m) Source # 
Instance details

Defined in What4.Utils.MonadST

Methods

liftST :: ST s a -> StateT u m a Source #

MonadST s m => MonadST s (ReaderT r m) Source # 
Instance details

Defined in What4.Utils.MonadST

Methods

liftST :: ST s a -> ReaderT r m a Source #

MonadST s (VarRecorder s t) Source # 
Instance details

Defined in What4.Expr.VarIdentification

Methods

liftST :: ST s a -> VarRecorder s t a Source #

MonadST s m => MonadST s (ContT r m) Source # 
Instance details

Defined in What4.Utils.MonadST

Methods

liftST :: ST s a -> ContT r m a Source #

data ST s a #

The strict ST monad. The ST monad allows for destructive updates, but is escapable (unlike IO). A computation of type ST s a returns a value of type a, and execute in "thread" s. The s parameter is either

  • an uninstantiated type variable (inside invocations of runST), or
  • RealWorld (inside invocations of stToIO).

It serves to keep the internal states of different invocations of runST separate from each other and from invocations of stToIO.

The >>= and >> operations are strict in the state (though not in values stored in the state). For example,

runST (writeSTRef _|_ v >>= f) = _|_

Instances

Instances details
MonadST s (ST s) Source # 
Instance details

Defined in What4.Utils.MonadST

Methods

liftST :: ST s a -> ST s a Source #

Monad (ST s)

Since: base-2.1

Instance details

Defined in GHC.ST

Methods

(>>=) :: ST s a -> (a -> ST s b) -> ST s b #

(>>) :: ST s a -> ST s b -> ST s b #

return :: a -> ST s a #

Functor (ST s)

Since: base-2.1

Instance details

Defined in GHC.ST

Methods

fmap :: (a -> b) -> ST s a -> ST s b #

(<$) :: a -> ST s b -> ST s a #

MonadFix (ST s)

Since: base-2.1

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> ST s a) -> ST s a #

MonadFail (ST s)

Since: base-4.11.0.0

Instance details

Defined in GHC.ST

Methods

fail :: String -> ST s a #

Applicative (ST s)

Since: base-4.4.0.0

Instance details

Defined in GHC.ST

Methods

pure :: a -> ST s a #

(<*>) :: ST s (a -> b) -> ST s a -> ST s b #

liftA2 :: (a -> b -> c) -> ST s a -> ST s b -> ST s c #

(*>) :: ST s a -> ST s b -> ST s b #

(<*) :: ST s a -> ST s b -> ST s a #

MonadThrow (ST s) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> ST s a #

PrimMonad (ST s) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (ST s) #

Methods

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

PrimBase (ST s) 
Instance details

Defined in Control.Monad.Primitive

Methods

internal :: ST s a -> State# (PrimState (ST s)) -> (# State# (PrimState (ST s)), a #) #

Show (ST s a)

Since: base-2.1

Instance details

Defined in GHC.ST

Methods

showsPrec :: Int -> ST s a -> ShowS #

show :: ST s a -> String #

showList :: [ST s a] -> ShowS #

Semigroup a => Semigroup (ST s a)

Since: base-4.11.0.0

Instance details

Defined in GHC.ST

Methods

(<>) :: ST s a -> ST s a -> ST s a #

sconcat :: NonEmpty (ST s a) -> ST s a #

stimes :: Integral b => b -> ST s a -> ST s a #

Monoid a => Monoid (ST s a)

Since: base-4.11.0.0

Instance details

Defined in GHC.ST

Methods

mempty :: ST s a #

mappend :: ST s a -> ST s a -> ST s a #

mconcat :: [ST s a] -> ST s a #

Strict (ST s a) (ST s a) 
Instance details

Defined in Control.Lens.Iso

Methods

strict :: Iso' (ST s a) (ST0 s a) #

type PrimState (ST s) 
Instance details

Defined in Control.Monad.Primitive

type PrimState (ST s) = s

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

Instances

Instances details
MonadST RealWorld IO Source # 
Instance details

Defined in What4.Utils.MonadST

Methods

liftST :: ST RealWorld a -> IO a Source #