haskell-tools-rewrite-0.8.1.0: Facilities for generating new parts of the Haskell-Tools AST

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.Tools.AST.ElementTypes

Contents

Synopsis

Documentation

type AnnList node dom = AnnListG node dom SrcTemplateStage Source #

type AnnMaybe node dom = AnnMaybeG node dom SrcTemplateStage Source #

Modules

type Module dom = Ann UModule dom SrcTemplateStage Source #

The representation of a haskell module, that is a separate compilation unit. It may or may not have a header.

type ModuleHead dom = Ann UModuleHead dom SrcTemplateStage Source #

Module declaration with name and (optional) exports

type ExportSpecs dom = Ann UExportSpecs dom SrcTemplateStage Source #

A list of export specifications surrounded by parentheses

type ExportSpec dom = Ann UExportSpec dom SrcTemplateStage Source #

Export specifier

type IESpec dom = Ann UIESpec dom SrcTemplateStage Source #

Marks a name to be imported or exported with related names (subspecifier)

type SubSpec dom = Ann USubSpec dom SrcTemplateStage Source #

Marks how related names will be imported or exported with a given name

type ModulePragma dom = Ann UModulePragma dom SrcTemplateStage Source #

Pragmas that must be used after the module head

type FilePragma dom = Ann UFilePragma dom SrcTemplateStage Source #

Pragmas that must be used before defining the module

type ImportDecl dom = Ann UImportDecl dom SrcTemplateStage Source #

An import declaration: import Module.Name

type ImportSpec dom = Ann UImportSpec dom SrcTemplateStage Source #

Restriction on the imported names

type ImportQualified dom = Ann UImportQualified dom SrcTemplateStage Source #

Marks the import as qualified: qualified

type ImportSource dom = Ann UImportSource dom SrcTemplateStage Source #

Marks the import as source: {-# SOURCE #-}

type ImportSafe dom = Ann UImportSafe dom SrcTemplateStage Source #

Marks the import as safe: safe

type TypeNamespace dom = Ann UTypeNamespace dom SrcTemplateStage Source #

Marks an imported name to belong to the type namespace: type

type ImportRenaming dom = Ann UImportRenaming dom SrcTemplateStage Source #

Renaming imports ( as A )

type ModuleName dom = Ann UModuleName dom SrcTemplateStage Source #

The name of a module

type LanguageExtension dom = Ann ULanguageExtension dom SrcTemplateStage Source #

The name of the enabled language extension, for example ( LambdaCase )

Declarations

type Decl dom = Ann UDecl dom SrcTemplateStage Source #

Haskell declaration

type ClassBody dom = Ann UClassBody dom SrcTemplateStage Source #

The list of declarations that can appear in a typeclass

type ClassElement dom = Ann UClassElement dom SrcTemplateStage Source #

Members of a class declaration

type InstBody dom = Ann UInstBody dom SrcTemplateStage Source #

Instance body is the implementation of the class functions ( where a x = 1; b x = 2 )

type InstBodyDecl dom = Ann UInstBodyDecl dom SrcTemplateStage Source #

Declarations inside an instance declaration.

type GadtConDecl dom = Ann UGadtConDecl dom SrcTemplateStage Source #

GADT constructor declaration ( D1 :: { val :: Int } -> T String )

type GadtConType dom = Ann UGadtConType dom SrcTemplateStage Source #

Type of GADT constructors (can be record types: { val :: Int })

type FieldWildcard dom = Ann UFieldWildcard dom SrcTemplateStage Source #

Marker for a field wildcard. Only needed to attach semantic information in a type-safe way.

type FunDeps dom = Ann UFunDeps dom SrcTemplateStage Source #

A list of functional dependencies: | a -> b, c -> d separated by commas

type FunDep dom = Ann UFunDep dom SrcTemplateStage Source #

A functional dependency, given on the form l1 ... ln -> r1 ... rn

type ConDecl dom = Ann UConDecl dom SrcTemplateStage Source #

A constructor declaration for a datatype

type DataOrNewtypeKeyword dom = Ann UDataOrNewtypeKeyword dom SrcTemplateStage Source #

The data or the newtype keyword to define ADTs.

type FieldDecl dom = Ann UFieldDecl dom SrcTemplateStage Source #

Field declaration ( fld :: Int )

type Deriving dom = Ann UDeriving dom SrcTemplateStage Source #

A deriving clause following a data type declaration. ( deriving Show or deriving (Show, Eq) )

type InstanceRule dom = Ann UInstanceRule dom SrcTemplateStage Source #

The instance declaration rule, which is, roughly, the part of the instance declaration before the where keyword.

type InstanceHead dom = Ann UInstanceHead dom SrcTemplateStage Source #

The specification of the class instance declaration

type OverlapPragma dom = Ann UOverlapPragma dom SrcTemplateStage Source #

Overlap pragmas. Can be applied to class declarations and class instance declarations.

type TypeEqn dom = Ann UTypeEqn dom SrcTemplateStage Source #

Type equations as found in closed type families ( T A = S )

type TopLevelPragma dom = Ann UTopLevelPragma dom SrcTemplateStage Source #

Top level pragmas

type Rule dom = Ann URule dom SrcTemplateStage Source #

A rewrite rule ( "map/map" forall f g xs. map f (map g xs) = map (f.g) xs )

type RuleVar dom = Ann URuleVar dom SrcTemplateStage Source #

A variable for a rewrite rule. With or without type signature.

type AnnotationSubject dom = Ann UAnnotationSubject dom SrcTemplateStage Source #

Annotation allows you to connect an expression to any declaration.

type MinimalFormula dom = Ann UMinimalFormula dom SrcTemplateStage Source #

Formulas of minimal annotations declaring which functions should be defined.

type SourceRange dom = Ann USourceRange dom SrcTemplateStage Source #

In-AST source ranges (for generated pragmas)

type TypeFamily dom = Ann UTypeFamily dom SrcTemplateStage Source #

Open type and data families

type TypeFamilySpec dom = Ann UTypeFamilySpec dom SrcTemplateStage Source #

Type family specification with kinds specification and injectivity.

type InjectivityAnn dom = Ann UInjectivityAnn dom SrcTemplateStage Source #

Injectivity annotation for type families ( = r | r -> a )

type PatternSynonym dom = Ann UPatternSynonym dom SrcTemplateStage Source #

Pattern synonyms: pattern Arrow t1 t2 = App "->" [t1, t2]

type PatSynRhs dom = Ann UPatSynRhs dom SrcTemplateStage Source #

Right-hand side of pattern synonym

type PatSynLhs dom = Ann UPatSynLhs dom SrcTemplateStage Source #

Left hand side of a pattern synonym

type PatSynWhere dom = Ann UPatSynWhere dom SrcTemplateStage Source #

Where clause of pattern synonym (explicit expression direction)

type PatternSignature dom = Ann UPatternTypeSignature dom SrcTemplateStage Source #

Pattern type signature declaration ( pattern Succ :: Int -> Int )

type Role dom = Ann URole dom SrcTemplateStage Source #

Role annotations for types

type CallConv dom = Ann UCallConv dom SrcTemplateStage Source #

Call conventions of foreign functions

type Safety dom = Ann USafety dom SrcTemplateStage Source #

Safety annotations for foreign calls

type ConlikeAnnot dom = Ann UConlikeAnnot dom SrcTemplateStage Source #

A CONLIKE modifier for an INLINE pragma.

type PhaseControl dom = Ann UPhaseControl dom SrcTemplateStage Source #

Controls the activation of a rewrite rule ( [1] )

Binds

type ValueBind dom = Ann UValueBind dom SrcTemplateStage Source #

Value binding for top-level and local bindings

type Match dom = Ann UMatch dom SrcTemplateStage Source #

Clause of function binding

type MatchLhs dom = Ann UMatchLhs dom SrcTemplateStage Source #

Something on the left side of the match

type Rhs dom = Ann URhs dom SrcTemplateStage Source #

Right hand side of a value binding (possible with guards): ( = 3 or | x == 1 = 3; | otherwise = 4 )

type GuardedRhs dom = Ann UGuardedRhs dom SrcTemplateStage Source #

A guarded right-hand side of a value binding ( | x > 3 = 2 )

type RhsGuard dom = Ann URhsGuard dom SrcTemplateStage Source #

Guards for value bindings and pattern matches ( Just v x, v 1 )

type LocalBind dom = Ann ULocalBind dom SrcTemplateStage Source #

Bindings that are enabled in local blocks (where or let).

type LocalBinds dom = Ann ULocalBinds dom SrcTemplateStage Source #

Local bindings attached to a declaration ( where x = 42 )

type FixitySignature dom = Ann UFixitySignature dom SrcTemplateStage Source #

A fixity signature ( infixl 5 +, - ).

type TypeSignature dom = Ann UTypeSignature dom SrcTemplateStage Source #

A type signature ( f :: Int -> Int )

Types

type Type dom = Ann UType dom SrcTemplateStage Source #

Haskell types

type TyVar dom = Ann UTyVar dom SrcTemplateStage Source #

Type variable declarations (with possible kind annotation)

type Assertion dom = Ann UAssertion dom SrcTemplateStage Source #

A single assertion in the context

Kinds

type KindConstraint dom = Ann UKindConstraint dom SrcTemplateStage Source #

Kind constraint ( :: * -> * )

type Kind dom = Ann UKind dom SrcTemplateStage Source #

Haskell kinds

type PromotedKind dom = Ann (UPromoted UKind) dom SrcTemplateStage Source #

Values promoted to the kind level

Expressions

type Expr dom = Ann UExpr dom SrcTemplateStage Source #

Haskell expressions

type Alt dom = Ann UAlt dom SrcTemplateStage Source #

Clause of case expression ( Just x -> x + 1 )

type CaseRhs dom = Ann UCaseRhs dom SrcTemplateStage Source #

Right hand side of a match (possible with guards): ( -> 3 or | x == 1 -> 3; | otherwise -> 4 )

type GuardedCaseRhs dom = Ann UGuardedCaseRhs dom SrcTemplateStage Source #

A guarded right-hand side of pattern matches binding ( | x > 3 -> 2 )

type FieldUpdate dom = Ann UFieldUpdate dom SrcTemplateStage Source #

Field update expressions

type TupSecElem dom = Ann UTupSecElem dom SrcTemplateStage Source #

An element of a tuple section that can be an expression or missing (indicating a value from a parameter)

type ExprPragma dom = Ann UExprPragma dom SrcTemplateStage Source #

Pragmas that can be applied to expressions

type Cmd dom = Ann UCmd dom SrcTemplateStage Source #

Special expressions for arrows

type CmdAlt dom = Ann UCmdAlt dom SrcTemplateStage Source #

Clause of case expression for commands

type ArrowApp dom = Ann UArrowAppl dom SrcTemplateStage Source #

Arrow directions

Statements

type Stmt dom = Ann UStmt dom SrcTemplateStage Source #

A statement in a do-notation

type DoKind dom = Ann UDoKind dom SrcTemplateStage Source #

Keywords do or mdo to start a do-block

type CompStmt dom = Ann UCompStmt dom SrcTemplateStage Source #

List comprehension statement

type ListCompBody dom = Ann UListCompBody dom SrcTemplateStage Source #

Body of a list comprehension: ( | x <- [1..10] )

type CmdStmt dom = Ann UCmdStmt dom SrcTemplateStage Source #

A do-notation for arrows

Patterns

type Pattern dom = Ann UPattern dom SrcTemplateStage Source #

Representation of patterns for pattern bindings

Template Haskell

type Splice dom = Ann USplice dom SrcTemplateStage Source #

A template haskell splice

type Bracket dom = Ann UBracket dom SrcTemplateStage Source #

Template Haskell bracket expressions

type QuasiQuote dom = Ann UQuasiQuote dom SrcTemplateStage Source #

Template haskell quasi-quotation: [quoter|str]

Literals

type Literal dom = Ann ULiteral dom SrcTemplateStage Source #

Haskell literals

Names

type Operator dom = Ann UOperator dom SrcTemplateStage Source #

A definition that functions as an operator

type Name dom = Ann UName dom SrcTemplateStage Source #

A definition that functions as a name

type QualifiedName dom = Ann UQualifiedName dom SrcTemplateStage Source #

Possible qualified names. Contains also implicit names. Linear implicit parameter: %x. Non-linear implicit parameter: ?x.

type NamePart dom = Ann UNamePart dom SrcTemplateStage Source #

Parts of a qualified name.

type StringNode dom = Ann UStringNode dom SrcTemplateStage Source #

Program elements formatted as string literals (import packages, pragma texts)

Optional AST elements

AST elements with multiplicity

type DeclList dom = AnnList UDecl dom Source #

type NameList dom = AnnList UName dom Source #

type TypeList dom = AnnList UType dom Source #

type ExprList dom = AnnList UExpr dom Source #

type AltList dom = AnnList UAlt dom Source #

type StmtList dom = AnnList UStmt dom Source #

type KindList dom = AnnList UKind dom Source #

type RuleList dom = AnnList URule dom Source #

type RoleList dom = AnnList URole dom Source #

type CmdList dom = AnnList UCmd dom Source #