purescript-0.5.2.6: PureScript Programming Language Compiler

Safe HaskellNone

Language.PureScript.Declarations

Description

Data types for modules and declarations

Synopsis

Documentation

type Precedence = IntegerSource

A precedence level for an infix operator

data Associativity Source

Associativity for infix operators

Constructors

Infixl 
Infixr 
Infix 

data SourcePos Source

Source position information

Constructors

SourcePos 

Fields

sourceName :: String

Source name

sourcePosLine :: Int

Line number

sourcePosColumn :: Int

Column number

data Fixity Source

Fixity data for infix operators

data Module Source

A module declaration, consisting of 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.

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)

PositionedDeclarationRef SourcePos DeclarationRef

A declaration reference with source position information

data Declaration Source

The data type of declarations

Constructors

DataDeclaration ProperName [String] [(ProperName, [Type])]

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

DataBindingGroupDeclaration [Declaration]

A minimal mutually recursive set of data type declarations

TypeSynonymDeclaration ProperName [String] Type

A type synonym declaration (name, arguments, type)

TypeDeclaration Ident Type

A type declaration for a value (name, ty)

ValueDeclaration Ident NameKind [Binder] (Maybe Guard) Value

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

BindingGroupDeclaration [(Ident, NameKind, Value)]

A minimal mutually recursive set of value declarations

ExternDeclaration ForeignImportType Ident (Maybe JS) Type

A foreign import declaration (type, name, optional inline Javascript, type)

ExternDataDeclaration ProperName Kind

A data type foreign import (name, kind)

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

A type class instance foreign import

FixityDeclaration Fixity String

A fixity declaration (fixity data, operator name)

ImportDeclaration ModuleName (Maybe [DeclarationRef]) (Maybe ModuleName)

A module import (module name, optional set of identifiers to import, optional qualified as name)

TypeClassDeclaration ProperName [String] [(Qualified ProperName, [Type])] [Declaration]

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

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

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

PositionedDeclaration SourcePos Declaration

A declaration with source position information

isValueDecl :: Declaration -> BoolSource

Test if a declaration is a value declaration

isDataDecl :: Declaration -> BoolSource

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

isImportDecl :: Declaration -> BoolSource

Test if a declaration is a module import

isExternDataDecl :: Declaration -> BoolSource

Test if a declaration is a data type foreign import

isExternInstanceDecl :: Declaration -> BoolSource

Test if a declaration is a type class instance foreign import

isFixityDecl :: Declaration -> BoolSource

Test if a declaration is a fixity declaration

isExternDecl :: Declaration -> BoolSource

Test if a declaration is a foreign import

isTypeClassDeclaration :: Declaration -> BoolSource

Test if a declaration is a type class or instance declaration

type Guard = ValueSource

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

data Value Source

Data type for values

Constructors

NumericLiteral (Either Integer Double)

A numeric literal

StringLiteral String

A string literal

BooleanLiteral Bool

A boolean literal

UnaryMinus Value

A prefix -, will be desugared

BinaryNoParens (Qualified Ident) Value Value

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

Parens Value

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

ArrayLiteral [Value]

An array literal

ObjectLiteral [(String, Value)]

An object literal

Accessor String Value

An record property accessor expression

ObjectUpdate Value [(String, Value)]

Partial record update

Abs (Either Ident Binder) Value

Function introduction

App Value Value

Function application

Var (Qualified Ident)

Variable

IfThenElse Value Value Value

Conditional (if-then-else expression)

Constructor (Qualified ProperName)

A data constructor

Case [Value] [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 Value Type

A value with a type annotation

Let [Declaration] Value

A let binding

Do [DoNotationElement]

A do-notation block

TypeClassDictionary Bool (Qualified ProperName, [Type]) [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.

SuperClassDictionary (Qualified ProperName) [Type]

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

PositionedValue SourcePos Value

A value with source position information

data CaseAlternative Source

An alternative in a case statement

Constructors

CaseAlternative 

Fields

caseAlternativeBinders :: [Binder]

A collection of binders with which to match the inputs

caseAlternativeGuard :: Maybe Guard

An optional guard

caseAlternativeResult :: Value

The result expression

canonicalizeDictionary :: TypeClassDictionaryInScope -> Qualified IdentSource

Find the original dictionary which a type class dictionary in scope refers to

data DoNotationElement Source

A statement in a do-notation block

Constructors

DoNotationValue Value

A monadic value without a binder

DoNotationBind Binder Value

A monadic value with a binder

DoNotationLet [Declaration]

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

PositionedDoNotationElement SourcePos DoNotationElement

A do notation element with source position information

data Binder Source

Data type for binders

Constructors

NullBinder

Wildcard binder

BooleanBinder Bool

A binder which matches a boolean literal

StringBinder String

A binder which matches a string literal

NumberBinder (Either Integer Double)

A binder which matches a numeric literal

VarBinder Ident

A binder which binds an identifier

ConstructorBinder (Qualified ProperName) [Binder]

A binder which matches a data constructor

ObjectBinder [(String, Binder)]

A binder which matches a record and binds its properties

ArrayBinder [Binder]

A binder which matches an array and binds its elements

ConsBinder Binder Binder

A binder which matches an array and binds its head and tail

NamedBinder Ident Binder

A binder which binds its input to an identifier

PositionedBinder SourcePos Binder

A binder with source position information

binderNames :: Binder -> [Ident]Source

Collect all names introduced in binders in an expression

everythingOnValues :: (r -> r -> r) -> (Declaration -> r) -> (Value -> r) -> (Binder -> r) -> (CaseAlternative -> r) -> (DoNotationElement -> r) -> (Declaration -> r, Value -> r, Binder -> r, CaseAlternative -> r, DoNotationElement -> r)Source

everythingWithContextOnValues :: s -> r -> (r -> r -> r) -> (s -> Declaration -> (s, r)) -> (s -> Value -> (s, r)) -> (s -> Binder -> (s, r)) -> (s -> CaseAlternative -> (s, r)) -> (s -> DoNotationElement -> (s, r)) -> (Declaration -> r, Value -> r, Binder -> r, CaseAlternative -> r, DoNotationElement -> r)Source

accumTypes :: Monoid r => (Type -> r) -> (Declaration -> r, Value -> r, Binder -> r, CaseAlternative -> r, DoNotationElement -> r)Source