haskell-names-0.1.2: Name resolution library for Haskell

Safe HaskellNone

Language.Haskell.Names

Contents

Synopsis

Core functions

computeInterfacesSource

Arguments

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

getInterfacesSource

Arguments

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

annotateModuleSource

Arguments

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

Constructors

SymValue

value or function

Fields

sv_origName :: name
 
sv_fixity :: Maybe SymFixity
 
SymMethod

class method

Fields

sv_origName :: name
 
sv_fixity :: Maybe SymFixity
 
sv_className :: name
 
SymSelector

record field selector

Fields

sv_origName :: name
 
sv_fixity :: Maybe SymFixity
 
sv_typeName :: name
 
SymConstructor

data constructor

Fields

sv_origName :: name
 
sv_fixity :: Maybe SymFixity
 
sv_typeName :: name
 

data SymTypeInfo name Source

Information about a type-level entitity

Constructors

SymType

type synonym

Fields

st_origName :: name
 
st_fixity :: Maybe SymFixity
 
SymData

data type

Fields

st_origName :: name
 
st_fixity :: Maybe SymFixity
 
SymNewType

newtype

Fields

st_origName :: name
 
st_fixity :: Maybe SymFixity
 
SymTypeFam

type family

Fields

st_origName :: name
 
st_fixity :: Maybe SymFixity
 
SymDataFam

data family

Fields

st_origName :: name
 
st_fixity :: Maybe SymFixity
 
SymClass

type class

Fields

st_origName :: name
 
st_fixity :: Maybe SymFixity
 

Instances

data Symbols Source

The set of symbols (entities) exported by a single module. Contains the sets of value-level and type-level entities.

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 

data NameInfo l Source

Constructors

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

Binder

here the name is bound

Import Table

import declaration, and the table of symbols that it introduces

ImportPart Symbols

part of an import declaration

Export Symbols

export declaration, and the symbols it exports

None

no annotation

ScopeError (Error l)

scope error

type NameS = StringSource

String representing an unqualified entity name

type ModuleNameS = StringSource

String representing a module name

data GName Source

Possibly qualified name. If the name is not qualified, ModuleNameS is the empty string.

Constructors

GName ModuleNameS NameS 

data OrigName Source

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.

Constructors

OrigName 

data Error l Source

Constructors

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:

  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

ppError :: SrcInfo l => Error l -> StringSource

Display an error.

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

type SymFixity = (Assoc (), Int)Source

Repesents the symbol's fixity