Copyright | (c) 2013-2016 Galois Inc. |
---|---|
License | BSD3 |
Maintainer | cryptol@galois.com |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Cryptol.REPL.Monad
Description
Synopsis
- newtype REPL a = REPL {}
- runREPL :: Bool -> Bool -> Logger -> REPL a -> IO a
- io :: IO a -> REPL a
- raise :: REPLException -> REPL a
- stop :: REPL ()
- catch :: REPL a -> (REPLException -> REPL a) -> REPL a
- try :: REPL a -> REPL (Either REPLException a)
- finally :: REPL a -> REPL b -> REPL a
- rPutStrLn :: String -> REPL ()
- rPutStr :: String -> REPL ()
- rPrint :: Show a => a -> REPL ()
- data REPLException
- = ParseError ParseError
- | FileNotFound FilePath
- | DirectoryNotFound FilePath
- | NoPatError [Error]
- | NoIncludeError [IncludeError]
- | EvalError EvalErrorEx
- | TooWide WordTooWide
- | Unsupported Unsupported
- | ModuleSystemError NameDisp ModuleError
- | EvalPolyError Schema
- | InstantiationsNotFound Schema
- | TypeNotTestable Type
- | EvalInParamModule [TParam] [Name]
- | SBVError String
- | SBVException SBVException
- | SBVPortfolioException SBVPortfolioException
- | W4Exception W4Exception
- rethrowEvalError :: IO a -> IO a
- getFocusedEnv :: REPL ModContext
- getModuleEnv :: REPL ModuleEnv
- setModuleEnv :: ModuleEnv -> REPL ()
- getDynEnv :: REPL DynamicEnv
- setDynEnv :: DynamicEnv -> REPL ()
- getCallStacks :: REPL Bool
- getTCSolver :: REPL Solver
- resetTCSolver :: REPL ()
- uniqify :: Name -> REPL Name
- freshName :: Ident -> NameSource -> REPL Name
- whenDebug :: REPL () -> REPL ()
- getEvalOptsAction :: REPL (IO EvalOpts)
- getPPValOpts :: REPL PPOpts
- getExprNames :: REPL [String]
- getTypeNames :: REPL [String]
- getPropertyNames :: REPL ([(Name, Decl)], NameDisp)
- getModNames :: REPL [ModName]
- data LoadedModule = LoadedModule {}
- lName :: LoadedModule -> Maybe ModName
- getLoadedMod :: REPL (Maybe LoadedModule)
- setLoadedMod :: LoadedModule -> REPL ()
- clearLoadedMod :: REPL ()
- setEditPath :: FilePath -> REPL ()
- getEditPath :: REPL (Maybe FilePath)
- clearEditPath :: REPL ()
- setSearchPath :: [FilePath] -> REPL ()
- prependSearchPath :: [FilePath] -> REPL ()
- getPrompt :: REPL String
- shouldContinue :: REPL Bool
- unlessBatch :: REPL () -> REPL ()
- asBatch :: REPL a -> REPL a
- validEvalContext :: FreeVars a => a -> REPL ()
- updateREPLTitle :: REPL ()
- isolated :: REPL a -> REPL a
- setUpdateREPLTitle :: REPL () -> REPL ()
- withRandomGen :: (TFGen -> REPL (a, TFGen)) -> REPL a
- setRandomGen :: TFGen -> REPL ()
- getRandomGen :: REPL TFGen
- getModuleInput :: REPL (ModuleInput IO)
- data EnvVal
- data OptionDescr = OptionDescr {}
- setUser :: String -> String -> REPL Bool
- getUser :: String -> REPL EnvVal
- getKnownUser :: IsEnvVal a => String -> REPL a
- tryGetUser :: String -> REPL (Maybe EnvVal)
- userOptions :: OptionMap
- userOptionsWithAliases :: OptionMap
- getUserSatNum :: REPL SatNum
- getUserShowProverStats :: REPL Bool
- getUserProverValidate :: REPL Bool
- parsePPFloatFormat :: String -> Maybe PPFloatFormat
- parseFieldOrder :: String -> Maybe FieldOrder
- getProverConfig :: REPL (Either SBVProverConfig W4ProverConfig)
- parseSearchPath :: String -> [String]
- getPutStr :: REPL (String -> IO ())
- getLogger :: REPL Logger
- setLogger :: Logger -> REPL ()
- setPutStr :: (String -> IO ()) -> REPL ()
- smokeTest :: REPL [Smoke]
- data Smoke = Z3NotFound
- data RW = RW {
- eLoadedMod :: Maybe LoadedModule
- eEditFile :: Maybe FilePath
- eContinue :: Bool
- eIsBatch :: Bool
- eModuleEnv :: ModuleEnv
- eUserEnv :: UserEnv
- eLogger :: Logger
- eCallStacks :: Bool
- eUpdateTitle :: REPL ()
- eProverConfig :: Either SBVProverConfig W4ProverConfig
- eTCConfig :: SolverConfig
- eTCSolver :: Maybe Solver
- eTCSolverRestarts :: !Int
- eRandomGen :: TFGen
- defaultRW :: Bool -> Bool -> Logger -> IO RW
- mkUserEnv :: OptionMap -> UserEnv
REPL Monad
REPL_ context with InputT handling.
Instances
MonadIO REPL Source # | |
Defined in Cryptol.REPL.Monad | |
Applicative REPL Source # | |
Functor REPL Source # | |
Monad REPL Source # | |
FreshM REPL Source # | |
Defined in Cryptol.REPL.Monad | |
MonadCatch REPL Source # | |
Defined in Cryptol.REPL.Monad | |
MonadMask REPL Source # | |
Defined in Cryptol.REPL.Monad Methods mask :: HasCallStack => ((forall a. REPL a -> REPL a) -> REPL b) -> REPL b # uninterruptibleMask :: HasCallStack => ((forall a. REPL a -> REPL a) -> REPL b) -> REPL b # generalBracket :: HasCallStack => REPL a -> (a -> ExitCase b -> REPL c) -> (a -> REPL b) -> REPL (b, c) # | |
MonadThrow REPL Source # | |
Defined in Cryptol.REPL.Monad Methods throwM :: (HasCallStack, Exception e) => e -> REPL a # | |
MonadBaseControl IO REPL Source # | |
MonadBase IO REPL Source # | |
Defined in Cryptol.REPL.Monad | |
type StM REPL a Source # | |
Defined in Cryptol.REPL.Monad |
runREPL :: Bool -> Bool -> Logger -> REPL a -> IO a Source #
Run a REPL action with a fresh environment.
raise :: REPLException -> REPL a Source #
Raise an exception.
rPutStrLn :: String -> REPL () Source #
Use the configured output action to print a string with a trailing newline
rPrint :: Show a => a -> REPL () Source #
Use the configured output action to print something using its Show instance
Errors
data REPLException Source #
REPL exceptions.
Constructors
Instances
Exception REPLException Source # | |
Defined in Cryptol.REPL.Monad Methods toException :: REPLException -> SomeException # fromException :: SomeException -> Maybe REPLException # displayException :: REPLException -> String # | |
Show REPLException Source # | |
Defined in Cryptol.REPL.Monad Methods showsPrec :: Int -> REPLException -> ShowS # show :: REPLException -> String # showList :: [REPLException] -> ShowS # | |
PP REPLException Source # | |
Defined in Cryptol.REPL.Monad |
rethrowEvalError :: IO a -> IO a Source #
Environment
setModuleEnv :: ModuleEnv -> REPL () Source #
setDynEnv :: DynamicEnv -> REPL () Source #
getCallStacks :: REPL Bool Source #
getTCSolver :: REPL Solver Source #
resetTCSolver :: REPL () Source #
uniqify :: Name -> REPL Name Source #
Given an existing qualified name, prefix it with a
relatively-unique string. We make it unique by prefixing with a
character #
that is not lexically valid in a module name.
freshName :: Ident -> NameSource -> REPL Name Source #
Generate a fresh name using the given index. The name will reside within the "interactive" namespace.
getExprNames :: REPL [String] Source #
Get visible variable names. This is used for command line completition.
getTypeNames :: REPL [String] Source #
Get visible type signature names. This is used for command line completition.
getPropertyNames :: REPL ([(Name, Decl)], NameDisp) Source #
Return a list of property names, sorted by position in the file. Only properties defined in the current module are returned, including private properties in the current module. Imported properties are not returned.
getModNames :: REPL [ModName] Source #
data LoadedModule Source #
This indicates what the user would like to work on.
Constructors
LoadedModule | |
getLoadedMod :: REPL (Maybe LoadedModule) Source #
setLoadedMod :: LoadedModule -> REPL () Source #
Set the name of the currently focused file, loaded via :r
.
clearLoadedMod :: REPL () Source #
setEditPath :: FilePath -> REPL () Source #
Set the path for the ':e' command. Note that this does not change the focused module (i.e., what ":r" reloads)
clearEditPath :: REPL () Source #
setSearchPath :: [FilePath] -> REPL () Source #
prependSearchPath :: [FilePath] -> REPL () Source #
unlessBatch :: REPL () -> REPL () Source #
asBatch :: REPL a -> REPL a Source #
Run a computation in batch mode, restoring the previous isBatch flag afterwards
validEvalContext :: FreeVars a => a -> REPL () Source #
Is evaluation enabled? If the currently focused module is parameterized, then we cannot evaluate.
updateREPLTitle :: REPL () Source #
Update the title
setUpdateREPLTitle :: REPL () -> REPL () Source #
Set the function that will be called when updating the title
setRandomGen :: TFGen -> REPL () Source #
getRandomGen :: REPL TFGen Source #
getModuleInput :: REPL (ModuleInput IO) Source #
Config Options
data OptionDescr Source #
Constructors
OptionDescr | |
getUser :: String -> REPL EnvVal Source #
Get a user option, when it's known to exist. Fail with panic when it doesn't.
getKnownUser :: IsEnvVal a => String -> REPL a Source #
userOptions :: OptionMap Source #
userOptionsWithAliases :: OptionMap Source #
parseFieldOrder :: String -> Maybe FieldOrder Source #
parseSearchPath :: String -> [String] Source #
Configurable Output
Smoke Test
REPL RW Environment.
Constructors
RW | |
Fields
|