Copyright | (c) 2013-2016 Galois Inc. |
---|---|
License | BSD3 |
Maintainer | cryptol@galois.com |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Cryptol.ModuleSystem.Monad
Description
Synopsis
- data ImportSource
- importedModule :: ImportSource -> ModName
- data ModuleError
- = ModuleNotFound ModName [FilePath]
- | CantFindFile FilePath
- | BadUtf8 ModulePath Fingerprint UnicodeException
- | OtherIOError FilePath IOException
- | ModuleParseError ModulePath Fingerprint ParseError
- | RecursiveModules [ImportSource]
- | RenamerErrors ImportSource [RenamerError]
- | NoPatErrors ImportSource [Error]
- | ExpandPropGuardsError ImportSource Error
- | NoIncludeErrors ImportSource [IncludeError]
- | TypeCheckingFailed ImportSource NameMap [(Range, Error)]
- | OtherFailure String
- | ModuleNameMismatch ModName (Located ModName)
- | DuplicateModuleName ModName FilePath FilePath
- | FFILoadErrors ModName [FFILoadError]
- | ConfigLoadError ConfigLoadError
- | ErrorInFile ModulePath ModuleError
- moduleNotFound :: ModName -> [FilePath] -> ModuleM a
- cantFindFile :: FilePath -> ModuleM a
- badUtf8 :: ModulePath -> Fingerprint -> UnicodeException -> ModuleM a
- otherIOError :: FilePath -> IOException -> ModuleM a
- moduleParseError :: ModulePath -> Fingerprint -> ParseError -> ModuleM a
- recursiveModules :: [ImportSource] -> ModuleM a
- renamerErrors :: [RenamerError] -> ModuleM a
- noPatErrors :: [Error] -> ModuleM a
- expandPropGuardsError :: Error -> ModuleM a
- noIncludeErrors :: [IncludeError] -> ModuleM a
- typeCheckingFailed :: NameMap -> [(Range, Error)] -> ModuleM a
- moduleNameMismatch :: ModName -> Located ModName -> ModuleM a
- duplicateModuleName :: ModName -> FilePath -> FilePath -> ModuleM a
- ffiLoadErrors :: ModName -> [FFILoadError] -> ModuleM a
- errorInFile :: ModulePath -> ModuleM a -> ModuleM a
- tryModule :: ModuleM a -> ModuleM (Either ModuleError a)
- data ModuleWarning
- warn :: [ModuleWarning] -> ModuleM ()
- typeCheckWarnings :: NameMap -> [(Range, Warning)] -> ModuleM ()
- renamerWarnings :: [RenamerWarning] -> ModuleM ()
- data RO m = RO {
- roLoading :: [ImportSource]
- roEvalOpts :: m EvalOpts
- roCallStacks :: Bool
- roFileReader :: FilePath -> m ByteString
- roTCSolver :: Solver
- emptyRO :: ModuleInput m -> RO m
- newtype ModuleT m a = ModuleT {
- unModuleT :: ReaderT (RO m) (StateT ModuleEnv (ExceptionT ModuleError (WriterT [ModuleWarning] m))) a
- data ModuleInput m = ModuleInput {
- minpCallStacks :: Bool
- minpEvalOpts :: m EvalOpts
- minpByteReader :: FilePath -> m ByteString
- minpModuleEnv :: ModuleEnv
- minpTCSolver :: Solver
- runModuleT :: Monad m => ModuleInput m -> ModuleT m a -> m (Either ModuleError (a, ModuleEnv), [ModuleWarning])
- type ModuleM = ModuleT IO
- runModuleM :: ModuleInput IO -> ModuleM a -> IO (Either ModuleError (a, ModuleEnv), [ModuleWarning])
- io :: BaseM m IO => IO a -> ModuleT m a
- getByteReader :: Monad m => ModuleT m (FilePath -> m ByteString)
- getCallStacks :: Monad m => ModuleT m Bool
- readBytes :: Monad m => FilePath -> ModuleT m ByteString
- getModuleEnv :: Monad m => ModuleT m ModuleEnv
- getTCSolver :: Monad m => ModuleT m Solver
- setModuleEnv :: Monad m => ModuleEnv -> ModuleT m ()
- modifyModuleEnv :: Monad m => (ModuleEnv -> ModuleEnv) -> ModuleT m ()
- getLoadedMaybe :: ModName -> ModuleM (Maybe (LoadedModuleG TCTopEntity))
- isLoaded :: ModName -> ModuleM Bool
- isLoadedStrict :: ModName -> ModulePath -> ModuleM Bool
- loadingImport :: Located Import -> ModuleM a -> ModuleM a
- loadingModule :: ModName -> ModuleM a -> ModuleM a
- loadingModInstance :: Located ModName -> ModuleM a -> ModuleM a
- interactive :: ModuleM a -> ModuleM a
- loading :: ImportSource -> ModuleM a -> ModuleM a
- getImportSource :: ModuleM ImportSource
- getIfaces :: ModuleM (Map ModName (Either ModParamNames Iface))
- getLoaded :: ModName -> ModuleM Module
- getAllLoaded :: ModuleM (ModName -> Maybe (ModuleG (), IfaceG ()))
- getAllLoadedSignatures :: ModuleM (ModName -> Maybe ModParamNames)
- getNameSeeds :: ModuleM NameSeeds
- getSupply :: ModuleM Supply
- getMonoBinds :: ModuleM Bool
- getEvalForeignPolicy :: ModuleM EvalForeignPolicy
- setMonoBinds :: Bool -> ModuleM ()
- setNameSeeds :: NameSeeds -> ModuleM ()
- setSupply :: Supply -> ModuleM ()
- unloadModule :: (forall a. LoadedModuleG a -> Bool) -> ModuleM ()
- loadedModule :: ModulePath -> FileInfo -> NamingEnv -> Maybe ForeignSrc -> TCTopEntity -> ModuleM ()
- modifyEvalEnvM :: Traversable t => (EvalEnv -> Eval (t EvalEnv)) -> ModuleM (t ())
- modifyEvalEnv :: (EvalEnv -> Eval EvalEnv) -> ModuleM ()
- getEvalEnv :: ModuleM EvalEnv
- getEvalOptsAction :: ModuleM (IO EvalOpts)
- getEvalOpts :: ModuleM EvalOpts
- getNominalTypes :: ModuleM (Map Name NominalType)
- getFocusedModule :: ModuleM (Maybe (ImpName Name))
- setFocusedModule :: ImpName Name -> ModuleM ()
- setMaybeFocusedModule :: Maybe (ImpName Name) -> ModuleM ()
- getSearchPath :: ModuleM [FilePath]
- withPrependedSearchPath :: [FilePath] -> ModuleM a -> ModuleM a
- getFocusedEnv :: ModuleM ModContext
- getDynEnv :: ModuleM DynamicEnv
- setDynEnv :: DynamicEnv -> ModuleM ()
- withLogger :: (Logger -> a -> IO b) -> a -> ModuleM b
Documentation
data ImportSource Source #
Constructors
FromModule ModName | |
FromImport (Located Import) | |
FromSigImport (Located ModName) | |
FromModuleInstance (Located ModName) |
Instances
importedModule :: ImportSource -> ModName Source #
data ModuleError Source #
Constructors
ModuleNotFound ModName [FilePath] | Unable to find the module given, tried looking in these paths |
CantFindFile FilePath | Unable to open a file |
BadUtf8 ModulePath Fingerprint UnicodeException | Bad UTF-8 encoding in while decoding this file |
OtherIOError FilePath IOException | Some other IO error occurred while reading this file |
ModuleParseError ModulePath Fingerprint ParseError | Generated this parse error when parsing the file for module m |
RecursiveModules [ImportSource] | Recursive module group discovered |
RenamerErrors ImportSource [RenamerError] | Problems during the renaming phase |
NoPatErrors ImportSource [Error] | Problems during the NoPat phase |
ExpandPropGuardsError ImportSource Error | Problems during the ExpandPropGuards phase |
NoIncludeErrors ImportSource [IncludeError] | Problems during the NoInclude phase |
TypeCheckingFailed ImportSource NameMap [(Range, Error)] | Problems during type checking |
OtherFailure String | Problems after type checking, eg. specialization |
ModuleNameMismatch ModName (Located ModName) | Module loaded by 'import' statement has the wrong module name |
DuplicateModuleName ModName FilePath FilePath | Two modules loaded from different files have the same module name |
FFILoadErrors ModName [FFILoadError] | Errors loading foreign function implementations |
ConfigLoadError ConfigLoadError | |
ErrorInFile ModulePath ModuleError | This is just a tag on the error, indicating the file containing it. It is convenient when we had to look for the module, and we'd like to communicate the location of the problematic module to the handler. |
Instances
Show ModuleError Source # | |
Defined in Cryptol.ModuleSystem.Monad Methods showsPrec :: Int -> ModuleError -> ShowS # show :: ModuleError -> String # showList :: [ModuleError] -> ShowS # | |
PP ModuleError Source # | |
Defined in Cryptol.ModuleSystem.Monad | |
NFData ModuleError Source # | |
Defined in Cryptol.ModuleSystem.Monad Methods rnf :: ModuleError -> () # |
cantFindFile :: FilePath -> ModuleM a Source #
badUtf8 :: ModulePath -> Fingerprint -> UnicodeException -> ModuleM a Source #
otherIOError :: FilePath -> IOException -> ModuleM a Source #
moduleParseError :: ModulePath -> Fingerprint -> ParseError -> ModuleM a Source #
recursiveModules :: [ImportSource] -> ModuleM a Source #
renamerErrors :: [RenamerError] -> ModuleM a Source #
noPatErrors :: [Error] -> ModuleM a Source #
expandPropGuardsError :: Error -> ModuleM a Source #
noIncludeErrors :: [IncludeError] -> ModuleM a Source #
ffiLoadErrors :: ModName -> [FFILoadError] -> ModuleM a Source #
errorInFile :: ModulePath -> ModuleM a -> ModuleM a Source #
Run the computation, and if it caused and error, tag the error with the given file.
data ModuleWarning Source #
Constructors
TypeCheckWarnings NameMap [(Range, Warning)] | |
RenamerWarnings [RenamerWarning] |
Instances
warn :: [ModuleWarning] -> ModuleM () Source #
renamerWarnings :: [RenamerWarning] -> ModuleM () Source #
Constructors
RO | |
Fields
|
emptyRO :: ModuleInput m -> RO m Source #
Constructors
ModuleT | |
Fields
|
Instances
MonadT ModuleT Source # | |
Defined in Cryptol.ModuleSystem.Monad | |
MonadFail m => MonadFail (ModuleT m) Source # | |
Defined in Cryptol.ModuleSystem.Monad | |
MonadIO m => MonadIO (ModuleT m) Source # | |
Defined in Cryptol.ModuleSystem.Monad | |
Monad m => Applicative (ModuleT m) Source # | |
Defined in Cryptol.ModuleSystem.Monad | |
Monad m => Functor (ModuleT m) Source # | |
Monad m => Monad (ModuleT m) Source # | |
Monad m => FreshM (ModuleT m) Source # | |
Defined in Cryptol.ModuleSystem.Monad |
data ModuleInput m Source #
Constructors
ModuleInput | |
Fields
|
runModuleT :: Monad m => ModuleInput m -> ModuleT m a -> m (Either ModuleError (a, ModuleEnv), [ModuleWarning]) Source #
runModuleM :: ModuleInput IO -> ModuleM a -> IO (Either ModuleError (a, ModuleEnv), [ModuleWarning]) Source #
getByteReader :: Monad m => ModuleT m (FilePath -> m ByteString) Source #
getLoadedMaybe :: ModName -> ModuleM (Maybe (LoadedModuleG TCTopEntity)) Source #
isLoaded :: ModName -> ModuleM Bool Source #
This checks if the given name is loaded---it might refer to either a module or a signature.
isLoadedStrict :: ModName -> ModulePath -> ModuleM Bool Source #
interactive :: ModuleM a -> ModuleM a Source #
Push an "interactive" context onto the loading stack. A bit of a hack, as it uses a faked module name
getImportSource :: ModuleM ImportSource Source #
Get the currently focused import source.
setMonoBinds :: Bool -> ModuleM () Source #
setNameSeeds :: NameSeeds -> ModuleM () Source #
unloadModule :: (forall a. LoadedModuleG a -> Bool) -> ModuleM () Source #
loadedModule :: ModulePath -> FileInfo -> NamingEnv -> Maybe ForeignSrc -> TCTopEntity -> ModuleM () Source #
modifyEvalEnvM :: Traversable t => (EvalEnv -> Eval (t EvalEnv)) -> ModuleM (t ()) Source #
getSearchPath :: ModuleM [FilePath] Source #
withPrependedSearchPath :: [FilePath] -> ModuleM a -> ModuleM a Source #
Run a ModuleM
action in a context with a prepended search
path. Useful for temporarily looking in other places while
resolving imports, for example.
setDynEnv :: DynamicEnv -> ModuleM () Source #