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

Safe HaskellNone
LanguageHaskell2010

HERMIT.Monad

Contents

Synopsis

The HERMIT Monad

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, HasStash m, LiftCoreM m) => HermitM a -> m a Source

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

data HermitMEnv Source

The HermitM reader environment.

Constructors

HermitMEnv 

Fields

hEnvModGuts :: ModGuts

Note: this is a snapshot of the ModGuts from before the current transformation.

hEnvStash :: DefStash
 
hEnvLemmas :: Lemmas
 

data HermitMResult a Source

The HermitM result record.

Constructors

HermitMResult 

class Monad m => LiftCoreM m where Source

Methods

liftCoreM :: CoreM a -> m a Source

CoreM can be lifted to this monad.

Instances

Saving Definitions

newtype RememberedName Source

A label for individual definitions. Use a newtype so we can tab-complete in shell.

Constructors

RememberedName String 

type DefStash = Map RememberedName CoreDef Source

A store of saved definitions.

saveDef :: (HasStash m, Monad m) => RememberedName -> CoreDef -> m () Source

Save a definition for future use.

lookupDef :: (HasStash m, Monad m) => RememberedName -> m CoreDef Source

Lookup a previously saved definition.

class HasStash m where Source

Methods

getStash :: m DefStash Source

Get the stash of saved definitions.

putStash :: DefStash -> m () Source

Replace the stash of saved definitions.

Instances

Lemmas

data Equality Source

An equality is represented as a set of universally quantified binders, and the LHS and RHS of the equality.

newtype LemmaName Source

A name for lemmas. Use a newtype so we can tab-complete in shell.

Constructors

LemmaName String 

data Lemma Source

An equality with a proven status.

Constructors

Lemma 

Fields

lemmaEq :: Equality
 
lemmaP :: Bool
 
lemmaU :: Bool
 

type Lemmas = Map LemmaName Lemma Source

A collectin of named lemmas.

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

Only adds a lemma if doesn't already exist.

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

Writer Information

class HasLemmas m where Source

Methods

insertLemma :: LemmaName -> Lemma -> m () Source

Add (or replace) a named lemma.

getLemmas :: m Lemmas Source

Instances

Messages

class HasDebugChan m where Source

Methods

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

Get the debugging channel

data DebugMessage :: * where Source

A message packet.