{-# LANGUAGE FlexibleContexts, ScopedTypeVariables #-} module HERMIT.Shell.Externals where import Control.Applicative import Data.Monoid import Data.List (intercalate) import qualified Data.Map as M import Control.Monad (liftM) import Data.Dynamic (fromDynamic) import HERMIT.Context import HERMIT.Kure import HERMIT.External import HERMIT.Kernel.Scoped import HERMIT.Parser import HERMIT.Plugin.Renderer import HERMIT.PrettyPrinter.Common import HERMIT.Shell.Dictionary import HERMIT.Shell.Interpreter import HERMIT.Shell.KernelEffect import HERMIT.Shell.Proof as Proof import HERMIT.Shell.ScriptToRewrite import HERMIT.Shell.ShellEffect import HERMIT.Shell.Types ---------------------------------------------------------------------------------- -- | There are five types of commands. data ShellCommand = KernelEffect KernelEffect -- ^ Command that modifies the state of the (scoped) kernel. | ScriptEffect ScriptEffect -- ^ Command that deals with script files. | ShellEffect ShellEffect -- ^ Command that modifies the state of the shell. | QueryFun QueryFun -- ^ Command that queries the AST with a Transform (read only). | ProofCommand ProofCommand -- ^ Command that deals with proofs. -- | Interpret a boxed thing as one of the four possible shell command types. interpShellCommand :: [Interp ShellCommand] interpShellCommand = [ interp $ \ (RewriteCoreBox rr) -> KernelEffect (Apply rr) , interp $ \ (RewriteCoreTCBox rr) -> KernelEffect (Apply rr) , interp $ \ (BiRewriteCoreBox br) -> KernelEffect (Apply $ whicheverR br) , interp $ \ (CrumbBox cr) -> KernelEffect (Pathfinder (return (mempty @@ cr) :: TransformH CoreTC LocalPathH)) , interp $ \ (PathBox p) -> KernelEffect (Pathfinder (return p :: TransformH CoreTC LocalPathH)) , interp $ \ (TransformCorePathBox tt) -> KernelEffect (Pathfinder tt) , interp $ \ (TransformCoreTCPathBox tt) -> KernelEffect (Pathfinder tt) , interp $ \ (StringBox str) -> QueryFun (message str) , interp $ \ (TransformCoreStringBox tt) -> QueryFun (QueryString tt) , interp $ \ (TransformCoreTCStringBox tt) -> QueryFun (QueryString tt) , interp $ \ (TransformCoreTCDocHBox tt) -> QueryFun (QueryDocH $ unTransformDocH tt) , interp $ \ (TransformCoreCheckBox tt) -> QueryFun (CorrectnessCritera tt) , interp $ \ (TransformCoreTCCheckBox tt) -> QueryFun (CorrectnessCritera tt) , interp $ \ (effect :: KernelEffect) -> KernelEffect effect , interp $ \ (effect :: ShellEffect) -> ShellEffect effect , interp $ \ (effect :: ScriptEffect) -> ScriptEffect effect , interp $ \ (query :: QueryFun) -> QueryFun query , interp $ \ (cmd :: ProofCommand) -> ProofCommand cmd ] shell_externals :: [External] shell_externals = map (.+ Shell) [ external "resume" Resume -- HERMIT Kernel Exit [ "stops HERMIT; resumes compile" ] , external "abort" Abort -- UNIX Exit [ "hard UNIX-style exit; does not return to GHC; does not save" ] , external "continue" Continue -- Shell Exit, but not HERMIT [ "exits shell; resumes HERMIT" ] , external "gc" (Delete . SAST) [ "garbage-collect a given AST; does not remove from command log" ] , external "gc" (CLSModify gc) [ "garbage-collect all ASTs except for the initial and current AST" ] , external "display" Display [ "redisplays current state" ] , external "left" (Direction L) [ "move to the next child"] , external "right" (Direction R) [ "move to the previous child"] , external "up" (Direction U) [ "move to the parent node"] , external "down" (deprecatedIntToPathT 0 :: TransformH Core LocalPathH) -- TODO: short-term solution [ "move to the first child"] , external "navigate" (CLSModify $ \ st -> return $ st { cl_nav = True }) [ "switch to navigate mode" ] , external "command-line" (CLSModify $ \ st -> return $ st { cl_nav = False }) [ "switch to command line mode" ] , external "set-window" (CLSModify setWindow) [ "fix the window to the current focus" ] , external "top" (Direction T) [ "move to root of current scope" ] , external "back" (CLSModify $ versionCmd Back) [ "go back in the derivation" ] .+ VersionControl , external "log" (Inquiry showDerivationTree) [ "go back in the derivation" ] .+ VersionControl , external "step" (CLSModify $ versionCmd Step) [ "step forward in the derivation" ] .+ VersionControl , external "goto" (CLSModify . versionCmd . Goto) [ "goto a specific step in the derivation" ] .+ VersionControl , external "goto" (CLSModify . versionCmd . GotoTag) [ "goto a named step in the derivation" ] , external "tag" (CLSModify . versionCmd . AddTag) [ "tag