purescript-0.7.2.1: PureScript Programming Language Compiler

Safe HaskellNone
LanguageHaskell98

Language.PureScript.AST.Declarations

Description

Data types for modules and declarations

Synopsis

Documentation

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.

getModuleName :: Module -> ModuleName Source

Return a module's name.

data DeclarationRef Source

An item in a list of explicit imports or exports

Constructors

TypeRef ProperName (Maybe [ProperName])

A type constructor with data constructors

ValueRef Ident

A value

TypeClassRef ProperName

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

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 [(String, Maybe Kind)] [(ProperName, [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 [(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 Kind

A data type foreign import (name, kind)

ExternInstanceDeclaration Ident [Constraint] (Qualified ProperName) [Type]

A type class instance foreign import

FixityDeclaration Fixity String

A fixity declaration (fixity data, operator name)

ImportDeclaration ModuleName ImportDeclarationType (Maybe ModuleName)

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

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

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

TypeInstanceDeclaration Ident [Constraint] (Qualified ProperName) [Type] [Declaration]

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

PositionedDeclaration SourceSpan [Comment] Declaration

A declaration with source position information

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

isExternInstanceDecl :: Declaration -> Bool Source

Test if a declaration is a type class instance 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

NumericLiteral (Either Integer Double)

A numeric literal

StringLiteral String

A string literal

CharLiteral Char

A character literal

BooleanLiteral Bool

A boolean literal

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.

OperatorSection Expr (Either Expr Expr)

Operator section. This will be removed during desugaring and replaced with a partially applied operator or lambda to flip the arguments.

ArrayLiteral [Expr]

An array literal

ObjectLiteral [(String, Expr)]

An object literal

ObjectConstructor [(String, Maybe Expr)]

An object constructor (object literal with underscores). This will be removed during desugaring and expanded into a lambda that returns an object literal.

ObjectGetter String

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

Accessor String Expr

An record property accessor expression

ObjectUpdate Expr [(String, Expr)]

Partial record update

ObjectUpdater (Maybe Expr) [(String, Maybe Expr)]

Partial record updater. This will be removed during desugaring and expanded into a lambda that returns an object update.

Abs (Either Ident Binder) Expr

Function introduction

App Expr Expr

Function application

Var (Qualified Ident)

Variable

IfThenElse Expr Expr Expr

Conditional (if-then-else expression)

Constructor (Qualified ProperName)

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

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

TypeClassDictionary Bool Constraint (Map (Maybe ModuleName) (Map (Qualified ProperName) (Map (Qualified Ident) TypeClassDictionaryInScope)))

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

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

SuperClassDictionary (Qualified ProperName) [Type]

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

PositionedValue SourceSpan [Comment] Expr

A value with source position information

Instances

data CaseAlternative Source

An alternative in a case statement

Constructors

CaseAlternative 

Fields

caseAlternativeBinders :: [Binder]

A collection of binders with which to match the inputs

caseAlternativeResult :: Either [(Guard, Expr)] Expr

The result expression or a collect of guarded expressions

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