purescript-0.9.3: PureScript Programming Language Compiler

Safe HaskellNone
LanguageHaskell98

Language.PureScript.AST.Declarations

Description

Data types for modules and declarations

Synopsis

Documentation

type Context = [(Ident, Type)] Source #

A map of locally-bound names in scope.

data SimpleErrorMessage Source #

A type of error messages

Constructors

ErrorParsingFFIModule FilePath (Maybe ErrorMessage) 
ErrorParsingModule ParseError 
MissingFFIModule ModuleName 
MultipleFFIModules ModuleName [FilePath] 
UnnecessaryFFIModule ModuleName FilePath 
MissingFFIImplementations ModuleName [Ident] 
UnusedFFIImplementations ModuleName [Ident] 
InvalidFFIIdentifier ModuleName String 
CannotGetFileInfo FilePath 
CannotReadFile FilePath 
CannotWriteFile FilePath 
InfiniteType Type 
InfiniteKind Kind 
MultipleValueOpFixities (OpName ValueOpName) 
MultipleTypeOpFixities (OpName TypeOpName) 
OrphanTypeDeclaration Ident 
RedefinedModule ModuleName [SourceSpan] 
RedefinedIdent Ident 
OverlappingNamesInLet 
UnknownName (Qualified Name) 
UnknownImport ModuleName Name 
UnknownImportDataConstructor ModuleName (ProperName TypeName) (ProperName ConstructorName) 
UnknownExport Name 
UnknownExportDataConstructor (ProperName TypeName) (ProperName ConstructorName) 
ScopeConflict Name [ModuleName] 
ScopeShadowing Name (Maybe ModuleName) [ModuleName] 
DeclConflict Name Name 
ExportConflict (Qualified Name) (Qualified Name) 
DuplicateModuleName ModuleName 
DuplicateTypeArgument String 
InvalidDoBind 
InvalidDoLet 
CycleInDeclaration Ident 
CycleInTypeSynonym (Maybe (ProperName TypeName)) 
CycleInModules [ModuleName] 
NameIsUndefined Ident 
UndefinedTypeVariable (ProperName TypeName) 
PartiallyAppliedSynonym (Qualified (ProperName TypeName)) 
EscapedSkolem (Maybe Expr) 
TypesDoNotUnify Type Type 
KindsDoNotUnify Kind Kind 
ConstrainedTypeUnified Type Type 
OverlappingInstances (Qualified (ProperName ClassName)) [Type] [Qualified Ident] 
NoInstanceFound Constraint 
PossiblyInfiniteInstance (Qualified (ProperName ClassName)) [Type] 
CannotDerive (Qualified (ProperName ClassName)) [Type] 
CannotFindDerivingType (ProperName TypeName) 
DuplicateLabel String (Maybe Expr) 
DuplicateValueDeclaration Ident 
ArgListLengthsDiffer Ident 
OverlappingArgNames (Maybe Ident) 
MissingClassMember Ident 
ExtraneousClassMember Ident (Qualified (ProperName ClassName)) 
ExpectedType Type Kind 
IncorrectConstructorArity (Qualified (ProperName ConstructorName)) 
ExprDoesNotHaveType Expr Type 
PropertyIsMissing String 
AdditionalProperty String 
CannotApplyFunction Type Expr 
TypeSynonymInstance 
OrphanInstance Ident (Qualified (ProperName ClassName)) [Type] 
InvalidNewtype (ProperName TypeName) 
InvalidInstanceHead Type 
TransitiveExportError DeclarationRef [DeclarationRef] 
TransitiveDctorExportError DeclarationRef (ProperName ConstructorName) 
ShadowedName Ident 
ShadowedTypeVar String 
UnusedTypeVar String 
WildcardInferredType Type Context 
HoleInferredType String Type Context 
MissingTypeDeclaration Ident Type 
OverlappingPattern [[Binder]] Bool 
IncompleteExhaustivityCheck 
MisleadingEmptyTypeImport ModuleName (ProperName TypeName) 
ImportHidingModule ModuleName 
UnusedImport ModuleName 
UnusedExplicitImport ModuleName [String] (Maybe ModuleName) [DeclarationRef] 
UnusedDctorImport (ProperName TypeName) 
UnusedDctorExplicitImport (ProperName TypeName) [ProperName ConstructorName] 
DuplicateSelectiveImport ModuleName 
DuplicateImport ModuleName ImportDeclarationType (Maybe ModuleName) 
DuplicateImportRef Name 
DuplicateExportRef Name 
IntOutOfRange Integer String Integer Integer 
ImplicitQualifiedImport ModuleName ModuleName [DeclarationRef] 
ImplicitImport ModuleName [DeclarationRef] 
HidingImport ModuleName [DeclarationRef] 
CaseBinderLengthDiffers Int [Binder] 
IncorrectAnonymousArgument 
InvalidOperatorInBinder (Qualified (OpName ValueOpName)) (Qualified Ident) 
DeprecatedRequirePath 
CannotGeneralizeRecursiveFunction Ident Type 

data Module Source #

A module declaration, consisting of comments about the module, a module name, a list of declarations, and a list of the declarations that are explicitly exported. If the export list is Nothing, everything is exported.

Instances

getModuleName :: Module -> ModuleName Source #

Return a module's name.

addDefaultImport :: ModuleName -> Module -> Module Source #

Add an import declaration for a module if it does not already explicitly import it.

data DeclarationRef Source #

An item in a list of explicit imports or exports

Constructors

TypeRef (ProperName TypeName) (Maybe [ProperName ConstructorName])

A type constructor with data constructors

TypeOpRef (OpName TypeOpName)

A type operator

ValueRef Ident

A value

ValueOpRef (OpName ValueOpName)

A value-level operator

TypeClassRef (ProperName ClassName)

A type class

TypeInstanceRef Ident

A type class instance, created during typeclass desugaring (name, class name, instance types)

ModuleRef ModuleName

A module, in its entirety

ReExportRef ModuleName DeclarationRef

A value re-exported from another module. These will be inserted during elaboration in name desugaring.

PositionedDeclarationRef SourceSpan [Comment] DeclarationRef

A declaration reference with source position information

data ImportDeclarationType Source #

The data type which specifies type of import declaration

Constructors

Implicit

An import with no explicit list: `import M`.

Explicit [DeclarationRef]

An import with an explicit list of references to import: `import M (foo)`

Hiding [DeclarationRef]

An import with a list of references to hide: `import M hiding (foo)`

data Declaration Source #

The data type of declarations

Constructors

DataDeclaration DataDeclType (ProperName TypeName) [(String, Maybe Kind)] [(ProperName ConstructorName, [Type])]

A data type declaration (data or newtype, name, arguments, data constructors)

DataBindingGroupDeclaration [Declaration]

A minimal mutually recursive set of data type declarations

TypeSynonymDeclaration (ProperName TypeName) [(String, Maybe Kind)] Type

A type synonym declaration (name, arguments, type)

TypeDeclaration Ident Type

A type declaration for a value (name, ty)

ValueDeclaration Ident NameKind [Binder] (Either [(Guard, Expr)] Expr)

A value declaration (name, top-level binders, optional guard, value)

BindingGroupDeclaration [(Ident, NameKind, Expr)]

A minimal mutually recursive set of value declarations

ExternDeclaration Ident Type

A foreign import declaration (name, type)

ExternDataDeclaration (ProperName TypeName) Kind

A data type foreign import (name, kind)

FixityDeclaration (Either ValueFixity TypeFixity)

A fixity declaration

ImportDeclaration ModuleName ImportDeclarationType (Maybe ModuleName)

A module import (module name, qualifiedunqualifiedhiding, optional "qualified as" name)

TypeClassDeclaration (ProperName ClassName) [(String, Maybe Kind)] [Constraint] [Declaration]

A type class declaration (name, argument, implies, member declarations)

TypeInstanceDeclaration Ident [Constraint] (Qualified (ProperName ClassName)) [Type] TypeInstanceBody

A type instance declaration (name, dependencies, class name, instance types, member declarations)

PositionedDeclaration SourceSpan [Comment] Declaration

A declaration with source position information

data TypeInstanceBody Source #

The members of a type class instance declaration

Constructors

DerivedInstance

This is a derived instance

ExplicitInstance [Declaration]

This is a regular (explicit) instance

traverseTypeInstanceBody :: Applicative f => ([Declaration] -> f [Declaration]) -> TypeInstanceBody -> f TypeInstanceBody Source #

A traversal for TypeInstanceBody

isValueDecl :: Declaration -> Bool Source #

Test if a declaration is a value declaration

isDataDecl :: Declaration -> Bool Source #

Test if a declaration is a data type or type synonym declaration

isImportDecl :: Declaration -> Bool Source #

Test if a declaration is a module import

isExternDataDecl :: Declaration -> Bool Source #

Test if a declaration is a data type foreign import

isFixityDecl :: Declaration -> Bool Source #

Test if a declaration is a fixity declaration

isExternDecl :: Declaration -> Bool Source #

Test if a declaration is a foreign import

isTypeClassInstanceDeclaration :: Declaration -> Bool Source #

Test if a declaration is a type class instance declaration

isTypeClassDeclaration :: Declaration -> Bool Source #

Test if a declaration is a type class declaration

flattenDecls :: [Declaration] -> [Declaration] Source #

Recursively flatten data binding groups in the list of declarations

type Guard = Expr Source #

A guard is just a boolean-valued expression that appears alongside a set of binders

data Expr Source #

Data type for expressions and terms

Constructors

Literal (Literal Expr)

A literal value

UnaryMinus Expr

A prefix -, will be desugared

BinaryNoParens Expr Expr Expr

Binary operator application. During the rebracketing phase of desugaring, this data constructor will be removed.

Parens Expr

Explicit parentheses. During the rebracketing phase of desugaring, this data constructor will be removed.

Note: although it seems this constructor is not used, it _is_ useful, since it prevents certain traversals from matching.

ObjectGetter String

A record property getter (e.g. `_.x`). This will be removed during desugaring and expanded into a lambda that reads a property from a record.

Accessor String Expr

An record property accessor expression

ObjectUpdate Expr [(String, Expr)]

Partial record update

Abs (Either Ident Binder) Expr

Function introduction

App Expr Expr

Function application

Var (Qualified Ident)

Variable

Op (Qualified (OpName ValueOpName))

An operator. This will be desugared into a function during the "operators" phase of desugaring.

IfThenElse Expr Expr Expr

Conditional (if-then-else expression)

Constructor (Qualified (ProperName ConstructorName))

A data constructor

Case [Expr] [CaseAlternative]

A case expression. During the case expansion phase of desugaring, top-level binders will get desugared into case expressions, hence the need for guards and multiple binders per branch here.

TypedValue Bool Expr Type

A value with a type annotation

Let [Declaration] Expr

A let binding

Do [DoNotationElement]

A do-notation block

TypeClassDictionaryConstructorApp (Qualified (ProperName ClassName)) Expr

An application of a typeclass dictionary constructor. The value should be an ObjectLiteral.

TypeClassDictionary Constraint (Map (Maybe ModuleName) (Map (Qualified (ProperName ClassName)) (Map (Qualified Ident) TypeClassDictionaryInScope))) [ErrorMessageHint]

A placeholder for a type class dictionary to be inserted later. At the end of type checking, these placeholders will be replaced with actual expressions representing type classes dictionaries which can be evaluated at runtime. The constructor arguments represent (in order): whether or not to look at superclass implementations when searching for a dictionary, the type class name and instance type, and the type class dictionaries in scope.

TypeClassDictionaryAccessor (Qualified (ProperName ClassName)) Ident

A typeclass dictionary accessor, the implementation is left unspecified until CoreFn desugaring.

SuperClassDictionary (Qualified (ProperName ClassName)) [Type]

A placeholder for a superclass dictionary to be turned into a TypeClassDictionary during typechecking

AnonymousArgument

A placeholder for an anonymous function argument

Hole String

A typed hole that will be turned into a hint/error duing typechecking

PositionedValue SourceSpan [Comment] Expr

A value with source position information

Instances

data CaseAlternative Source #

An alternative in a case statement

Constructors

CaseAlternative 

Fields

data DoNotationElement Source #

A statement in a do-notation block

Constructors

DoNotationValue Expr

A monadic value without a binder

DoNotationBind Binder Expr

A monadic value with a binder

DoNotationLet [Declaration]

A let statement, i.e. a pure value with a binder

PositionedDoNotationElement SourceSpan [Comment] DoNotationElement

A do notation element with source position information