cryptol-2.9.0: Cryptol: The Language of Cryptography

Copyright(c) 2013-2016 Galois Inc.
LicenseBSD3
Maintainercryptol@galois.com
Stabilityprovisional
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Cryptol.ModuleSystem.Monad

Description

 
Synopsis

Documentation

data ImportSource Source #

Instances
Eq ImportSource Source # 
Instance details

Defined in Cryptol.ModuleSystem.Monad

Show ImportSource Source # 
Instance details

Defined in Cryptol.ModuleSystem.Monad

Generic ImportSource Source # 
Instance details

Defined in Cryptol.ModuleSystem.Monad

Associated Types

type Rep ImportSource :: Type -> Type #

NFData ImportSource Source # 
Instance details

Defined in Cryptol.ModuleSystem.Monad

Methods

rnf :: ImportSource -> () #

PP ImportSource Source # 
Instance details

Defined in Cryptol.ModuleSystem.Monad

Methods

ppPrec :: Int -> ImportSource -> Doc Source #

type Rep ImportSource Source # 
Instance details

Defined in Cryptol.ModuleSystem.Monad

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 UnicodeException

Bad UTF-8 encoding in while decoding this file

OtherIOError FilePath IOException

Some other IO error occurred while reading this file

ModuleParseError ModulePath 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

NoIncludeErrors ImportSource [IncludeError]

Problems during the NoInclude phase

TypeCheckingFailed ImportSource [(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

ImportedParamModule ModName

Attempt to import a parametrized module that was not instantiated.

FailedToParameterizeModDefs ModName [Name]

Failed to add the module parameters to all definitions in a module.

NotAParameterizedModule ModName 
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 pthe problematic module to the handler.

Instances
Show ModuleError Source # 
Instance details

Defined in Cryptol.ModuleSystem.Monad

NFData ModuleError Source # 
Instance details

Defined in Cryptol.ModuleSystem.Monad

Methods

rnf :: ModuleError -> () #

PP ModuleError Source # 
Instance details

Defined in Cryptol.ModuleSystem.Monad

Methods

ppPrec :: Int -> ModuleError -> Doc 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 #

Instances
Show ModuleWarning Source # 
Instance details

Defined in Cryptol.ModuleSystem.Monad

Generic ModuleWarning Source # 
Instance details

Defined in Cryptol.ModuleSystem.Monad

Associated Types

type Rep ModuleWarning :: Type -> Type #

NFData ModuleWarning Source # 
Instance details

Defined in Cryptol.ModuleSystem.Monad

Methods

rnf :: ModuleWarning -> () #

PP ModuleWarning Source # 
Instance details

Defined in Cryptol.ModuleSystem.Monad

type Rep ModuleWarning Source # 
Instance details

Defined in Cryptol.ModuleSystem.Monad

type Rep ModuleWarning = D1 (MetaData "ModuleWarning" "Cryptol.ModuleSystem.Monad" "cryptol-2.9.0-4aSi1YZNBynFQwh9aOpllR" False) (C1 (MetaCons "TypeCheckWarnings" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Range, Warning)])) :+: C1 (MetaCons "RenamerWarnings" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [RenamerWarning])))

data RO m Source #

newtype ModuleT m a Source #

Instances
MonadT ModuleT Source # 
Instance details

Defined in Cryptol.ModuleSystem.Monad

Methods

lift :: Monad m => m a -> ModuleT m a #

Monad m => Monad (ModuleT m) Source # 
Instance details

Defined in Cryptol.ModuleSystem.Monad

Methods

(>>=) :: ModuleT m a -> (a -> ModuleT m b) -> ModuleT m b #

(>>) :: ModuleT m a -> ModuleT m b -> ModuleT m b #

return :: a -> ModuleT m a #

fail :: String -> ModuleT m a #

Monad m => Functor (ModuleT m) Source # 
Instance details

Defined in Cryptol.ModuleSystem.Monad

Methods

fmap :: (a -> b) -> ModuleT m a -> ModuleT m b #

(<$) :: a -> ModuleT m b -> ModuleT m a #

MonadFail m => MonadFail (ModuleT m) Source # 
Instance details

Defined in Cryptol.ModuleSystem.Monad

Methods

fail :: String -> ModuleT m a #

Monad m => Applicative (ModuleT m) Source # 
Instance details

Defined in Cryptol.ModuleSystem.Monad

Methods

pure :: a -> ModuleT m a #

(<*>) :: ModuleT m (a -> b) -> ModuleT m a -> ModuleT m b #

liftA2 :: (a -> b -> c) -> ModuleT m a -> ModuleT m b -> ModuleT m c #

(*>) :: ModuleT m a -> ModuleT m b -> ModuleT m b #

(<*) :: ModuleT m a -> ModuleT m b -> ModuleT m a #

MonadIO m => MonadIO (ModuleT m) Source # 
Instance details

Defined in Cryptol.ModuleSystem.Monad

Methods

liftIO :: IO a -> ModuleT m a #

Monad m => FreshM (ModuleT m) Source # 
Instance details

Defined in Cryptol.ModuleSystem.Monad

Methods

liftSupply :: (Supply -> (a, Supply)) -> ModuleT m a Source #

io :: BaseM m IO => IO a -> ModuleT m a 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.

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.

withLogger :: (Logger -> a -> IO b) -> a -> ModuleM b Source #

Usefule for logging. For example: withLogger logPutStrLn Hello