Safe Haskell | None |
---|
- computeInterfaces :: (MonadModule m, ModuleInfo m ~ Symbols, Data l, SrcInfo l, Ord l) => Language -> [Extension] -> [Module l] -> m (Set (Error l))
- getInterfaces :: (MonadModule m, ModuleInfo m ~ Symbols, Data l, SrcInfo l, Ord l) => Language -> [Extension] -> [Module l] -> m ([Symbols], Set (Error l))
- annotateModule :: (MonadModule m, ModuleInfo m ~ Symbols, Data l, SrcInfo l, Eq l) => Language -> [Extension] -> Module l -> m (Module (Scoped l))
- qualifySymbols :: PackageId -> Symbols -> Symbols
- data SymValueInfo name
- = SymValue {
- sv_origName :: name
- sv_fixity :: Maybe SymFixity
- | SymMethod {
- sv_origName :: name
- sv_fixity :: Maybe SymFixity
- sv_className :: name
- | SymSelector {
- sv_origName :: name
- sv_fixity :: Maybe SymFixity
- sv_typeName :: name
- sv_constructors :: [name]
- | SymConstructor {
- sv_origName :: name
- sv_fixity :: Maybe SymFixity
- sv_typeName :: name
- = SymValue {
- data SymTypeInfo name
- = SymType {
- st_origName :: name
- st_fixity :: Maybe SymFixity
- | SymData {
- st_origName :: name
- st_fixity :: Maybe SymFixity
- | SymNewType {
- st_origName :: name
- st_fixity :: Maybe SymFixity
- | SymTypeFam {
- st_origName :: name
- st_fixity :: Maybe SymFixity
- | SymDataFam {
- st_origName :: name
- st_fixity :: Maybe SymFixity
- | SymClass {
- st_origName :: name
- st_fixity :: Maybe SymFixity
- = SymType {
- data Symbols = Symbols (Set (SymValueInfo OrigName)) (Set (SymTypeInfo OrigName))
- data Scoped l = Scoped (NameInfo l) l
- data NameInfo l
- = GlobalValue (SymValueInfo OrigName)
- | GlobalType (SymTypeInfo OrigName)
- | LocalValue SrcLoc
- | TypeVar SrcLoc
- | ValueBinder
- | TypeBinder
- | Import Table
- | ImportPart Symbols
- | Export Symbols
- | RecPatWildcard [OrigName]
- | RecExpWildcard [(OrigName, NameInfo l)]
- | None
- | ScopeError (Error l)
- type NameS = String
- type ModuleNameS = String
- data GName = GName {
- gModule :: ModuleNameS
- gName :: NameS
- ppGName :: GName -> String
- data OrigName = OrigName {}
- ppOrigName :: OrigName -> String
- data Error l
- = ENotInScope (QName l)
- | EAmbiguous (QName l) [OrigName]
- | 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
- type SymFixity = (Assoc (), Int)
- class HasOrigName i where
- origName :: i n -> n
Core functions
:: (MonadModule m, ModuleInfo m ~ Symbols, 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 ~ Symbols, Data l, SrcInfo l, Ord l) | |
=> Language | base language |
-> [Extension] | global extensions (e.g. specified on the command line) |
-> [Module l] | input modules |
-> m ([Symbols], 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 ~ Symbols, 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.
qualifySymbols :: PackageId -> Symbols -> SymbolsSource
Annotate all local symbols with the package name and version
Types
data SymValueInfo name Source
Information about a value-level entitity
SymValue | value or function |
| |
SymMethod | class method |
| |
SymSelector | record field selector |
| |
SymConstructor | data constructor |
|
Functor SymValueInfo | |
Typeable1 SymValueInfo | |
Foldable SymValueInfo | |
Traversable SymValueInfo | |
HasOrigName SymValueInfo | |
Eq name => Eq (SymValueInfo name) | |
Data name => Data (SymValueInfo name) | |
Ord name => Ord (SymValueInfo name) | |
Show name => Show (SymValueInfo name) | |
ToJSON name => ToJSON (SymValueInfo name) | |
FromJSON name => FromJSON (SymValueInfo name) |
data SymTypeInfo name Source
Information about a type-level entitity
SymType | type synonym |
| |
SymData | data type |
| |
SymNewType | newtype |
| |
SymTypeFam | type family |
| |
SymDataFam | data family |
| |
SymClass | type class |
|
Functor SymTypeInfo | |
Typeable1 SymTypeInfo | |
Foldable SymTypeInfo | |
Traversable SymTypeInfo | |
HasOrigName SymTypeInfo | |
Eq name => Eq (SymTypeInfo name) | |
Data name => Data (SymTypeInfo name) | |
Ord name => Ord (SymTypeInfo name) | |
Show name => Show (SymTypeInfo name) | |
ToJSON name => ToJSON (SymTypeInfo name) | |
FromJSON name => FromJSON (SymTypeInfo name) |
The set of symbols (entities) exported by a single module. Contains the sets of value-level and type-level entities.
Symbols (Set (SymValueInfo OrigName)) (Set (SymTypeInfo OrigName)) |
A pair of the name information and original annotation. Used as an annotation type for AST.
GlobalValue (SymValueInfo OrigName) | global value |
GlobalType (SymTypeInfo OrigName) | global type |
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 Table |
|
ImportPart Symbols | part of an |
Export Symbols |
|
RecPatWildcard [OrigName] | wildcard in a record pattern. The list contains resolved names of the fields that are brought in scope by this pattern. |
RecExpWildcard [(OrigName, 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 |
type ModuleNameS = StringSource
String representing a module name
Possibly qualified name. If the name is not qualified,
ModuleNameS
is the empty string.
GName | |
|
Qualified name, where ModuleNameS
points to the module where the
name was originally defined. The module part is never empty.
Also contains name and version of the package where it was defined. If
it's Nothing
, then the entity is defined in the "current" package.
ppOrigName :: OrigName -> StringSource
Display an OrigName
ENotInScope (QName l) | name is not in scope |
EAmbiguous (QName l) [OrigName] | 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 |
ppError :: SrcInfo l => Error l -> StringSource
Display an error.
Note: can span multiple lines; the trailing newline is included.
class HasOrigName i whereSource