Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module deals with finding imported modules and loading their interface files.
Synopsis
- data SourceInfo = SourceInfo {}
- sourceInfo :: SourceFile -> TCM SourceInfo
- data Mode
- data MainInterface
- includeStateChanges :: MainInterface -> Bool
- mergeInterface :: Interface -> TCM ()
- addImportedThings :: Signature -> BuiltinThings PrimFun -> PatternSynDefns -> DisplayForms -> Map QName String -> Set QName -> [TCWarning] -> TCM ()
- scopeCheckImport :: ModuleName -> TCM (ModuleName, Map ModuleName Scope)
- data MaybeWarnings' a
- = NoWarnings
- | SomeWarnings a
- type MaybeWarnings = MaybeWarnings' [TCWarning]
- applyFlagsToMaybeWarnings :: MaybeWarnings -> TCM MaybeWarnings
- hasWarnings :: MaybeWarnings -> Bool
- alreadyVisited :: TopLevelModuleName -> MainInterface -> PragmaOptions -> TCM (Interface, MaybeWarnings) -> TCM (Interface, MaybeWarnings)
- typeCheckMain :: SourceFile -> Mode -> SourceInfo -> TCM (Interface, MaybeWarnings)
- getInterface :: ModuleName -> TCM Interface
- getInterface_ :: TopLevelModuleName -> Maybe SourceInfo -> TCM Interface
- getInterface' :: TopLevelModuleName -> MainInterface -> Maybe SourceInfo -> TCM (Interface, MaybeWarnings)
- checkOptionsCompatible :: PragmaOptions -> PragmaOptions -> ModuleName -> TCM Bool
- isCached :: TopLevelModuleName -> SourceFile -> MaybeT TCM Interface
- getStoredInterface :: TopLevelModuleName -> SourceFile -> MainInterface -> Maybe SourceInfo -> TCM (Bool, (Interface, MaybeWarnings))
- typeCheck :: TopLevelModuleName -> SourceFile -> MainInterface -> Maybe SourceInfo -> TCM (Bool, (Interface, MaybeWarnings))
- chaseMsg :: String -> TopLevelModuleName -> Maybe String -> TCM ()
- highlightFromInterface :: Interface -> SourceFile -> TCM ()
- readInterface :: AbsolutePath -> TCM (Maybe Interface)
- readInterface' :: InterfaceFile -> TCM (Maybe Interface)
- writeInterface :: AbsolutePath -> Interface -> TCM Interface
- removePrivates :: ScopeInfo -> ScopeInfo
- concreteOptionsToOptionPragmas :: [Pragma] -> TCM [OptionsPragma]
- createInterface :: SourceFile -> TopLevelModuleName -> MainInterface -> Maybe SourceInfo -> TCM (Interface, MaybeWarnings)
- getUniqueMetasRanges :: [MetaId] -> TCM [Range]
- getUnsolvedMetas :: TCM [Range]
- getAllUnsolved :: TCM [TCWarning]
- getAllWarnings :: WhichWarnings -> TCM [TCWarning]
- getAllWarnings' :: MainInterface -> WhichWarnings -> TCM [TCWarning]
- getMaybeWarnings :: WhichWarnings -> TCM MaybeWarnings
- getMaybeWarnings' :: MainInterface -> WhichWarnings -> TCM MaybeWarnings
- getAllWarningsOfTCErr :: TCErr -> TCM [TCWarning]
- constructIScope :: Interface -> Interface
- buildInterface :: Text -> FileType -> TopLevelInfo -> [OptionsPragma] -> TCM Interface
- getInterfaceFileHashes :: AbsolutePath -> TCM (Maybe (Hash, Hash))
- getInterfaceFileHashes' :: InterfaceFile -> TCM (Maybe (Hash, Hash))
- moduleHash :: ModuleName -> TCM Hash
- isNewerThan :: FilePath -> FilePath -> IO Bool
Documentation
data SourceInfo Source #
Some information about the source code.
SourceInfo | |
|
sourceInfo :: SourceFile -> TCM SourceInfo Source #
Computes a SourceInfo
record for the given file.
Is the aim to type-check the top-level module, or only to scope-check it?
data MainInterface Source #
Are we loading the interface for the user-loaded file or for an import?
MainInterface Mode | For the main file. In this case state changes inflicted by
|
NotMainInterface | For an imported file. In this case state changes inflicted by
|
Instances
Eq MainInterface Source # | |
Defined in Agda.Interaction.Imports (==) :: MainInterface -> MainInterface -> Bool # (/=) :: MainInterface -> MainInterface -> Bool # | |
Show MainInterface Source # | |
Defined in Agda.Interaction.Imports showsPrec :: Int -> MainInterface -> ShowS # show :: MainInterface -> String # showList :: [MainInterface] -> ShowS # |
includeStateChanges :: MainInterface -> Bool Source #
Should state changes inflicted by createInterface
be preserved?
mergeInterface :: Interface -> TCM () Source #
Merge an interface into the current proof state.
:: Signature | |
-> BuiltinThings PrimFun | |
-> PatternSynDefns | |
-> DisplayForms | |
-> Map QName String | Imported user warnings |
-> Set QName | Name of imported definitions which are partial |
-> [TCWarning] | |
-> TCM () |
scopeCheckImport :: ModuleName -> TCM (ModuleName, Map ModuleName Scope) Source #
Scope checks the given module. A proper version of the module name (with correct definition sites) is returned.
data MaybeWarnings' a Source #
Instances
type MaybeWarnings = MaybeWarnings' [TCWarning] Source #
hasWarnings :: MaybeWarnings -> Bool Source #
alreadyVisited :: TopLevelModuleName -> MainInterface -> PragmaOptions -> TCM (Interface, MaybeWarnings) -> TCM (Interface, MaybeWarnings) Source #
If the module has already been visited (without warnings), then
its interface is returned directly. Otherwise the computation is
used to find the interface and the computed interface is stored for
potential later use (unless the MainInterface
is
).MainInterface
ScopeCheck
:: SourceFile | The path to the file. |
-> Mode | Should the file be type-checked, or only scope-checked? |
-> SourceInfo | Information about the source code. |
-> TCM (Interface, MaybeWarnings) |
Type checks the main file of the interaction. This could be the file loaded in the interacting editor (emacs), or the file passed on the command line.
First, the primitive modules are imported.
Then, getInterface'
is called to do the main work.
If the Mode
is ScopeCheck
, then type-checking is not
performed, only scope-checking. (This may include type-checking
of imported modules.) In this case the generated, partial
interface is not stored in the state (stDecodedModules
). Note,
however, that if the file has already been type-checked, then a
complete interface is returned.
getInterface :: ModuleName -> TCM Interface Source #
Tries to return the interface associated to the given (imported) module. The time stamp of the relevant interface file is also returned. Calls itself recursively for the imports of the given module. May type check the module. An error is raised if a warning is encountered.
Do not use this for the main file, use typeCheckMain
instead.
:: TopLevelModuleName | |
-> Maybe SourceInfo | Optional information about the source code. |
-> TCM Interface |
See getInterface
.
:: TopLevelModuleName | |
-> MainInterface | |
-> Maybe SourceInfo | Optional information about the source code. |
-> TCM (Interface, MaybeWarnings) |
A more precise variant of getInterface
. If warnings are
encountered then they are returned instead of being turned into
errors.
checkOptionsCompatible :: PragmaOptions -> PragmaOptions -> ModuleName -> TCM Bool Source #
Check if the options used for checking an imported module are compatible with the current options. Raises Non-fatal errors if not.
:: TopLevelModuleName | Module name of file we process. |
-> SourceFile | File we process. |
-> MaybeT TCM Interface |
Check whether interface file exists and is in cache in the correct version (as testified by the interface file hash).
:: TopLevelModuleName | Module name of file we process. |
-> SourceFile | File we process. |
-> MainInterface | |
-> Maybe SourceInfo | Optional information about the source code. |
-> TCM (Bool, (Interface, MaybeWarnings)) |
|
Try to get the interface from interface file or cache.
:: TopLevelModuleName | Module name of file we process. |
-> SourceFile | File we process. |
-> MainInterface | |
-> Maybe SourceInfo | Optional information about the source code. |
-> TCM (Bool, (Interface, MaybeWarnings)) |
|
Run the type checker on a file and create an interface.
Mostly, this function calls createInterface
.
But if it is not the main module we check,
we do it in a fresh state, suitably initialize,
in order to forget some state changes after successful type checking.
:: String | The prefix, like |
-> TopLevelModuleName | The module name. |
-> Maybe String | Optionally: the file name. |
-> TCM () |
highlightFromInterface Source #
:: Interface | |
-> SourceFile | The corresponding file. |
-> TCM () |
Print the highlighting information contained in the given interface.
readInterface :: AbsolutePath -> TCM (Maybe Interface) Source #
Read interface file corresponding to a module.
readInterface' :: InterfaceFile -> TCM (Maybe Interface) Source #
writeInterface :: AbsolutePath -> Interface -> TCM Interface Source #
Writes the given interface to the given file.
The written interface is decoded and returned.
removePrivates :: ScopeInfo -> ScopeInfo Source #
concreteOptionsToOptionPragmas :: [Pragma] -> TCM [OptionsPragma] Source #
:: SourceFile | The file to type check. |
-> TopLevelModuleName | The expected module name. |
-> MainInterface | Are we dealing with the main module? |
-> Maybe SourceInfo | Optional information about the source code. |
-> TCM (Interface, MaybeWarnings) |
Tries to type check a module and write out its interface. The function only writes out an interface file if it does not encounter any warnings.
If appropriate this function writes out syntax highlighting information.
getUnsolvedMetas :: TCM [Range] Source #
getAllUnsolved :: TCM [TCWarning] Source #
getAllWarnings :: WhichWarnings -> TCM [TCWarning] Source #
Collect all warnings that have accumulated in the state.
getAllWarnings' :: MainInterface -> WhichWarnings -> TCM [TCWarning] Source #
Expert version of getAllWarnings
; if isMain
is a
MainInterface
, the warnings definitely include also unsolved
warnings.
constructIScope :: Interface -> Interface Source #
Reconstruct the iScope
(not serialized)
from the iInsideScope
(serialized).
:: Text | Source code. |
-> FileType | Agda file? Literate Agda file? |
-> TopLevelInfo |
|
-> [OptionsPragma] | Options set in |
-> TCM Interface |
Builds an interface for the current module, which should already have been successfully type checked.
getInterfaceFileHashes :: AbsolutePath -> TCM (Maybe (Hash, Hash)) Source #
Returns (iSourceHash, iFullHash)
We do not need to check that the file exist because we only
accept InterfaceFile
as an input and not arbitrary AbsolutePath
!
getInterfaceFileHashes' :: InterfaceFile -> TCM (Maybe (Hash, Hash)) Source #
moduleHash :: ModuleName -> TCM Hash Source #