hermit-0.7.1.0: Haskell Equational Reasoning Model-to-Implementation Tunnel

Safe HaskellNone
LanguageHaskell2010

HERMIT.Monad

Contents

Synopsis

The HERMIT Monad

data HermitM a Source

The HERMIT monad is kept abstract.

It provides a reader for ModGuts, state for Lemmas, and access to a debugging channel.

Instances

Monad HermitM 
Functor HermitM 
Applicative HermitM 
MonadThings HermitM 
HasDynFlags HermitM 
MonadUnique HermitM 
MonadIO HermitM 
MonadCatch HermitM 
LiftCoreM HermitM 
HasLemmas HermitM 
HasHscEnv HermitM 
HasDebugChan HermitM 
HasHermitMEnv HermitM 
Extern [RewriteH LCoreTC] 
Extern [RewriteH LCore] 
Extern (BiRewriteH LCoreTC) 
Extern (BiRewriteH LCore) 
Extern (RewriteH LCoreTC) 
Extern (RewriteH LCore) 
Extern (RewriteH Equality) 
Extern (PrettyH LCoreTC) 
Extern (PrettyH LCore) 
Extern (TransformH LCoreTC String) 
Extern (TransformH LCoreTC ()) 
Extern (TransformH LCoreTC LocalPathH) 
Extern (TransformH LCoreTC LCore) 
Extern (TransformH LCoreTC DocH) 
Extern (TransformH LCore String) 
Extern (TransformH LCore ()) 
Extern (TransformH LCore LocalPathH) 
Extern (TransformH LCore DocH) 
Extern (TransformH Equality String) 
Extern (TransformH Equality ()) 
type Box [RewriteH LCoreTC] = RewriteLCoreTCListBox 
type Box [RewriteH LCore] = RewriteLCoreListBox 
type Box (BiRewriteH LCoreTC) = BiRewriteLCoreTCBox 
type Box (BiRewriteH LCore) = BiRewriteLCoreBox 
type Box (RewriteH LCoreTC) = RewriteLCoreTCBox 
type Box (RewriteH LCore) = RewriteLCoreBox 
type Box (RewriteH Equality) 
type Box (PrettyH LCoreTC) = PrettyHLCoreTCBox 
type Box (PrettyH LCore) = PrettyHLCoreBox 
type Box (TransformH LCoreTC String) = TransformLCoreTCStringBox 
type Box (TransformH LCoreTC ()) = TransformLCoreTCUnitBox 
type Box (TransformH LCoreTC LocalPathH) = TransformLCoreTCPathBox 
type Box (TransformH LCoreTC LCore) = TransformLCoreTCLCoreBox 
type Box (TransformH LCoreTC DocH) = TransformLCoreTCDocHBox 
type Box (TransformH LCore String) = TransformLCoreStringBox 
type Box (TransformH LCore ()) = TransformLCoreUnitBox 
type Box (TransformH LCore LocalPathH) = TransformLCorePathBox 
type Box (TransformH LCore DocH) = TransformLCoreDocHBox 
type Box (TransformH Equality String) 
type Box (TransformH Equality ()) 

runHM :: DebugChan -> HermitMEnv -> (HermitMResult a -> CoreM b) -> (String -> CoreM b) -> HermitM a -> CoreM b Source

Eliminator for HermitM.

embedHermitM :: (HasDebugChan m, HasHermitMEnv m, HasLemmas m, LiftCoreM m) => HermitM a -> m a Source

Allow HermitM to be embedded in another monad with proper capabilities.

data HermitMEnv Source

The HermitM environment.

data HermitMResult a Source

The HermitM result record.

Constructors

HermitMResult 

Fields

hResChanged :: Bool

Whether Lemmas have changed

hResLemmas :: Lemmas
 
hResult :: a
 

class Monad m => LiftCoreM m where Source

Methods

liftCoreM :: CoreM a -> m a Source

CoreM can be lifted to this monad.

Instances

Lemmas

class HasLemmas m where Source

Methods

getLemmas :: m Lemmas Source

putLemmas :: Lemmas -> m () Source

withLemmas :: Lemmas -> m a -> m a Source

Instances

addLemma :: (HasLemmas m, Monad m) => LemmaName -> Lemma -> m () Source

Only adds a lemma if doesn't already exist.

findLemma :: (HasLemmas m, Monad m) => LemmaName -> m Lemma Source

Find a lemma by name. Fails if lemma does not exist.

insertLemma :: (HasLemmas m, Monad m) => LemmaName -> Lemma -> m () Source

Insert or replace a lemma.

Reader Information

class HasHermitMEnv m where Source

Methods

getHermitMEnv :: m HermitMEnv Source

Get the HermitMEnv

class HasHscEnv m where Source

Methods

getHscEnv :: m HscEnv Source

Messages

class HasDebugChan m where Source

Methods

getDebugChan :: m (DebugMessage -> m ()) Source

Get the debugging channel

data DebugMessage :: * where Source

A message packet.