Safe Haskell | None |
---|---|
Language | Haskell2010 |
- computeInterfaces :: (MonadModule m, ModuleInfo m ~ [Symbol], Data l, SrcInfo l, Ord l) => Language -> [Extension] -> [Module l] -> m (Set (Error l))
- getInterfaces :: (MonadModule m, ModuleInfo m ~ [Symbol], Data l, SrcInfo l, Ord l) => Language -> [Extension] -> [Module l] -> m ([[Symbol]], Set (Error l))
- annotateModule :: (MonadModule m, ModuleInfo m ~ [Symbol], Data l, SrcInfo l, Eq l) => Language -> [Extension] -> Module l -> m (Module (Scoped l))
- data Symbol
- = Value { }
- | Method { }
- | Selector {
- symbolModule :: ModuleName
- symbolName :: Name
- typeName :: Name
- constructors :: [Name]
- | Constructor {
- symbolModule :: ModuleName
- symbolName :: Name
- typeName :: Name
- | Type { }
- | Data { }
- | NewType { }
- | TypeFam { }
- | DataFam { }
- | Class { }
- data Scoped l = Scoped (NameInfo l) l
- data NameInfo l
- = GlobalSymbol Symbol QName
- | LocalValue SrcLoc
- | TypeVar SrcLoc
- | ValueBinder
- | TypeBinder
- | Import (Map QName [Symbol])
- | ImportPart [Symbol]
- | Export [Symbol]
- | RecPatWildcard [Symbol]
- | RecExpWildcard [(Name, NameInfo l)]
- | None
- | ScopeError (Error l)
- data Error l
- = ENotInScope (QName l)
- | EAmbiguous (QName l) [Symbol]
- | ETypeAsClass (QName l)
- | EClassAsType (QName l)
- | ENotExported (Maybe (Name l)) (Name l) (ModuleName l)
- | EModNotFound (ModuleName l)
- | EInternal String
- ppError :: SrcInfo l => Error l -> String
- ppSymbol :: Symbol -> String
Core functions
:: (MonadModule m, ModuleInfo m ~ [Symbol], Data l, SrcInfo l, Ord l) | |
=> Language | base language |
-> [Extension] | global extensions (e.g. specified on the command line) |
-> [Module l] | input modules |
-> m (Set (Error l)) | errors in export or import lists |
computeInterfaces
takes a list of possibly recursive modules and
computes the interface of each module. The computed interfaces are
written into the m
's cache and are available to further computations
in this monad.
Returns the set of import/export errors. Note that the interfaces are registered in the cache regardless of whether there are any errors, but if there are errors, the interfaces may be incomplete.
:: (MonadModule m, ModuleInfo m ~ [Symbol], Data l, SrcInfo l, Ord l) | |
=> Language | base language |
-> [Extension] | global extensions (e.g. specified on the command line) |
-> [Module l] | input modules |
-> m ([[Symbol]], Set (Error l)) | output modules, and errors in export or import lists |
Like computeInterfaces
, but also returns a list of interfaces, one
per module and in the same order
:: (MonadModule m, ModuleInfo m ~ [Symbol], Data l, SrcInfo l, Eq l) | |
=> Language | base language |
-> [Extension] | global extensions (e.g. specified on the command line) |
-> Module l | input module |
-> m (Module (Scoped l)) | output (annotated) module |
Annotate a module with scoping information. This assumes that all
module dependencies have been resolved and cached — usually you need
to run computeInterfaces
first, unless you have one module in
isolation.
Types
Information about an entity. Carries at least the module it was originally declared in and its name.
Value | value or function |
| |
Method | class method |
| |
Selector | record field selector |
| |
Constructor | data constructor |
| |
Type | type synonym |
| |
Data | data type |
| |
NewType | newtype |
| |
TypeFam | type family |
| |
DataFam | data family |
| |
Class | type class |
|
A pair of the name information and original annotation. Used as an annotation type for AST.
Information about the names used in an AST.
GlobalSymbol Symbol QName | global entitiy and the way it is referenced |
LocalValue SrcLoc | local value, and location where it is bound |
TypeVar SrcLoc | type variable, and location where it is bound |
ValueBinder | here the value name is bound |
TypeBinder | here the type name is defined |
Import (Map QName [Symbol]) |
|
ImportPart [Symbol] | part of an |
Export [Symbol] | part of an |
RecPatWildcard [Symbol] | wildcard in a record pattern. The list contains resolved names of the fields that are brought in scope by this pattern. |
RecExpWildcard [(Name, NameInfo l)] | wildcard in a record construction expression. The list contains resolved names of the fields and information about values assigned to those fields. |
None | no annotation |
ScopeError (Error l) | scope error |
Errors during name resolution.
ENotInScope (QName l) | name is not in scope |
EAmbiguous (QName l) [Symbol] | name is ambiguous |
ETypeAsClass (QName l) | type is used where a type class is expected |
EClassAsType (QName l) | type class is used where a type is expected |
ENotExported (Maybe (Name l)) (Name l) (ModuleName l) | Attempt to explicitly import a name which is not exported (or, possibly, does not even exist). For example: import Prelude(Bool(Right)) The fields are:
|
EModNotFound (ModuleName l) | module not found |
EInternal String | internal error |