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

Safe HaskellNone
LanguageHaskell2010

HERMIT.Shell.Types

Synopsis

Documentation

newtype CLT m a Source

This type is similiar to PluginM, except that its exception and state types are supersets of those for PluginM, and it is a transformer. There are two functions: clm and pluginM for converting between the two. The reason we do this is to obtain a clean separation of plugin state from commandline state without nesting state transformers. Nesting StateT leads to a lot of awkward lifting and manual state management in the command line code.

NB: an alternative to monad transformers, like Oleg's Extensible Effects, might be useful here.

Instances

MonadTrans CLT 
Monad m => MonadError CLException (CLT m) 
Monad m => MonadReader PluginReader (CLT m) 
Monad m => MonadState CommandLineState (CLT m) 
Monad m => Monad (CLT m)

Our own custom instance of Monad for CLT so we don't have to depend on newtype deriving to do the right thing for fail.

Functor m => Functor (CLT m) 
(Monad m, Functor m) => Applicative (CLT m) 
MonadIO m => MonadIO (CLT m) 
MonadException m => MonadException (CLT m) 
Monad m => MonadCatch (CLT m) 

runCLT :: PluginReader -> CommandLineState -> CLT m a -> m (Either CLException a, CommandLineState) Source

Run a CLT computation.

clm2clt :: CLMonad m => CLT IO a -> m a Source

Lift a CLT IO computation into a computation in an arbitrary CLMonad.

clm :: CLT IO a -> PluginM a Source

Lift a CLM computation into the PluginM monad.

pluginM :: CLMonad m => PluginM a -> m a Source

Lift a PluginM computation into the CLM monad.

data CommandLineState Source

Constructors

CommandLineState 

Fields

cl_pstate :: PluginState

Access to the enclosing plugin state. This is propagated back to the plugin after the CLT computation ends. We do it this way because nested StateT is a pain.

cl_height :: Int

console height, in lines

cl_scripts :: [(ScriptName, Script)]
 
cl_nav :: Bool

keyboard input the nav panel

cl_foci :: Map AST PathStack

focus assigned to each AST

cl_tags :: Map AST [String]

list of tags on an AST

cl_proofstack :: Map AST [ProofTodo]

stack of todos for the proof shell

cl_window :: PathH

path to beginning of window, always a prefix of focus path in kernel

cl_externals :: [External]

Currently visible externals

cl_running_script :: Maybe Script

Nothing = no script running, otherwise the remaining script commands

cl_safety :: Safety

which level of safety we are running in

cl_templemmas :: TVar [(HermitC, LemmaName, Lemma)]

updated by kernel env with temporary obligations

cl_failhard :: Bool

Any exception will cause an abort.

cl_diffonly :: Bool

Print diffs instead of full focus.

data ProofTodo Source

Constructors

Unproven 

Fields

ptName :: LemmaName

lemma we are proving

ptLemma :: Lemma
 
ptContext :: HermitC

context in which lemma is being proved

ptPath :: PathStack

path into lemma to focus on

mkCLS :: PluginM CommandLineState Source

Create default CommandLineState from PluginState. Note: the dictionary (cl_dict) will be empty, and should be populated if needed.

newtype CLSBox Source

Constructors

CLSBox CommandLineState 

Instances

cl_putStr :: CLMonad m => String -> m () Source

pathStack2Path :: ([LocalPath crumb], LocalPath crumb) -> Path crumb Source

data Direction Source

A primitive means of denoting navigation of a tree (within a local scope).

Constructors

U

Up

T

Top

addAST :: CLMonad m => AST -> m () Source

getProofStack :: CLMonad m => m [ProofTodo] Source

Always returns a non-empty list.

fixWindow :: CLMonad m => m () Source

queryInContext :: forall b m. (MonadCatch m, CLMonad m) => TransformH LCoreTC b -> CommitMsg -> m b Source