Agda-2.5.2: A dependently typed functional programming language and proof assistant

Safe HaskellNone
LanguageHaskell2010

Agda.Interaction.Imports

Description

This module deals with finding imported modules and loading their interface files.

Synopsis

Documentation

data MainInterface Source #

Are we loading the interface for the user-loaded file or for an import?

Constructors

MainInterface

Interface for main file.

NotMainInterface

Interface for imported file.

mergeInterface :: Interface -> TCM () Source #

Merge an interface into the current proof state.

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 #

Constructors

NoWarnings 
SomeWarnings a 

Instances

Functor MaybeWarnings' Source # 

Methods

fmap :: (a -> b) -> MaybeWarnings' a -> MaybeWarnings' b #

(<$) :: a -> MaybeWarnings' b -> MaybeWarnings' a #

Foldable MaybeWarnings' Source # 

Methods

fold :: Monoid m => MaybeWarnings' m -> m #

foldMap :: Monoid m => (a -> m) -> MaybeWarnings' a -> m #

foldr :: (a -> b -> b) -> b -> MaybeWarnings' a -> b #

foldr' :: (a -> b -> b) -> b -> MaybeWarnings' a -> b #

foldl :: (b -> a -> b) -> b -> MaybeWarnings' a -> b #

foldl' :: (b -> a -> b) -> b -> MaybeWarnings' a -> b #

foldr1 :: (a -> a -> a) -> MaybeWarnings' a -> a #

foldl1 :: (a -> a -> a) -> MaybeWarnings' a -> a #

toList :: MaybeWarnings' a -> [a] #

null :: MaybeWarnings' a -> Bool #

length :: MaybeWarnings' a -> Int #

elem :: Eq a => a -> MaybeWarnings' a -> Bool #

maximum :: Ord a => MaybeWarnings' a -> a #

minimum :: Ord a => MaybeWarnings' a -> a #

sum :: Num a => MaybeWarnings' a -> a #

product :: Num a => MaybeWarnings' a -> a #

Traversable MaybeWarnings' Source # 

Methods

traverse :: Applicative f => (a -> f b) -> MaybeWarnings' a -> f (MaybeWarnings' b) #

sequenceA :: Applicative f => MaybeWarnings' (f a) -> f (MaybeWarnings' a) #

mapM :: Monad m => (a -> m b) -> MaybeWarnings' a -> m (MaybeWarnings' b) #

sequence :: Monad m => MaybeWarnings' (m a) -> m (MaybeWarnings' a) #

Null a => Null (MaybeWarnings' a) Source # 

alreadyVisited :: TopLevelModuleName -> 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.

typeCheckMain :: AbsolutePath -> TCM (Interface, MaybeWarnings) Source #

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.

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.

getInterface' Source #

Arguments

:: TopLevelModuleName 
-> MainInterface

If type checking is necessary, should all state changes inflicted by createInterface be preserved? Yes, if we are the MainInterface. No, if we are NotMainInterface.

-> TCM (Interface, MaybeWarnings) 

A more precise variant of getInterface. If warnings are encountered then they are returned instead of being turned into errors.

isCached Source #

Arguments

:: TopLevelModuleName

Module name of file we process.

-> AbsolutePath

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).

getStoredInterface Source #

Arguments

:: TopLevelModuleName

Module name of file we process.

-> AbsolutePath

File we process.

-> Bool

If type checking is necessary, should all state changes inflicted by createInterface be preserved? True, if we are the MainInterface. False, if we are NotMainInterface.

-> TCM (Bool, (Interface, MaybeWarnings))

Bool is: do we have to merge the interface?

Try to get the interface from interface file or cache.

typeCheck Source #

Arguments

:: TopLevelModuleName

Module name of file we process.

-> AbsolutePath

File we process.

-> Bool

If type checking is necessary, should all state changes inflicted by createInterface be preserved? True, if we are the MainInterface. False, if we are NotMainInterface.

-> TCM (Bool, (Interface, MaybeWarnings))

Bool is: do we have to merge the interface?

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.

chaseMsg Source #

Arguments

:: String

The prefix, like Checking, Finished, Skipping.

-> TopLevelModuleName

The module name.

-> Maybe String

Optionally: the file name.

-> TCM () 

Formats and outputs the Checking, Finished and Skipping messages.

highlightFromInterface Source #

Arguments

:: Interface 
-> AbsolutePath

The corresponding file.

-> TCM () 

Print the highlighting information contained in the given interface.

writeInterface :: FilePath -> Interface -> TCM () Source #

Writes the given interface to the given file.

createInterface Source #

Arguments

:: AbsolutePath

The file to type check.

-> TopLevelModuleName

The expected module name.

-> Bool 
-> 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.

data WhichWarnings Source #

Collect all warnings that have accumulated in the state. Depending on the argument, we either respect the flags passed in by the user, or not (for instance when deciding if we are writing an interface file or not)

Constructors

ErrorWarnings 
AllWarnings

order of constructors important for derived Ord instance

buildInterface Source #

Arguments

:: AbsolutePath 
-> TopLevelInfo

TopLevelInfo for the current module.

-> HighlightingInfo

Syntax highlighting info for the module.

-> Set String

MAlonzo: Haskell modules imported in imported modules (transitively).

-> Set String

UHC backend: Haskell modules imported in imported modules (transitively).

-> [OptionsPragma]

Options set in OPTIONS pragmas.

-> TCM Interface 

Builds an interface for the current module, which should already have been successfully type checked.

getInterfaceFileHashes :: FilePath -> TCM (Maybe (Hash, Hash)) Source #

Returns (iSourceHash, iFullHash)

isNewerThan :: FilePath -> FilePath -> IO Bool Source #

True if the first file is newer than the second file. If a file doesn't exist it is considered to be infinitely old.