haskell-names-0.5.2: Name resolution library for Haskell

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.Names

Contents

Synopsis

Core functions

computeInterfaces Source

Arguments

:: (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.

getInterfaces Source

Arguments

:: (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

annotateModule Source

Arguments

:: (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

data Symbol Source

Information about an entity. Carries at least the module it was originally declared in and its name.

Constructors

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

data Scoped l Source

A pair of the name information and original annotation. Used as an annotation type for AST.

Constructors

Scoped (NameInfo l) l 

Instances

data NameInfo l Source

Information about the names used in an AST.

Constructors

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

import declaration, and the table of symbols that it introduces

ImportPart [Symbol]

part of an import declaration

Export [Symbol]

part of an export declaration

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

data Error l Source

Errors during name resolution.

Constructors

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:

  1. optional parent in the import list, e.g. Bool in Bool(Right)
  2. the name which is not exported
  3. the module which does not export the name
EModNotFound (ModuleName l)

module not found

EInternal String

internal error

Instances

Functor Error 
Foldable Error 
Traversable Error 
Eq l => Eq (Error l) 
Data l => Data (Error l) 
Ord l => Ord (Error l) 
Show l => Show (Error l) 
Typeable (* -> *) Error 

Pretty printing

ppError :: SrcInfo l => Error l -> String Source

Display an error.

Note: can span multiple lines; the trailing newline is included.

ppSymbol :: Symbol -> String Source

Pretty print a symbol.