language-haskell
Safe HaskellNone
LanguageHaskell2010

Language.Haskell.Extensions.Abstract

Description

The abstract node types forming a Haskell module with language extensions. Every node type has the kind TreeNodeKind.

Synopsis

Types and classes for extension support

type SupportFor (e :: Extension) l = If (Elem e (ExtensionsSupportedBy l)) () Void Source #

SupportFor e l reduces to () if the language l supports extension e and to Void otherwise.

type Supports (e :: Extension) l = SupportFor e l ~ () Source #

Constraint asserting the language l supports extension e

type SupportsNo (e :: Extension) l = SupportFor e l ~ Void Source #

Constraint asserting the language l does not support extension e

type family SupportsAllOf (es :: [Extension]) l where ... Source #

Constraint asserting the language l supports all extensions in the list es

Equations

SupportsAllOf ('[] :: [Extension]) _1 = () 
SupportsAllOf (e ': es) l = (Supports e l, SupportsAllOf es l) 

type family ExtendedWithAllOf (es :: [Extension]) l where ... Source #

Equations

ExtendedWithAllOf ('[] :: [Extension]) _1 = () 
ExtendedWithAllOf (e ': es) l = (ExtendedWith '[e] l, ExtendedWithAllOf es l) 

class SupportsAllOf es λ => ExtendedWith (es :: [Extension]) λ where Source #

If the language λ supports all the extensions es, instance ExtendedWith es λ provides the implementation.

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct es λ l d s Source #

How to construct the AST nodes supporting the extensions

Instances

Instances details
ExtendedWith '['BangPatterns] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['BangPatterns] Language l d s Source #

ExtendedWith '['CApiFFI] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['CApiFFI] Language l d s Source #

ExtendedWith '['DefaultSignatures] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['DefaultSignatures] Language l d s Source #

ExtendedWith '['DerivingStrategies] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['DerivingStrategies] Language l d s Source #

ExtendedWith '['DerivingVia] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['DerivingVia] Language l d s Source #

ExtendedWith '['ExplicitNamespaces] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['ExplicitNamespaces] Language l d s Source #

ExtendedWith '['ExtendedLiterals] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['ExtendedLiterals] Language l d s Source #

ExtendedWith '['FunctionalDependencies] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['FunctionalDependencies] Language l d s Source #

ExtendedWith '['GADTs, 'TypeData] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['GADTs, 'TypeData] Language l d s Source #

ExtendedWith '['ImplicitParameters] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['ImplicitParameters] Language l d s Source #

ExtendedWith '['InterruptibleFFI] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['InterruptibleFFI] Language l d s Source #

ExtendedWith '['LambdaCase] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['LambdaCase] Language l d s Source #

ExtendedWith '['MagicHash] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['MagicHash] Language l d s Source #

ExtendedWith '['NPlusKPatterns] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['NPlusKPatterns] Language l d s Source #

ExtendedWith '['NamedDefaults] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['NamedDefaults] Language l d s Source #

ExtendedWith '['NamedFieldPuns] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['NamedFieldPuns] Language l d s Source #

ExtendedWith '['ParallelListComprehensions] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['ParallelListComprehensions] Language l d s Source #

ExtendedWith '['PatternSynonyms] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['PatternSynonyms] Language l d s Source #

ExtendedWith '['QualifiedDo, 'RecursiveDo] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['QualifiedDo, 'RecursiveDo] Language l d s Source #

ExtendedWith '['QualifiedDo] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['QualifiedDo] Language l d s Source #

ExtendedWith '['RecordWildCards] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['RecordWildCards] Language l d s Source #

ExtendedWith '['RecursiveDo] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['RecursiveDo] Language l d s Source #

ExtendedWith '['StandaloneDeriving] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['StandaloneDeriving] Language l d s Source #

ExtendedWith '['Strict] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['Strict] Language l d s Source #

ExtendedWith '['StrictData] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['StrictData] Language l d s Source #

ExtendedWith '['TupleSections] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['TupleSections] Language l d s Source #

ExtendedWith '['TypeAbstractions] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['TypeAbstractions] Language l d s Source #

ExtendedWith '['TypeData] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['TypeData] Language l d s Source #

ExtendedWith '['UnboxedSums] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['UnboxedSums] Language l d s Source #

ExtendedWith '['UnboxedTuples] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['UnboxedTuples] Language l d s Source #

ExtendedWith '['ViewPatterns] Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

build :: forall l (d :: NodeWrap) (s :: NodeWrap). Construct '['ViewPatterns] Language l d s Source #

data family Construct (es :: [Extension]) :: TreeNodeKind Source #

Construct es is a record of functions for constructing the AST nodes for language extensions es.

Instances

Instances details
data Construct '['BangPatterns] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['BangPatterns] λ l d s = BangPatternConstruction {}
data Construct '['CApiFFI] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['DefaultSignatures] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['DefaultSignatures] λ l d s = DefaultSignatureConstruction {}
data Construct '['DerivingStrategies] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['DerivingVia] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['DerivingVia] λ l d s = DerivingViaConstruction {}
data Construct '['ExplicitNamespaces] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['ExtendedLiterals] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['FunctionalDependencies] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['FunctionalDependencies] λ l d s = FunctionalDependenciesConstruction {}
data Construct '['GADTs, 'TypeData] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['GADTs, 'TypeData] λ l d s = TypeGADTConstruction {}
data Construct '['ImplicitParameters] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['InterruptibleFFI] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['LambdaCase] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['LambdaCase] λ l d s = LambdaCaseConstruction {}
data Construct '['MagicHash] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['MagicHash] λ l d s = MagicHashConstruction {}
data Construct '['NPlusKPatterns] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['NamedDefaults] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['NamedFieldPuns] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['ParallelListComprehensions] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['ParallelListComprehensions] λ l d s = ParallelListComprehensionConstruction {}
data Construct '['PatternSynonyms] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['PatternSynonyms] λ l d s = PatternSynonymConstruction {}
data Construct '['QualifiedDo, 'RecursiveDo] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['QualifiedDo] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['RecordWildCards] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['RecursiveDo] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['RecursiveDo] λ l d s = RecursiveDoConstruction {}
data Construct '['StandaloneDeriving] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['Strict] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['Strict] λ l d s = StrictConstruction {}
data Construct '['StrictData] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['StrictData] λ l d s = StrictDataConstruction {}
data Construct '['TupleSections] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['TypeAbstractions] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['TypeAbstractions] λ l d s = TypeAbstractionConstruction {}
data Construct '['TypeData] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['TypeData] λ l d s = TypeDataConstruction {}
data Construct '['UnboxedSums] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['UnboxedSums] λ l d s = UnboxedSumsConstruction {}
data Construct '['UnboxedTuples] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['ViewPatterns] λ l d s Source # 
Instance details

Defined in Language.Haskell.Extensions.Abstract

data Construct '['ViewPatterns] λ l d s = ViewPatternConstruction {}

class (Haskell λ, ExtendedWithAllOf '['MagicHash, 'ExtendedLiterals, 'ParallelListComprehensions, 'ExplicitNamespaces, 'NamedFieldPuns, 'RecordWildCards, 'RecursiveDo, 'QualifiedDo, 'LambdaCase, 'TupleSections, 'UnboxedTuples, 'UnboxedSums, 'InterruptibleFFI, 'CApiFFI, 'StrictData, 'Strict, 'BangPatterns, 'ViewPatterns, 'NPlusKPatterns, 'NamedDefaults, 'PatternSynonyms, 'ImplicitParameters, 'StandaloneDeriving, 'DerivingStrategies, 'DerivingVia, 'DefaultSignatures, 'TypeData, 'TypeAbstractions, 'FunctionalDependencies] λ, ExtendedWith '['GADTs, 'TypeData] λ, ExtendedWith '['QualifiedDo, 'RecursiveDo] λ) => ExtendedHaskell λ where Source #

The big collection of all known extensions

Minimal complete definition

multiWayIfExpression, overloadedLabel, getField, fieldProjection, safeImportDeclaration, packageQualifiedImportDeclaration, safePackageQualifiedImportDeclaration, infixTypeApplication, infixTypeLHSApplication, typeLHSApplication, simpleKindedTypeLHS, existentialConstructor, explicitlyScopedInstanceDeclaration, forallType, constrainedType, kindedType, typeWildcard, groundType, explicitlyKindedTypeVariable, implicitlyKindedTypeVariable, inferredTypeVariable, inferredExplicitlyKindedTypeVariable, typeKind, groundTypeKind, typeRoleDeclaration, kindedDataDeclaration, kindedNewtypeDeclaration, gadtDeclaration, gadtNewtypeDeclaration, gadtConstructors, recordFunctionType, multiplicityFunctionType, linearFunctionType, dataFamilyDeclaration, openTypeFamilyDeclaration, closedTypeFamilyDeclaration, injectiveOpenTypeFamilyDeclaration, injectiveClosedTypeFamilyDeclaration, dataFamilyInstance, newtypeFamilyInstance, gadtDataFamilyInstance, gadtNewtypeFamilyInstance, typeFamilyInstance, classReferenceInstanceLHS, infixTypeClassInstanceLHS, classInstanceLHSApplication, classInstanceLHSKindApplication, kindSignature, typeEquality, typeConstraint, constraintType, inferredRole, nominalRole, representationalRole, phantomRole, promotedConstructorType, promotedTupleType, promotedListType, promotedIntegerLiteral, promotedCharLiteral, promotedStringLiteral, promotedInfixTypeApplication, visibleDependentType, visibleTypeApplication, visibleKindApplication, typedPattern, constructorPatternWithTypeApplications

Associated Types

type GADTConstructor λ = (x :: TreeNodeSubKind) | x -> λ Source #

type Kind λ = (x :: TreeNodeSubKind) | x -> λ Source #

type TypeVarBinding λ = (x :: TreeNodeSubKind) | x -> λ Source #

type ModuleMember λ = (x :: Type) | x -> λ Source #

type TypeRole λ = (x :: Type) | x -> λ Source #

Methods

hashLiteral :: forall l (d :: NodeWrap) (s :: NodeWrap). Value λ l d s -> Value λ l d s Source #

mdoExpression :: forall s l (d :: NodeWrap). s (GuardedExpression l l d d) -> Expression λ l d s Source #

parallelListComprehension :: forall s l (d :: NodeWrap). s (Expression l l d d) -> NonEmpty (s (Statement l l d d)) -> NonEmpty (s (Statement l l d d)) -> [NonEmpty (s (Statement l l d d))] -> Expression λ l d s Source #

tupleSectionExpression :: forall s l (d :: NodeWrap). NonEmpty (Maybe (s (Expression l l d d))) -> Expression λ l d s Source #

multiWayIfExpression :: forall s l (d :: NodeWrap). [s (GuardedExpression l l d d)] -> Expression λ l d s Source #

overloadedLabel :: forall l (d :: NodeWrap) (s :: NodeWrap). Text -> Expression λ l d s Source #

getField :: forall s l (d :: NodeWrap). s (Expression l l d d) -> Name λ -> Expression λ l d s Source #

fieldProjection :: forall l (d :: NodeWrap) (s :: NodeWrap). NonEmpty (Name λ) -> Expression λ l d s Source #

wildcardRecordExpression :: forall s l (d :: NodeWrap). QualifiedName λ -> [s (FieldBinding l l d d)] -> Expression λ l d s Source #

recursiveStatement :: forall s l (d :: NodeWrap). [s (Statement l l d d)] -> Statement λ l d s Source #

safeImportDeclaration :: forall s l (d :: NodeWrap). Bool -> ModuleName λ -> Maybe (ModuleName λ) -> Maybe (s (ImportSpecification l l d d)) -> Import λ l d s Source #

packageQualifiedImportDeclaration :: forall s l (d :: NodeWrap). Bool -> Text -> ModuleName λ -> Maybe (ModuleName λ) -> Maybe (s (ImportSpecification l l d d)) -> Import λ l d s Source #

safePackageQualifiedImportDeclaration :: forall s l (d :: NodeWrap). Bool -> Text -> ModuleName λ -> Maybe (ModuleName λ) -> Maybe (s (ImportSpecification l l d d)) -> Import λ l d s Source #

infixTypeApplication :: forall s l (d :: NodeWrap). s (Type l l d d) -> QualifiedName λ -> s (Type l l d d) -> Type λ l d s Source #

infixTypeLHSApplication :: forall l (d :: NodeWrap) (s :: NodeWrap). TypeVarBinding λ l d s -> Name λ -> TypeVarBinding λ l d s -> TypeLHS λ l d s Source #

typeLHSApplication :: forall s l (d :: NodeWrap). s (TypeLHS l l d d) -> TypeVarBinding λ l d s -> TypeLHS λ l d s Source #

simpleKindedTypeLHS :: forall l (d :: NodeWrap) (s :: NodeWrap). Name λ -> [TypeVarBinding λ l d s] -> TypeLHS λ l d s Source #

existentialConstructor :: forall l (d :: NodeWrap) s. [TypeVarBinding λ l d s] -> s (Context l l d d) -> s (DataConstructor l l d d) -> DataConstructor λ l d s Source #

explicitlyScopedInstanceDeclaration :: forall l (d :: NodeWrap) s. [TypeVarBinding λ l d s] -> s (Context l l d d) -> s (ClassInstanceLHS l l d d) -> [s (Declaration l l d d)] -> Declaration λ l d s Source #

forallType :: forall l (d :: NodeWrap) s. [TypeVarBinding λ l d s] -> s (Type l l d d) -> Type λ l d s Source #

constrainedType :: forall s l (d :: NodeWrap). s (Context l l d d) -> s (Type l l d d) -> Type λ l d s Source #

kindedType :: forall s l (d :: NodeWrap). s (Type l l d d) -> s (Kind l l d d) -> Type λ l d s Source #

typeWildcard :: forall l (d :: NodeWrap) (s :: NodeWrap). Type λ l d s Source #

groundType :: forall l (d :: NodeWrap) (s :: NodeWrap). Type λ l d s Source #

explicitlyKindedTypeVariable :: forall s l (d :: NodeWrap). Name λ -> s (Kind l l d d) -> TypeVarBinding λ l d s Source #

implicitlyKindedTypeVariable :: forall l (d :: NodeWrap) (s :: NodeWrap). Name λ -> TypeVarBinding λ l d s Source #

inferredTypeVariable :: forall l (d :: NodeWrap) (s :: NodeWrap). Name λ -> TypeVarBinding λ l d s Source #

inferredExplicitlyKindedTypeVariable :: forall s l (d :: NodeWrap). Name λ -> s (Kind l l d d) -> TypeVarBinding λ l d s Source #

typeKind :: forall s l (d :: NodeWrap). s (Type l l d d) -> Kind λ l d s Source #

groundTypeKind :: forall l (d :: NodeWrap) (s :: NodeWrap). Type λ l d s Source #

typeRoleDeclaration :: forall l (d :: NodeWrap) (s :: NodeWrap). QualifiedName λ -> [TypeRole λ] -> Declaration λ l d s Source #

kindedDataDeclaration :: forall s l (d :: NodeWrap). s (Context l l d d) -> s (TypeLHS l l d d) -> s (Kind l l d d) -> [s (DataConstructor l l d d)] -> [s (DerivingClause l l d d)] -> Declaration λ l d s Source #

kindedNewtypeDeclaration :: forall s l (d :: NodeWrap). s (Context l l d d) -> s (TypeLHS l l d d) -> s (Kind l l d d) -> s (DataConstructor l l d d) -> [s (DerivingClause l l d d)] -> Declaration λ l d s Source #

gadtDeclaration :: forall s l (d :: NodeWrap). s (TypeLHS l l d d) -> Maybe (s (Kind l l d d)) -> [s (GADTConstructor l l d d)] -> [s (DerivingClause l l d d)] -> Declaration λ l d s Source #

gadtNewtypeDeclaration :: forall s l (d :: NodeWrap). s (TypeLHS l l d d) -> Maybe (s (Kind l l d d)) -> s (GADTConstructor l l d d) -> [s (DerivingClause l l d d)] -> Declaration λ l d s Source #

gadtConstructors :: forall l (d :: NodeWrap) s. NonEmpty (Name λ) -> [TypeVarBinding λ l d s] -> s (Context l l d d) -> s (Type l l d d) -> GADTConstructor λ l d s Source #

recordFunctionType :: forall s l (d :: NodeWrap). [s (FieldDeclaration l l d d)] -> s (Type l l d d) -> Type λ l d s Source #

multiplicityFunctionType :: forall s l (d :: NodeWrap). s (Type l l d d) -> s (Type l l d d) -> s (Type l l d d) -> Type λ l d s Source #

linearFunctionType :: forall s l (d :: NodeWrap). s (Type l l d d) -> s (Type l l d d) -> Type λ l d s Source #

punnedFieldBinding :: forall l (d :: NodeWrap) (s :: NodeWrap). QualifiedName λ -> FieldBinding λ l d s Source #

punnedFieldPattern :: forall l (d :: NodeWrap) (s :: NodeWrap). QualifiedName λ -> FieldPattern λ l d s Source #

dataFamilyDeclaration :: forall s l (d :: NodeWrap). s (TypeLHS l l d d) -> Maybe (s (Kind l l d d)) -> Declaration λ l d s Source #

openTypeFamilyDeclaration :: forall s l (d :: NodeWrap). s (TypeLHS l l d d) -> Maybe (s (Kind l l d d)) -> Declaration λ l d s Source #

closedTypeFamilyDeclaration :: forall s l (d :: NodeWrap). s (TypeLHS l l d d) -> Maybe (s (Kind l l d d)) -> [s (Declaration l l d d)] -> Declaration λ l d s Source #

injectiveOpenTypeFamilyDeclaration :: forall s l (d :: NodeWrap). s (TypeLHS l l d d) -> TypeVarBinding λ l d s -> Maybe (Name λ, NonEmpty (Name λ)) -> Declaration λ l d s Source #

injectiveClosedTypeFamilyDeclaration :: forall s l (d :: NodeWrap). s (TypeLHS l l d d) -> TypeVarBinding λ l d s -> Maybe (Name λ, NonEmpty (Name λ)) -> [s (Declaration l l d d)] -> Declaration λ l d s Source #

dataFamilyInstance :: forall l (d :: NodeWrap) s. [TypeVarBinding λ l d s] -> s (Context l l d d) -> s (ClassInstanceLHS l l d d) -> Maybe (s (Kind l l d d)) -> [s (DataConstructor l l d d)] -> [s (DerivingClause l l d d)] -> Declaration λ l d s Source #

newtypeFamilyInstance :: forall l (d :: NodeWrap) s. [TypeVarBinding λ l d s] -> s (Context l l d d) -> s (ClassInstanceLHS l l d d) -> Maybe (s (Kind l l d d)) -> s (DataConstructor l l d d) -> [s (DerivingClause l l d d)] -> Declaration λ l d s Source #

gadtDataFamilyInstance :: forall l (d :: NodeWrap) s. [TypeVarBinding λ l d s] -> s (ClassInstanceLHS l l d d) -> Maybe (s (Kind l l d d)) -> [s (GADTConstructor l l d d)] -> [s (DerivingClause l l d d)] -> Declaration λ l d s Source #

gadtNewtypeFamilyInstance :: forall l (d :: NodeWrap) s. [TypeVarBinding λ l d s] -> s (ClassInstanceLHS l l d d) -> Maybe (s (Kind l l d d)) -> s (GADTConstructor l l d d) -> [s (DerivingClause l l d d)] -> Declaration λ l d s Source #

typeFamilyInstance :: forall l (d :: NodeWrap) s. [TypeVarBinding λ l d s] -> s (ClassInstanceLHS l l d d) -> s (Type l l d d) -> Declaration λ l d s Source #

classReferenceInstanceLHS :: forall l (d :: NodeWrap) (s :: NodeWrap). QualifiedName λ -> ClassInstanceLHS λ l d s Source #

infixTypeClassInstanceLHS :: forall s l (d :: NodeWrap). s (Type l l d d) -> QualifiedName λ -> s (Type l l d d) -> ClassInstanceLHS λ l d s Source #

classInstanceLHSApplication :: forall s l (d :: NodeWrap). s (ClassInstanceLHS l l d d) -> s (Type l l d d) -> ClassInstanceLHS λ l d s Source #

classInstanceLHSKindApplication :: forall s l (d :: NodeWrap). s (ClassInstanceLHS l l d d) -> s (Kind l l d d) -> ClassInstanceLHS λ l d s Source #

kindSignature :: forall s l (d :: NodeWrap). Name λ -> s (Kind l l d d) -> Declaration λ l d s Source #

typeEquality :: forall s l (d :: NodeWrap). s (Type l l d d) -> s (Type l l d d) -> Context λ l d s Source #

typeConstraint :: forall s l (d :: NodeWrap). s (Type l l d d) -> Context λ l d s Source #

constraintType :: forall s l (d :: NodeWrap). s (Context l l d d) -> Type λ l d s Source #

inferredRole :: TypeRole λ Source #

nominalRole :: TypeRole λ Source #

representationalRole :: TypeRole λ Source #

phantomRole :: TypeRole λ Source #

promotedConstructorType :: forall s l (d :: NodeWrap). s (Constructor l l d d) -> Type λ l d s Source #

promotedTupleType :: forall s l (d :: NodeWrap). [s (Type l l d d)] -> Type λ l d s Source #

promotedListType :: forall s l (d :: NodeWrap). [s (Type l l d d)] -> Type λ l d s Source #

promotedIntegerLiteral :: forall l (d :: NodeWrap) (s :: NodeWrap). Integer -> Type λ l d s Source #

promotedCharLiteral :: forall l (d :: NodeWrap) (s :: NodeWrap). Char -> Type λ l d s Source #

promotedStringLiteral :: forall l (d :: NodeWrap) (s :: NodeWrap). Text -> Type λ l d s Source #

promotedInfixTypeApplication :: forall s l (d :: NodeWrap). s (Type l l d d) -> QualifiedName λ -> s (Type l l d d) -> Type λ l d s Source #

visibleDependentType :: forall l (d :: NodeWrap) s. [TypeVarBinding λ l d s] -> s (Type l l d d) -> Type λ l d s Source #

visibleTypeApplication :: forall s l (d :: NodeWrap). s (Expression l l d d) -> s (Type l l d d) -> Expression λ l d s Source #

visibleKindApplication :: forall s l (d :: NodeWrap). s (Type l l d d) -> s (Kind l l d d) -> Type λ l d s Source #

typedPattern :: forall s l (d :: NodeWrap). s (Pattern l l d d) -> s (Type l l d d) -> Pattern λ l d s Source #

constructorPatternWithTypeApplications :: forall s l (d :: NodeWrap). s (Constructor l l d d) -> [s (Type l l d d)] -> [s (Pattern l l d d)] -> Pattern λ l d s Source #

wildcardRecordPattern :: forall s l (d :: NodeWrap). QualifiedName λ -> [s (FieldPattern l l d d)] -> Pattern λ l d s Source #

Instances

Instances details
ExtendedHaskell Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

hashLiteral :: forall l (d :: NodeWrap) (s :: NodeWrap). Value Language l d s -> Value Language l d s Source #

mdoExpression :: forall s l (d :: NodeWrap). s (GuardedExpression l l d d) -> Expression Language l d s Source #

parallelListComprehension :: forall s l (d :: NodeWrap). s (Expression l l d d) -> NonEmpty (s (Statement l l d d)) -> NonEmpty (s (Statement l l d d)) -> [NonEmpty (s (Statement l l d d))] -> Expression Language l d s Source #

tupleSectionExpression :: forall s l (d :: NodeWrap). NonEmpty (Maybe (s (Expression l l d d))) -> Expression Language l d s Source #

multiWayIfExpression :: forall s l (d :: NodeWrap). [s (GuardedExpression l l d d)] -> Expression Language l d s Source #

overloadedLabel :: forall l (d :: NodeWrap) (s :: NodeWrap). Text -> Expression Language l d s Source #

getField :: forall s l (d :: NodeWrap). s (Expression l l d d) -> Name Language -> Expression Language l d s Source #

fieldProjection :: forall l (d :: NodeWrap) (s :: NodeWrap). NonEmpty (Name Language) -> Expression Language l d s Source #

wildcardRecordExpression :: forall s l (d :: NodeWrap). QualifiedName Language -> [s (FieldBinding l l d d)] -> Expression Language l d s Source #

recursiveStatement :: forall s l (d :: NodeWrap). [s (Statement l l d d)] -> Statement Language l d s Source #

safeImportDeclaration :: forall s l (d :: NodeWrap). Bool -> ModuleName Language -> Maybe (ModuleName Language) -> Maybe (s (ImportSpecification l l d d)) -> Import Language l d s Source #

packageQualifiedImportDeclaration :: forall s l (d :: NodeWrap). Bool -> Text -> ModuleName Language -> Maybe (ModuleName Language) -> Maybe (s (ImportSpecification l l d d)) -> Import Language l d s Source #

safePackageQualifiedImportDeclaration :: forall s l (d :: NodeWrap). Bool -> Text -> ModuleName Language -> Maybe (ModuleName Language) -> Maybe (s (ImportSpecification l l d d)) -> Import Language l d s Source #

infixTypeApplication :: forall s l (d :: NodeWrap). s (Type l l d d) -> QualifiedName Language -> s (Type l l d d) -> Type Language l d s Source #

infixTypeLHSApplication :: forall l (d :: NodeWrap) (s :: NodeWrap). TypeVarBinding Language l d s -> Name Language -> TypeVarBinding Language l d s -> TypeLHS Language l d s Source #

typeLHSApplication :: forall s l (d :: NodeWrap). s (TypeLHS l l d d) -> TypeVarBinding Language l d s -> TypeLHS Language l d s Source #

simpleKindedTypeLHS :: forall l (d :: NodeWrap) (s :: NodeWrap). Name Language -> [TypeVarBinding Language l d s] -> TypeLHS Language l d s Source #

existentialConstructor :: forall l (d :: NodeWrap) s. [TypeVarBinding Language l d s] -> s (Context l l d d) -> s (DataConstructor l l d d) -> DataConstructor Language l d s Source #

explicitlyScopedInstanceDeclaration :: forall l (d :: NodeWrap) s. [TypeVarBinding Language l d s] -> s (Context l l d d) -> s (ClassInstanceLHS l l d d) -> [s (Declaration l l d d)] -> Declaration Language l d s Source #

forallType :: forall l (d :: NodeWrap) s. [TypeVarBinding Language l d s] -> s (Type l l d d) -> Type Language l d s Source #

constrainedType :: forall s l (d :: NodeWrap). s (Context l l d d) -> s (Type l l d d) -> Type Language l d s Source #

kindedType :: forall s l (d :: NodeWrap). s (Type l l d d) -> s (Kind l l d d) -> Type Language l d s Source #

typeWildcard :: forall l (d :: NodeWrap) (s :: NodeWrap). Type Language l d s Source #

groundType :: forall l (d :: NodeWrap) (s :: NodeWrap). Type Language l d s Source #

explicitlyKindedTypeVariable :: forall s l (d :: NodeWrap). Name Language -> s (Kind l l d d) -> TypeVarBinding Language l d s Source #

implicitlyKindedTypeVariable :: forall l (d :: NodeWrap) (s :: NodeWrap). Name Language -> TypeVarBinding Language l d s Source #

inferredTypeVariable :: forall l (d :: NodeWrap) (s :: NodeWrap). Name Language -> TypeVarBinding Language l d s Source #

inferredExplicitlyKindedTypeVariable :: forall s l (d :: NodeWrap). Name Language -> s (Kind l l d d) -> TypeVarBinding Language l d s Source #

typeKind :: forall s l (d :: NodeWrap). s (Type l l d d) -> Kind Language l d s Source #

groundTypeKind :: forall l (d :: NodeWrap) (s :: NodeWrap). Type Language l d s Source #

typeRoleDeclaration :: forall l (d :: NodeWrap) (s :: NodeWrap). QualifiedName Language -> [TypeRole Language] -> Declaration Language l d s Source #

kindedDataDeclaration :: forall s l (d :: NodeWrap). s (Context l l d d) -> s (TypeLHS l l d d) -> s (Kind l l d d) -> [s (DataConstructor l l d d)] -> [s (DerivingClause l l d d)] -> Declaration Language l d s Source #

kindedNewtypeDeclaration :: forall s l (d :: NodeWrap). s (Context l l d d) -> s (TypeLHS l l d d) -> s (Kind l l d d) -> s (DataConstructor l l d d) -> [s (DerivingClause l l d d)] -> Declaration Language l d s Source #

gadtDeclaration :: forall s l (d :: NodeWrap). s (TypeLHS l l d d) -> Maybe (s (Kind l l d d)) -> [s (GADTConstructor l l d d)] -> [s (DerivingClause l l d d)] -> Declaration Language l d s Source #

gadtNewtypeDeclaration :: forall s l (d :: NodeWrap). s (TypeLHS l l d d) -> Maybe (s (Kind l l d d)) -> s (GADTConstructor l l d d) -> [s (DerivingClause l l d d)] -> Declaration Language l d s Source #

gadtConstructors :: forall l (d :: NodeWrap) s. NonEmpty (Name Language) -> [TypeVarBinding Language l d s] -> s (Context l l d d) -> s (Type l l d d) -> GADTConstructor Language l d s Source #

recordFunctionType :: forall s l (d :: NodeWrap). [s (FieldDeclaration l l d d)] -> s (Type l l d d) -> Type Language l d s Source #

multiplicityFunctionType :: forall s l (d :: NodeWrap). s (Type l l d d) -> s (Type l l d d) -> s (Type l l d d) -> Type Language l d s Source #

linearFunctionType :: forall s l (d :: NodeWrap). s (Type l l d d) -> s (Type l l d d) -> Type Language l d s Source #

punnedFieldBinding :: forall l (d :: NodeWrap) (s :: NodeWrap). QualifiedName Language -> FieldBinding Language l d s Source #

punnedFieldPattern :: forall l (d :: NodeWrap) (s :: NodeWrap). QualifiedName Language -> FieldPattern Language l d s Source #

dataFamilyDeclaration :: forall s l (d :: NodeWrap). s (TypeLHS l l d d) -> Maybe (s (Kind l l d d)) -> Declaration Language l d s Source #

openTypeFamilyDeclaration :: forall s l (d :: NodeWrap). s (TypeLHS l l d d) -> Maybe (s (Kind l l d d)) -> Declaration Language l d s Source #

closedTypeFamilyDeclaration :: forall s l (d :: NodeWrap). s (TypeLHS l l d d) -> Maybe (s (Kind l l d d)) -> [s (Declaration l l d d)] -> Declaration Language l d s Source #

injectiveOpenTypeFamilyDeclaration :: forall s l (d :: NodeWrap). s (TypeLHS l l d d) -> TypeVarBinding Language l d s -> Maybe (Name Language, NonEmpty (Name Language)) -> Declaration Language l d s Source #

injectiveClosedTypeFamilyDeclaration :: forall s l (d :: NodeWrap). s (TypeLHS l l d d) -> TypeVarBinding Language l d s -> Maybe (Name Language, NonEmpty (Name Language)) -> [s (Declaration l l d d)] -> Declaration Language l d s Source #

dataFamilyInstance :: forall l (d :: NodeWrap) s. [TypeVarBinding Language l d s] -> s (Context l l d d) -> s (ClassInstanceLHS l l d d) -> Maybe (s (Kind l l d d)) -> [s (DataConstructor l l d d)] -> [s (DerivingClause l l d d)] -> Declaration Language l d s Source #

newtypeFamilyInstance :: forall l (d :: NodeWrap) s. [TypeVarBinding Language l d s] -> s (Context l l d d) -> s (ClassInstanceLHS l l d d) -> Maybe (s (Kind l l d d)) -> s (DataConstructor l l d d) -> [s (DerivingClause l l d d)] -> Declaration Language l d s Source #

gadtDataFamilyInstance :: forall l (d :: NodeWrap) s. [TypeVarBinding Language l d s] -> s (ClassInstanceLHS l l d d) -> Maybe (s (Kind l l d d)) -> [s (GADTConstructor l l d d)] -> [s (DerivingClause l l d d)] -> Declaration Language l d s Source #

gadtNewtypeFamilyInstance :: forall l (d :: NodeWrap) s. [TypeVarBinding Language l d s] -> s (ClassInstanceLHS l l d d) -> Maybe (s (Kind l l d d)) -> s (GADTConstructor l l d d) -> [s (DerivingClause l l d d)] -> Declaration Language l d s Source #

typeFamilyInstance :: forall l (d :: NodeWrap) s. [TypeVarBinding Language l d s] -> s (ClassInstanceLHS l l d d) -> s (Type l l d d) -> Declaration Language l d s Source #

classReferenceInstanceLHS :: forall l (d :: NodeWrap) (s :: NodeWrap). QualifiedName Language -> ClassInstanceLHS Language l d s Source #

infixTypeClassInstanceLHS :: forall s l (d :: NodeWrap). s (Type l l d d) -> QualifiedName Language -> s (Type l l d d) -> ClassInstanceLHS Language l d s Source #

classInstanceLHSApplication :: forall s l (d :: NodeWrap). s (ClassInstanceLHS l l d d) -> s (Type l l d d) -> ClassInstanceLHS Language l d s Source #

classInstanceLHSKindApplication :: forall s l (d :: NodeWrap). s (ClassInstanceLHS l l d d) -> s (Kind l l d d) -> ClassInstanceLHS Language l d s Source #

kindSignature :: forall s l (d :: NodeWrap). Name Language -> s (Kind l l d d) -> Declaration Language l d s Source #

typeEquality :: forall s l (d :: NodeWrap). s (Type l l d d) -> s (Type l l d d) -> Context Language l d s Source #

typeConstraint :: forall s l (d :: NodeWrap). s (Type l l d d) -> Context Language l d s Source #

constraintType :: forall s l (d :: NodeWrap). s (Context l l d d) -> Type Language l d s Source #

inferredRole :: TypeRole Language Source #

nominalRole :: TypeRole Language Source #

representationalRole :: TypeRole Language Source #

phantomRole :: TypeRole Language Source #

promotedConstructorType :: forall s l (d :: NodeWrap). s (Constructor l l d d) -> Type Language l d s Source #

promotedTupleType :: forall s l (d :: NodeWrap). [s (Type l l d d)] -> Type Language l d s Source #

promotedListType :: forall s l (d :: NodeWrap). [s (Type l l d d)] -> Type Language l d s Source #

promotedIntegerLiteral :: forall l (d :: NodeWrap) (s :: NodeWrap). Integer -> Type Language l d s Source #

promotedCharLiteral :: forall l (d :: NodeWrap) (s :: NodeWrap). Char -> Type Language l d s Source #

promotedStringLiteral :: forall l (d :: NodeWrap) (s :: NodeWrap). Text -> Type Language l d s Source #

promotedInfixTypeApplication :: forall s l (d :: NodeWrap). s (Type l l d d) -> QualifiedName Language -> s (Type l l d d) -> Type Language l d s Source #

visibleDependentType :: forall l (d :: NodeWrap) s. [TypeVarBinding Language l d s] -> s (Type l l d d) -> Type Language l d s Source #

visibleTypeApplication :: forall s l (d :: NodeWrap). s (Expression l l d d) -> s (Type l l d d) -> Expression Language l d s Source #

visibleKindApplication :: forall s l (d :: NodeWrap). s (Type l l d d) -> s (Kind l l d d) -> Type Language l d s Source #

typedPattern :: forall s l (d :: NodeWrap). s (Pattern l l d d) -> s (Type l l d d) -> Pattern Language l d s Source #

constructorPatternWithTypeApplications :: forall s l (d :: NodeWrap). s (Constructor l l d d) -> [s (Type l l d d)] -> [s (Pattern l l d d)] -> Pattern Language l d s Source #

wildcardRecordPattern :: forall s l (d :: NodeWrap). QualifiedName Language -> [s (FieldPattern l l d d)] -> Pattern Language l d s Source #

Constraint synonyms

type UniversallyApplicable t l (d :: NodeWrap) = (At t (GADTConstructor l l d d), At t (Kind l l d d), At t (TypeVarBinding l l d d), At t (DerivingStrategy l l d d), At t (FunctionalDependency l l d d), At t (PatternLHS l l d d), At t (PatternEquationLHS l l d d), At t (PatternEquationClause l l d d), UniversallyApplicable t l d) Source #

Constraint UniversallyApplicable t l d means that the transformation t can be applied to any AST node of language l with subtrees wrapped in d.

type DeeplyFunctor t l = (Functor t (GADTConstructor l l), Functor t (Kind l l), Functor t (TypeVarBinding l l), Functor t (DerivingStrategy l l), Functor t (FunctionalDependency l l), Functor t (PatternLHS l l), Functor t (PatternEquationLHS l l), Functor t (PatternEquationClause l l), DeeplyFunctor t l) Source #

Named collection of constraints DeeplyFunctor t l means that every AST node of language l is a Functor for transformation t.

type DeeplyFoldable t l = (Foldable t (GADTConstructor l l), Foldable t (Kind l l), Foldable t (TypeVarBinding l l), Foldable t (DerivingStrategy l l), Foldable t (FunctionalDependency l l), Foldable t (LambdaCasesAlternative l l), Foldable t (PatternLHS l l), Foldable t (PatternEquationLHS l l), Foldable t (PatternEquationClause l l), DeeplyFoldable t l) Source #

Named collection of constraints DeeplyFoldable t l means that every AST node of language l is Foldable for transformation t.

type DeeplyTraversable t l = (Traversable t (GADTConstructor l l), Traversable t (Kind l l), Traversable t (TypeVarBinding l l), Traversable t (DerivingStrategy l l), Traversable t (FunctionalDependency l l), Traversable t (PatternLHS l l), Traversable t (PatternEquationLHS l l), Traversable t (PatternEquationClause l l), DeeplyTraversable t l) Source #

Named collection of constraints DeeplyTraversable t l means that every AST node of language l is Traversable for transformation t.

AST node types for language extensions

type family PatternLHS λ :: TreeNodeSubKind Source #

Instances

Instances details
type PatternLHS Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

type family Associativity λ = (x :: Type) | x -> λ Source #

type family CallSafety λ = (x :: Type) | x -> λ Source #

Instances

Instances details
type CallSafety Language Source # 
Instance details

Defined in Language.Haskell.AST

type CallSafety Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

type family CaseAlternative λ = (x :: TreeNodeSubKind) | x -> λ Source #

type family Constructor λ = (x :: TreeNodeSubKind) | x -> λ Source #

Instances

Instances details
type Constructor Language Source # 
Instance details

Defined in Language.Haskell.AST

type Constructor Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

type family Context λ = (x :: TreeNodeSubKind) | x -> λ Source #

Instances

Instances details
type Context Language Source # 
Instance details

Defined in Language.Haskell.AST

type Context Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

type family DataConstructor λ = (x :: TreeNodeSubKind) | x -> λ Source #

type family Declaration λ = (x :: TreeNodeSubKind) | x -> λ Source #

Instances

Instances details
type Declaration Language Source # 
Instance details

Defined in Language.Haskell.AST

type Declaration Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

type family DerivingClause λ = (x :: TreeNodeSubKind) | x -> λ Source #

type family EquationLHS λ = (x :: TreeNodeSubKind) | x -> λ Source #

Instances

Instances details
type EquationLHS Language Source # 
Instance details

Defined in Language.Haskell.AST

type EquationLHS Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

type family EquationRHS λ = (x :: TreeNodeSubKind) | x -> λ Source #

Instances

Instances details
type EquationRHS Language Source # 
Instance details

Defined in Language.Haskell.AST

type EquationRHS Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

type family Export λ = (x :: TreeNodeSubKind) | x -> λ Source #

Instances

Instances details
type Export Language Source # 
Instance details

Defined in Language.Haskell.AST

type Export Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

type family Expression λ = (x :: TreeNodeSubKind) | x -> λ Source #

Instances

Instances details
type Expression Language Source # 
Instance details

Defined in Language.Haskell.AST

type Expression Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

type family FieldBinding λ = (x :: TreeNodeSubKind) | x -> λ Source #

Instances

Instances details
type FieldBinding Language Source # 
Instance details

Defined in Language.Haskell.AST

type FieldBinding Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

type family FieldPattern λ = (x :: TreeNodeSubKind) | x -> λ Source #

Instances

Instances details
type FieldPattern Language Source # 
Instance details

Defined in Language.Haskell.AST

type FieldPattern Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

class Haskell λ where Source #

An abstract finally-tagless specification of a Haskell 2010 language

Associated Types

type Module λ = (x :: TreeNodeSubKind) | x -> λ Source #

type Declaration λ = (x :: TreeNodeSubKind) | x -> λ Source #

type Expression λ = (x :: TreeNodeSubKind) | x -> λ Source #

type Type λ = (x :: TreeNodeSubKind) | x -> λ Source #

type EquationLHS λ = (x :: TreeNodeSubKind) | x -> λ Source #

type EquationRHS λ = (x :: TreeNodeSubKind) | x -> λ Source #

type GuardedExpression λ = (x :: TreeNodeSubKind) | x -> λ Source #

type Pattern λ = (x :: TreeNodeSubKind) | x -> λ Source #

type Statement λ = (x :: TreeNodeSubKind) | x -> λ Source #

type ClassInstanceLHS λ = (x :: TreeNodeSubKind) | x -> λ Source #

type TypeLHS λ = (x :: TreeNodeSubKind) | x -> λ Source #

type Import λ = (x :: TreeNodeSubKind) | x -> λ Source #

type ImportSpecification λ = (x :: TreeNodeSubKind) | x -> λ Source #

type ImportItem λ = (x :: TreeNodeSubKind) | x -> λ Source #

type Export λ = (x :: TreeNodeSubKind) | x -> λ Source #

type Context λ = (x :: TreeNodeSubKind) | x -> λ Source #

type DataConstructor λ = (x :: TreeNodeSubKind) | x -> λ Source #

type DerivingClause λ = (x :: TreeNodeSubKind) | x -> λ Source #

type FieldDeclaration λ = (x :: TreeNodeSubKind) | x -> λ Source #

type FieldBinding λ = (x :: TreeNodeSubKind) | x -> λ Source #

type FieldPattern λ = (x :: TreeNodeSubKind) | x -> λ Source #

type CaseAlternative λ = (x :: TreeNodeSubKind) | x -> λ Source #

type Constructor λ = (x :: TreeNodeSubKind) | x -> λ Source #

type Value λ = (x :: TreeNodeSubKind) | x -> λ Source #

type CallingConvention λ = (x :: Type) | x -> λ Source #

type CallSafety λ = (x :: Type) | x -> λ Source #

type Associativity λ = (x :: Type) | x -> λ Source #

type Members λ = (x :: Type) | x -> λ Source #

type Name λ = (x :: Type) | x -> λ Source #

type ModuleName λ = (x :: Type) | x -> λ Source #

type QualifiedName λ = (x :: Type) | x -> λ Source #

Methods

anonymousModule :: forall s l (d :: NodeWrap). [s (Import l l d d)] -> [s (Declaration l l d d)] -> Module λ l d s Source #

namedModule :: forall s l (d :: NodeWrap). ModuleName λ -> Maybe [s (Export l l d d)] -> [s (Import l l d d)] -> [s (Declaration l l d d)] -> Module λ l d s Source #

withLanguagePragma :: forall s l (d :: NodeWrap). [ExtensionSwitch] -> s (Module l l d d) -> Module λ l d s Source #

exportClassOrType :: forall l (d :: NodeWrap) (s :: NodeWrap). QualifiedName λ -> Maybe (Members λ) -> Export λ l d s Source #

exportVar :: forall l (d :: NodeWrap) (s :: NodeWrap). QualifiedName λ -> Export λ l d s Source #

reExportModule :: forall l (d :: NodeWrap) (s :: NodeWrap). ModuleName λ -> Export λ l d s Source #

importDeclaration :: forall s l (d :: NodeWrap). Bool -> ModuleName λ -> Maybe (ModuleName λ) -> Maybe (s (ImportSpecification l l d d)) -> Import λ l d s Source #

excludedImports :: forall s l (d :: NodeWrap). [s (ImportItem l l d d)] -> ImportSpecification λ l d s Source #

includedImports :: forall s l (d :: NodeWrap). [s (ImportItem l l d d)] -> ImportSpecification λ l d s Source #

importClassOrType :: forall l (d :: NodeWrap) (s :: NodeWrap). Name λ -> Maybe (Members λ) -> ImportItem λ l d s Source #

importVar :: forall l (d :: NodeWrap) (s :: NodeWrap). Name λ -> ImportItem λ l d s Source #

allMembers :: Members λ Source #

memberList :: [Name λ] -> Members λ Source #

classDeclaration :: forall s l (d :: NodeWrap). s (Context l l d d) -> s (TypeLHS l l d d) -> [s (Declaration l l d d)] -> Declaration λ l d s Source #

dataDeclaration :: forall s l (d :: NodeWrap). s (Context l l d d) -> s (TypeLHS l l d d) -> [s (DataConstructor l l d d)] -> [s (DerivingClause l l d d)] -> Declaration λ l d s Source #

defaultDeclaration :: forall s l (d :: NodeWrap). [s (Type l l d d)] -> Declaration λ l d s Source #

equationDeclaration :: forall s l (d :: NodeWrap). s (EquationLHS l l d d) -> s (EquationRHS l l d d) -> [s (Declaration l l d d)] -> Declaration λ l d s Source #

fixityDeclaration :: forall l (d :: NodeWrap) (s :: NodeWrap). Associativity λ -> Maybe Int -> NonEmpty (Name λ) -> Declaration λ l d s Source #

foreignExport :: forall s l (d :: NodeWrap). CallingConvention λ -> Maybe Text -> Name λ -> s (Type l l d d) -> Declaration λ l d s Source #

foreignImport :: forall s l (d :: NodeWrap). CallingConvention λ -> Maybe (CallSafety λ) -> Maybe Text -> Name λ -> s (Type l l d d) -> Declaration λ l d s Source #

instanceDeclaration :: forall s l (d :: NodeWrap). s (Context l l d d) -> s (ClassInstanceLHS l l d d) -> [s (Declaration l l d d)] -> Declaration λ l d s Source #

newtypeDeclaration :: forall s l (d :: NodeWrap). s (Context l l d d) -> s (TypeLHS l l d d) -> s (DataConstructor l l d d) -> [s (DerivingClause l l d d)] -> Declaration λ l d s Source #

typeSynonymDeclaration :: forall s l (d :: NodeWrap). s (TypeLHS l l d d) -> s (Type l l d d) -> Declaration λ l d s Source #

typeSignature :: forall s l (d :: NodeWrap). NonEmpty (Name λ) -> s (Context l l d d) -> s (Type l l d d) -> Declaration λ l d s Source #

applyExpression :: forall s l (d :: NodeWrap). s (Expression l l d d) -> s (Expression l l d d) -> Expression λ l d s Source #

conditionalExpression :: forall s l (d :: NodeWrap). s (Expression l l d d) -> s (Expression l l d d) -> s (Expression l l d d) -> Expression λ l d s Source #

constructorExpression :: forall s l (d :: NodeWrap). s (Constructor l l d d) -> Expression λ l d s Source #

caseExpression :: forall s l (d :: NodeWrap). s (Expression l l d d) -> [s (CaseAlternative l l d d)] -> Expression λ l d s Source #

doExpression :: forall s l (d :: NodeWrap). s (GuardedExpression l l d d) -> Expression λ l d s Source #

infixExpression :: forall s l (d :: NodeWrap). s (Expression l l d d) -> s (Expression l l d d) -> s (Expression l l d d) -> Expression λ l d s Source #

leftSectionExpression :: forall s l (d :: NodeWrap). s (Expression l l d d) -> QualifiedName λ -> Expression λ l d s Source #

lambdaExpression :: forall s l (d :: NodeWrap). [s (Pattern l l d d)] -> s (Expression l l d d) -> Expression λ l d s Source #

letExpression :: forall s l (d :: NodeWrap). [s (Declaration l l d d)] -> s (Expression l l d d) -> Expression λ l d s Source #

listComprehension :: forall s l (d :: NodeWrap). s (Expression l l d d) -> NonEmpty (s (Statement l l d d)) -> Expression λ l d s Source #

listExpression :: forall s l (d :: NodeWrap). [s (Expression l l d d)] -> Expression λ l d s Source #

literalExpression :: forall s l (d :: NodeWrap). s (Value l l d d) -> Expression λ l d s Source #

negate :: forall l (d :: NodeWrap) (s :: NodeWrap). Expression λ l d s Source #

recordExpression :: forall s l (d :: NodeWrap). s (Expression l l d d) -> [s (FieldBinding l l d d)] -> Expression λ l d s Source #

referenceExpression :: forall l (d :: NodeWrap). QualifiedName λ -> Expression λ l d d Source #

rightSectionExpression :: forall s l (d :: NodeWrap). QualifiedName λ -> s (Expression l l d d) -> Expression λ l d s Source #

sequenceExpression :: forall s l (d :: NodeWrap). s (Expression l l d d) -> Maybe (s (Expression l l d d)) -> Maybe (s (Expression l l d d)) -> Expression λ l d s Source #

tupleExpression :: forall s l (d :: NodeWrap). NonEmpty (s (Expression l l d d)) -> Expression λ l d s Source #

typedExpression :: forall s l (d :: NodeWrap). s (Expression l l d d) -> s (Type l l d d) -> Expression λ l d s Source #

asPattern :: forall s l (d :: NodeWrap). Name λ -> s (Pattern l l d d) -> Pattern λ l d s Source #

constructorPattern :: forall s l (d :: NodeWrap). s (Constructor l l d d) -> [s (Pattern l l d d)] -> Pattern λ l d s Source #

infixPattern :: forall s l (d :: NodeWrap). s (Pattern l l d d) -> QualifiedName λ -> s (Pattern l l d d) -> Pattern λ l d s Source #

irrefutablePattern :: forall s l (d :: NodeWrap). s (Pattern l l d d) -> Pattern λ l d s Source #

listPattern :: forall s l (d :: NodeWrap). [s (Pattern l l d d)] -> Pattern λ l d s Source #

literalPattern :: forall s l (d :: NodeWrap). s (Value l l d d) -> Pattern λ l d s Source #

recordPattern :: forall s l (d :: NodeWrap). QualifiedName λ -> [s (FieldPattern l l d d)] -> Pattern λ l d s Source #

tuplePattern :: forall s l (d :: NodeWrap). NonEmpty (s (Pattern l l d d)) -> Pattern λ l d s Source #

variablePattern :: forall l (d :: NodeWrap) (s :: NodeWrap). Name λ -> Pattern λ l d s Source #

wildcardPattern :: forall l (d :: NodeWrap) (s :: NodeWrap). Pattern λ l d s Source #

constructorType :: forall s l (d :: NodeWrap). s (Constructor l l d d) -> Type λ l d s Source #

functionConstructorType :: forall l (d :: NodeWrap) (s :: NodeWrap). Type λ l d s Source #

functionType :: forall s l (d :: NodeWrap). s (Type l l d d) -> s (Type l l d d) -> Type λ l d s Source #

listType :: forall s l (d :: NodeWrap). s (Type l l d d) -> Type λ l d s Source #

strictType :: forall s l (d :: NodeWrap). s (Type l l d d) -> Type λ l d s Source #

tupleType :: forall s l (d :: NodeWrap). NonEmpty (s (Type l l d d)) -> Type λ l d s Source #

typeApplication :: forall s l (d :: NodeWrap). s (Type l l d d) -> s (Type l l d d) -> Type λ l d s Source #

typeVariable :: forall l (d :: NodeWrap) (s :: NodeWrap). Name λ -> Type λ l d s Source #

constructorReference :: forall l (d :: NodeWrap) (s :: NodeWrap). QualifiedName λ -> Constructor λ l d s Source #

emptyListConstructor :: forall l (d :: NodeWrap) (s :: NodeWrap). Constructor λ l d s Source #

tupleConstructor :: forall l (d :: NodeWrap) (s :: NodeWrap). Int -> Constructor λ l d s Source #

unitConstructor :: forall l (d :: NodeWrap) (s :: NodeWrap). Constructor λ l d s Source #

constructor :: forall s l (d :: NodeWrap). Name λ -> [s (Type l l d d)] -> DataConstructor λ l d s Source #

recordConstructor :: forall s l (d :: NodeWrap). Name λ -> [s (FieldDeclaration l l d d)] -> DataConstructor λ l d s Source #

constructorFields :: forall s l (d :: NodeWrap). NonEmpty (Name λ) -> s (Type l l d d) -> FieldDeclaration λ l d s Source #

fieldBinding :: forall s l (d :: NodeWrap). QualifiedName λ -> s (Expression l l d d) -> FieldBinding λ l d s Source #

fieldPattern :: forall s l (d :: NodeWrap). QualifiedName λ -> s (Pattern l l d d) -> FieldPattern λ l d s Source #

simpleDerive :: forall l (d :: NodeWrap) (s :: NodeWrap). QualifiedName λ -> DerivingClause λ l d s Source #

typeClassInstanceLHS :: forall s l (d :: NodeWrap). QualifiedName λ -> s (Type l l d d) -> ClassInstanceLHS λ l d s Source #

simpleTypeLHS :: forall l (d :: NodeWrap) (s :: NodeWrap). Name λ -> [Name λ] -> TypeLHS λ l d s Source #

prefixLHS :: forall s l (d :: NodeWrap). s (EquationLHS l l d d) -> NonEmpty (s (Pattern l l d d)) -> EquationLHS λ l d s Source #

infixLHS :: forall s l (d :: NodeWrap). s (Pattern l l d d) -> Name λ -> s (Pattern l l d d) -> EquationLHS λ l d s Source #

patternLHS :: forall s l (d :: NodeWrap). s (Pattern l l d d) -> EquationLHS λ l d s Source #

variableLHS :: forall l (d :: NodeWrap) (s :: NodeWrap). Name λ -> EquationLHS λ l d s Source #

caseAlternative :: forall s l (d :: NodeWrap). s (Pattern l l d d) -> s (EquationRHS l l d d) -> [s (Declaration l l d d)] -> CaseAlternative λ l d s Source #

guardedRHS :: forall s l (d :: NodeWrap). NonEmpty (s (GuardedExpression l l d d)) -> EquationRHS λ l d s Source #

normalRHS :: forall s l (d :: NodeWrap). s (Expression l l d d) -> EquationRHS λ l d s Source #

guardedExpression :: forall s l (d :: NodeWrap). [s (Statement l l d d)] -> s (Expression l l d d) -> GuardedExpression λ l d s Source #

classConstraint :: forall s l (d :: NodeWrap). QualifiedName λ -> s (Type l l d d) -> Context λ l d s Source #

constraints :: forall s l (d :: NodeWrap). [s (Context l l d d)] -> Context λ l d s Source #

noContext :: forall l (d :: NodeWrap) (s :: NodeWrap). Context λ l d s Source #

bindStatement :: forall s l (d :: NodeWrap). s (Pattern l l d d) -> s (Expression l l d d) -> Statement λ l d s Source #

expressionStatement :: forall s l (d :: NodeWrap). s (Expression l l d d) -> Statement λ l d s Source #

letStatement :: forall s l (d :: NodeWrap). [s (Declaration l l d d)] -> Statement λ l d s Source #

charLiteral :: forall l (d :: NodeWrap) (s :: NodeWrap). Char -> Value λ l d s Source #

floatingLiteral :: forall l (d :: NodeWrap) (s :: NodeWrap). Rational -> Value λ l d s Source #

integerLiteral :: forall l (d :: NodeWrap) (s :: NodeWrap). Integer -> Value λ l d s Source #

stringLiteral :: forall l (d :: NodeWrap) (s :: NodeWrap). Text -> Value λ l d s Source #

name :: Text -> Name λ Source #

moduleName :: NonEmpty (Name λ) -> ModuleName λ Source #

qualifiedName :: Maybe (ModuleName λ) -> Name λ -> QualifiedName λ Source #

nonAssociative :: Associativity λ Source #

leftAssociative :: Associativity λ Source #

rightAssociative :: Associativity λ Source #

cCall :: CallingConvention λ Source #

cppCall :: CallingConvention λ Source #

dotNetCall :: CallingConvention λ Source #

jvmCall :: CallingConvention λ Source #

stdCall :: CallingConvention λ Source #

safeCall :: CallSafety λ Source #

unsafeCall :: CallSafety λ Source #

Instances

Instances details
Haskell Language Source # 
Instance details

Defined in Language.Haskell.AST

Associated Types

type Module Language 
Instance details

Defined in Language.Haskell.AST

type Declaration Language 
Instance details

Defined in Language.Haskell.AST

type Expression Language 
Instance details

Defined in Language.Haskell.AST

type Type Language 
Instance details

Defined in Language.Haskell.AST

type EquationLHS Language 
Instance details

Defined in Language.Haskell.AST

type EquationRHS Language 
Instance details

Defined in Language.Haskell.AST

type GuardedExpression Language 
Instance details

Defined in Language.Haskell.AST

type Pattern Language 
Instance details

Defined in Language.Haskell.AST

type Statement Language 
Instance details

Defined in Language.Haskell.AST

type ClassInstanceLHS Language 
Instance details

Defined in Language.Haskell.AST

type TypeLHS Language 
Instance details

Defined in Language.Haskell.AST

type Import Language 
Instance details

Defined in Language.Haskell.AST

type ImportSpecification Language 
Instance details

Defined in Language.Haskell.AST

type ImportItem Language 
Instance details

Defined in Language.Haskell.AST

type Export Language 
Instance details

Defined in Language.Haskell.AST

type Context Language 
Instance details

Defined in Language.Haskell.AST

type DataConstructor Language 
Instance details

Defined in Language.Haskell.AST

type DerivingClause Language 
Instance details

Defined in Language.Haskell.AST

type FieldDeclaration Language 
Instance details

Defined in Language.Haskell.AST

type FieldBinding Language 
Instance details

Defined in Language.Haskell.AST

type FieldPattern Language 
Instance details

Defined in Language.Haskell.AST

type CaseAlternative Language 
Instance details

Defined in Language.Haskell.AST

type Constructor Language 
Instance details

Defined in Language.Haskell.AST

type Value Language 
Instance details

Defined in Language.Haskell.AST

type CallingConvention Language 
Instance details

Defined in Language.Haskell.AST

type CallSafety Language 
Instance details

Defined in Language.Haskell.AST

type Associativity Language 
Instance details

Defined in Language.Haskell.AST

type Members Language 
Instance details

Defined in Language.Haskell.AST

type Name Language 
Instance details

Defined in Language.Haskell.AST

type ModuleName Language 
Instance details

Defined in Language.Haskell.AST

type QualifiedName Language 
Instance details

Defined in Language.Haskell.AST

Methods

anonymousModule :: forall s l (d :: NodeWrap). [s (Import l l d d)] -> [s (Declaration l l d d)] -> Module Language l d s Source #

namedModule :: forall s l (d :: NodeWrap). ModuleName Language -> Maybe [s (Export l l d d)] -> [s (Import l l d d)] -> [s (Declaration l l d d)] -> Module Language l d s Source #

withLanguagePragma :: forall s l (d :: NodeWrap). [ExtensionSwitch] -> s (Module l l d d) -> Module Language l d s Source #

exportClassOrType :: forall l (d :: NodeWrap) (s :: NodeWrap). QualifiedName Language -> Maybe (Members Language) -> Export Language l d s Source #

exportVar :: forall l (d :: NodeWrap) (s :: NodeWrap). QualifiedName Language -> Export Language l d s Source #

reExportModule :: forall l (d :: NodeWrap) (s :: NodeWrap). ModuleName Language -> Export Language l d s Source #

importDeclaration :: forall s l (d :: NodeWrap). Bool -> ModuleName Language -> Maybe (ModuleName Language) -> Maybe (s (ImportSpecification l l d d)) -> Import Language l d s Source #

excludedImports :: forall s l (d :: NodeWrap). [s (ImportItem l l d d)] -> ImportSpecification Language l d s Source #

includedImports :: forall s l (d :: NodeWrap). [s (ImportItem l l d d)] -> ImportSpecification Language l d s Source #

importClassOrType :: forall l (d :: NodeWrap) (s :: NodeWrap). Name Language -> Maybe (Members Language) -> ImportItem Language l d s Source #

importVar :: forall l (d :: NodeWrap) (s :: NodeWrap). Name Language -> ImportItem Language l d s Source #

allMembers :: Members Language Source #

memberList :: [Name Language] -> Members Language Source #

classDeclaration :: forall s l (d :: NodeWrap). s (Context l l d d) -> s (TypeLHS l l d d) -> [s (Declaration l l d d)] -> Declaration Language l d s Source #

dataDeclaration :: forall s l (d :: NodeWrap). s (Context l l d d) -> s (TypeLHS l l d d) -> [s (DataConstructor l l d d)] -> [s (DerivingClause l l d d)] -> Declaration Language l d s Source #

defaultDeclaration :: forall s l (d :: NodeWrap). [s (Type l l d d)] -> Declaration Language l d s Source #

equationDeclaration :: forall s l (d :: NodeWrap). s (EquationLHS l l d d) -> s (EquationRHS l l d d) -> [s (Declaration l l d d)] -> Declaration Language l d s Source #

fixityDeclaration :: forall l (d :: NodeWrap) (s :: NodeWrap). Associativity Language -> Maybe Int -> NonEmpty (Name Language) -> Declaration Language l d s Source #

foreignExport :: forall s l (d :: NodeWrap). CallingConvention Language -> Maybe Text -> Name Language -> s (Type l l d d) -> Declaration Language l d s Source #

foreignImport :: forall s l (d :: NodeWrap). CallingConvention Language -> Maybe (CallSafety Language) -> Maybe Text -> Name Language -> s (Type l l d d) -> Declaration Language l d s Source #

instanceDeclaration :: forall s l (d :: NodeWrap). s (Context l l d d) -> s (ClassInstanceLHS l l d d) -> [s (Declaration l l d d)] -> Declaration Language l d s Source #

newtypeDeclaration :: forall s l (d :: NodeWrap). s (Context l l d d) -> s (TypeLHS l l d d) -> s (DataConstructor l l d d) -> [s (DerivingClause l l d d)] -> Declaration Language l d s Source #

typeSynonymDeclaration :: forall s l (d :: NodeWrap). s (TypeLHS l l d d) -> s (Type l l d d) -> Declaration Language l d s Source #

typeSignature :: forall s l (d :: NodeWrap). NonEmpty (Name Language) -> s (Context l l d d) -> s (Type l l d d) -> Declaration Language l d s Source #

applyExpression :: forall s l (d :: NodeWrap). s (Expression l l d d) -> s (Expression l l d d) -> Expression Language l d s Source #

conditionalExpression :: forall s l (d :: NodeWrap). s (Expression l l d d) -> s (Expression l l d d) -> s (Expression l l d d) -> Expression Language l d s Source #

constructorExpression :: forall s l (d :: NodeWrap). s (Constructor l l d d) -> Expression Language l d s Source #

caseExpression :: forall s l (d :: NodeWrap). s (Expression l l d d) -> [s (CaseAlternative l l d d)] -> Expression Language l d s Source #

doExpression :: forall s l (d :: NodeWrap). s (GuardedExpression l l d d) -> Expression Language l d s Source #

infixExpression :: forall s l (d :: NodeWrap). s (Expression l l d d) -> s (Expression l l d d) -> s (Expression l l d d) -> Expression Language l d s Source #

leftSectionExpression :: forall s l (d :: NodeWrap). s (Expression l l d d) -> QualifiedName Language -> Expression Language l d s Source #

lambdaExpression :: forall s l (d :: NodeWrap). [s (Pattern l l d d)] -> s (Expression l l d d) -> Expression Language l d s Source #

letExpression :: forall s l (d :: NodeWrap). [s (Declaration l l d d)] -> s (Expression l l d d) -> Expression Language l d s Source #

listComprehension :: forall s l (d :: NodeWrap). s (Expression l l d d) -> NonEmpty (s (Statement l l d d)) -> Expression Language l d s Source #

listExpression :: forall s l (d :: NodeWrap). [s (Expression l l d d)] -> Expression Language l d s Source #

literalExpression :: forall s l (d :: NodeWrap). s (Value l l d d) -> Expression Language l d s Source #

negate :: forall l (d :: NodeWrap) (s :: NodeWrap). Expression Language l d s Source #

recordExpression :: forall s l (d :: NodeWrap). s (Expression l l d d) -> [s (FieldBinding l l d d)] -> Expression Language l d s Source #

referenceExpression :: forall l (d :: NodeWrap). QualifiedName Language -> Expression Language l d d Source #

rightSectionExpression :: forall s l (d :: NodeWrap). QualifiedName Language -> s (Expression l l d d) -> Expression Language l d s Source #

sequenceExpression :: forall s l (d :: NodeWrap). s (Expression l l d d) -> Maybe (s (Expression l l d d)) -> Maybe (s (Expression l l d d)) -> Expression Language l d s Source #

tupleExpression :: forall s l (d :: NodeWrap). NonEmpty (s (Expression l l d d)) -> Expression Language l d s Source #

typedExpression :: forall s l (d :: NodeWrap). s (Expression l l d d) -> s (Type l l d d) -> Expression Language l d s Source #

asPattern :: forall s l (d :: NodeWrap). Name Language -> s (Pattern l l d d) -> Pattern Language l d s Source #

constructorPattern :: forall s l (d :: NodeWrap). s (Constructor l l d d) -> [s (Pattern l l d d)] -> Pattern Language l d s Source #

infixPattern :: forall s l (d :: NodeWrap). s (Pattern l l d d) -> QualifiedName Language -> s (Pattern l l d d) -> Pattern Language l d s Source #

irrefutablePattern :: forall s l (d :: NodeWrap). s (Pattern l l d d) -> Pattern Language l d s Source #

listPattern :: forall s l (d :: NodeWrap). [s (Pattern l l d d)] -> Pattern Language l d s Source #

literalPattern :: forall s l (d :: NodeWrap). s (Value l l d d) -> Pattern Language l d s Source #

recordPattern :: forall s l (d :: NodeWrap). QualifiedName Language -> [s (FieldPattern l l d d)] -> Pattern Language l d s Source #

tuplePattern :: forall s l (d :: NodeWrap). NonEmpty (s (Pattern l l d d)) -> Pattern Language l d s Source #

variablePattern :: forall l (d :: NodeWrap) (s :: NodeWrap). Name Language -> Pattern Language l d s Source #

wildcardPattern :: forall l (d :: NodeWrap) (s :: NodeWrap). Pattern Language l d s Source #

constructorType :: forall s l (d :: NodeWrap). s (Constructor l l d d) -> Type Language l d s Source #

functionConstructorType :: forall l (d :: NodeWrap) (s :: NodeWrap). Type Language l d s Source #

functionType :: forall s l (d :: NodeWrap). s (Type l l d d) -> s (Type l l d d) -> Type Language l d s Source #

listType :: forall s l (d :: NodeWrap). s (Type l l d d) -> Type Language l d s Source #

strictType :: forall s l (d :: NodeWrap). s (Type l l d d) -> Type Language l d s Source #

tupleType :: forall s l (d :: NodeWrap). NonEmpty (s (Type l l d d)) -> Type Language l d s Source #

typeApplication :: forall s l (d :: NodeWrap). s (Type l l d d) -> s (Type l l d d) -> Type Language l d s Source #

typeVariable :: forall l (d :: NodeWrap) (s :: NodeWrap). Name Language -> Type Language l d s Source #

constructorReference :: forall l (d :: NodeWrap) (s :: NodeWrap). QualifiedName Language -> Constructor Language l d s Source #

emptyListConstructor :: forall l (d :: NodeWrap) (s :: NodeWrap). Constructor Language l d s Source #

tupleConstructor :: forall l (d :: NodeWrap) (s :: NodeWrap). Int -> Constructor Language l d s Source #

unitConstructor :: forall l (d :: NodeWrap) (s :: NodeWrap). Constructor Language l d s Source #

constructor :: forall s l (d :: NodeWrap). Name Language -> [s (Type l l d d)] -> DataConstructor Language l d s Source #

recordConstructor :: forall s l (d :: NodeWrap). Name Language -> [s (FieldDeclaration l l d d)] -> DataConstructor Language l d s Source #

constructorFields :: forall s l (d :: NodeWrap). NonEmpty (Name Language) -> s (Type l l d d) -> FieldDeclaration Language l d s Source #

fieldBinding :: forall s l (d :: NodeWrap). QualifiedName Language -> s (Expression l l d d) -> FieldBinding Language l d s Source #

fieldPattern :: forall s l (d :: NodeWrap). QualifiedName Language -> s (Pattern l l d d) -> FieldPattern Language l d s Source #

simpleDerive :: forall l (d :: NodeWrap) (s :: NodeWrap). QualifiedName Language -> DerivingClause Language l d s Source #

typeClassInstanceLHS :: forall s l (d :: NodeWrap). QualifiedName Language -> s (Type l l d d) -> ClassInstanceLHS Language l d s Source #

simpleTypeLHS :: forall l (d :: NodeWrap) (s :: NodeWrap). Name Language -> [Name Language] -> TypeLHS Language l d s Source #

prefixLHS :: forall s l (d :: NodeWrap). s (EquationLHS l l d d) -> NonEmpty (s (Pattern l l d d)) -> EquationLHS Language l d s Source #

infixLHS :: forall s l (d :: NodeWrap). s (Pattern l l d d) -> Name Language -> s (Pattern l l d d) -> EquationLHS Language l d s Source #

patternLHS :: forall s l (d :: NodeWrap). s (Pattern l l d d) -> EquationLHS Language l d s Source #

variableLHS :: forall l (d :: NodeWrap) (s :: NodeWrap). Name Language -> EquationLHS Language l d s Source #

caseAlternative :: forall s l (d :: NodeWrap). s (Pattern l l d d) -> s (EquationRHS l l d d) -> [s (Declaration l l d d)] -> CaseAlternative Language l d s Source #

guardedRHS :: forall s l (d :: NodeWrap). NonEmpty (s (GuardedExpression l l d d)) -> EquationRHS Language l d s Source #

normalRHS :: forall s l (d :: NodeWrap). s (Expression l l d d) -> EquationRHS Language l d s Source #

guardedExpression :: forall s l (d :: NodeWrap). [s (Statement l l d d)] -> s (Expression l l d d) -> GuardedExpression Language l d s Source #

classConstraint :: forall s l (d :: NodeWrap). QualifiedName Language -> s (Type l l d d) -> Context Language l d s Source #

constraints :: forall s l (d :: NodeWrap). [s (Context l l d d)] -> Context Language l d s Source #

noContext :: forall l (d :: NodeWrap) (s :: NodeWrap). Context Language l d s Source #

bindStatement :: forall s l (d :: NodeWrap). s (Pattern l l d d) -> s (Expression l l d d) -> Statement Language l d s Source #

expressionStatement :: forall s l (d :: NodeWrap). s (Expression l l d d) -> Statement Language l d s Source #

letStatement :: forall s l (d :: NodeWrap). [s (Declaration l l d d)] -> Statement Language l d s Source #

charLiteral :: forall l (d :: NodeWrap) (s :: NodeWrap). Char -> Value Language l d s Source #

floatingLiteral :: forall l (d :: NodeWrap) (s :: NodeWrap). Rational -> Value Language l d s Source #

integerLiteral :: forall l (d :: NodeWrap) (s :: NodeWrap). Integer -> Value Language l d s Source #

stringLiteral :: forall l (d :: NodeWrap) (s :: NodeWrap). Text -> Value Language l d s Source #

name :: Text -> Name Language Source #

moduleName :: NonEmpty (Name Language) -> ModuleName Language Source #

qualifiedName :: Maybe (ModuleName Language) -> Name Language -> QualifiedName Language Source #

nonAssociative :: Associativity Language Source #

leftAssociative :: Associativity Language Source #

rightAssociative :: Associativity Language Source #

cCall :: CallingConvention Language Source #

cppCall :: CallingConvention Language Source #

dotNetCall :: CallingConvention Language Source #

jvmCall :: CallingConvention Language Source #

stdCall :: CallingConvention Language Source #

safeCall :: CallSafety Language Source #

unsafeCall :: CallSafety Language Source #

Haskell Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

Associated Types

type Module Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type Declaration Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type Expression Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type Type Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type EquationLHS Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type EquationRHS Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type GuardedExpression Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type Pattern Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type Statement Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type ClassInstanceLHS Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type TypeLHS Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type Import Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type ImportSpecification Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type ImportItem Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type Export Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type Context Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type DataConstructor Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type DerivingClause Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type FieldDeclaration Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type FieldBinding Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type FieldPattern Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type CaseAlternative Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type Constructor Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type Value Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type CallingConvention Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type CallSafety Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type Associativity Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type Members Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type Name Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type ModuleName Language 
Instance details

Defined in Language.Haskell.Extensions.AST

type QualifiedName Language 
Instance details

Defined in Language.Haskell.Extensions.AST

Methods

anonymousModule :: forall s l (d :: NodeWrap). [s (Import l l d d)] -> [s (Declaration l l d d)] -> Module Language l d s Source #

namedModule :: forall s l (d :: NodeWrap). ModuleName Language -> Maybe [s (Export l l d d)] -> [s (Import l l d d)] -> [s (Declaration l l d d)] -> Module Language l d s Source #

withLanguagePragma :: forall s l (d :: NodeWrap). [ExtensionSwitch] -> s (Module l l d d) -> Module Language l d s Source #

exportClassOrType :: forall l (d :: NodeWrap) (s :: NodeWrap). QualifiedName Language -> Maybe (Members Language) -> Export Language l d s Source #

exportVar :: forall l (d :: NodeWrap) (s :: NodeWrap). QualifiedName Language -> Export Language l d s Source #

reExportModule :: forall l (d :: NodeWrap) (s :: NodeWrap). ModuleName Language -> Export Language l d s Source #

importDeclaration :: forall s l (d :: NodeWrap). Bool -> ModuleName Language -> Maybe (ModuleName Language) -> Maybe (s (ImportSpecification l l d d)) -> Import Language l d s Source #

excludedImports :: forall s l (d :: NodeWrap). [s (ImportItem l l d d)] -> ImportSpecification Language l d s Source #

includedImports :: forall s l (d :: NodeWrap). [s (ImportItem l l d d)] -> ImportSpecification Language l d s Source #

importClassOrType :: forall l (d :: NodeWrap) (s :: NodeWrap). Name Language -> Maybe (Members Language) -> ImportItem Language l d s Source #

importVar :: forall l (d :: NodeWrap) (s :: NodeWrap). Name Language -> ImportItem Language l d s Source #

allMembers :: Members Language Source #

memberList :: [Name Language] -> Members Language Source #

classDeclaration :: forall s l (d :: NodeWrap). s (Context l l d d) -> s (TypeLHS l l d d) -> [s (Declaration l l d d)] -> Declaration Language l d s Source #

dataDeclaration :: forall s l (d :: NodeWrap). s (Context l l d d) -> s (TypeLHS l l d d) -> [s (DataConstructor l l d d)] -> [s (DerivingClause l l d d)] -> Declaration Language l d s Source #

defaultDeclaration :: forall s l (d :: NodeWrap). [s (Type l l d d)] -> Declaration Language l d s Source #

equationDeclaration :: forall s l (d :: NodeWrap). s (EquationLHS l l d d) -> s (EquationRHS l l d d) -> [s (Declaration l l d d)] -> Declaration Language l d s Source #

fixityDeclaration :: forall l (d :: NodeWrap) (s :: NodeWrap). Associativity Language -> Maybe Int -> NonEmpty (Name Language) -> Declaration Language l d s Source #

foreignExport :: forall s l (d :: NodeWrap). CallingConvention Language -> Maybe Text -> Name Language -> s (Type l l d d) -> Declaration Language l d s Source #

foreignImport :: forall s l (d :: NodeWrap). CallingConvention Language -> Maybe (CallSafety Language) -> Maybe Text -> Name Language -> s (Type l l d d) -> Declaration Language l d s Source #

instanceDeclaration :: forall s l (d :: NodeWrap). s (Context l l d d) -> s (ClassInstanceLHS l l d d) -> [s (Declaration l l d d)] -> Declaration Language l d s Source #

newtypeDeclaration :: forall s l (d :: NodeWrap). s (Context l l d d) -> s (TypeLHS l l d d) -> s (DataConstructor l l d d) -> [s (DerivingClause l l d d)] -> Declaration Language l d s Source #

typeSynonymDeclaration :: forall s l (d :: NodeWrap). s (TypeLHS l l d d) -> s (Type l l d d) -> Declaration Language l d s Source #

typeSignature :: forall s l (d :: NodeWrap). NonEmpty (Name Language) -> s (Context l l d d) -> s (Type l l d d) -> Declaration Language l d s Source #

applyExpression :: forall s l (d :: NodeWrap). s (Expression l l d d) -> s (Expression l l d d) -> Expression Language l d s Source #

conditionalExpression :: forall s l (d :: NodeWrap). s (Expression l l d d) -> s (Expression l l d d) -> s (Expression l l d d) -> Expression Language l d s Source #

constructorExpression :: forall s l (d :: NodeWrap). s (Constructor l l d d) -> Expression Language l d s Source #

caseExpression :: forall s l (d :: NodeWrap). s (Expression l l d d) -> [s (CaseAlternative l l d d)] -> Expression Language l d s Source #

doExpression :: forall s l (d :: NodeWrap). s (GuardedExpression l l d d) -> Expression Language l d s Source #

infixExpression :: forall s l (d :: NodeWrap). s (Expression l l d d) -> s (Expression l l d d) -> s (Expression l l d d) -> Expression Language l d s Source #

leftSectionExpression :: forall s l (d :: NodeWrap). s (Expression l l d d) -> QualifiedName Language -> Expression Language l d s Source #

lambdaExpression :: forall s l (d :: NodeWrap). [s (Pattern l l d d)] -> s (Expression l l d d) -> Expression Language l d s Source #

letExpression :: forall s l (d :: NodeWrap). [s (Declaration l l d d)] -> s (Expression l l d d) -> Expression Language l d s Source #

listComprehension :: forall s l (d :: NodeWrap). s (Expression l l d d) -> NonEmpty (s (Statement l l d d)) -> Expression Language l d s Source #

listExpression :: forall s l (d :: NodeWrap). [s (Expression l l d d)] -> Expression Language l d s Source #

literalExpression :: forall s l (d :: NodeWrap). s (Value l l d d) -> Expression Language l d s Source #

negate :: forall l (d :: NodeWrap) (s :: NodeWrap). Expression Language l d s Source #

recordExpression :: forall s l (d :: NodeWrap). s (Expression l l d d) -> [s (FieldBinding l l d d)] -> Expression Language l d s Source #

referenceExpression :: forall l (d :: NodeWrap). QualifiedName Language -> Expression Language l d d Source #

rightSectionExpression :: forall s l (d :: NodeWrap). QualifiedName Language -> s (Expression l l d d) -> Expression Language l d s Source #

sequenceExpression :: forall s l (d :: NodeWrap). s (Expression l l d d) -> Maybe (s (Expression l l d d)) -> Maybe (s (Expression l l d d)) -> Expression Language l d s Source #

tupleExpression :: forall s l (d :: NodeWrap). NonEmpty (s (Expression l l d d)) -> Expression Language l d s Source #

typedExpression :: forall s l (d :: NodeWrap). s (Expression l l d d) -> s (Type l l d d) -> Expression Language l d s Source #

asPattern :: forall s l (d :: NodeWrap). Name Language -> s (Pattern l l d d) -> Pattern Language l d s Source #

constructorPattern :: forall s l (d :: NodeWrap). s (Constructor l l d d) -> [s (Pattern l l d d)] -> Pattern Language l d s Source #

infixPattern :: forall s l (d :: NodeWrap). s (Pattern l l d d) -> QualifiedName Language -> s (Pattern l l d d) -> Pattern Language l d s Source #

irrefutablePattern :: forall s l (d :: NodeWrap). s (Pattern l l d d) -> Pattern Language l d s Source #

listPattern :: forall s l (d :: NodeWrap). [s (Pattern l l d d)] -> Pattern Language l d s Source #

literalPattern :: forall s l (d :: NodeWrap). s (Value l l d d) -> Pattern Language l d s Source #

recordPattern :: forall s l (d :: NodeWrap). QualifiedName Language -> [s (FieldPattern l l d d)] -> Pattern Language l d s Source #

tuplePattern :: forall s l (d :: NodeWrap). NonEmpty (s (Pattern l l d d)) -> Pattern Language l d s Source #

variablePattern :: forall l (d :: NodeWrap) (s :: NodeWrap). Name Language -> Pattern Language l d s Source #

wildcardPattern :: forall l (d :: NodeWrap) (s :: NodeWrap). Pattern Language l d s Source #

constructorType :: forall s l (d :: NodeWrap). s (Constructor l l d d) -> Type Language l d s Source #

functionConstructorType :: forall l (d :: NodeWrap) (s :: NodeWrap). Type Language l d s Source #

functionType :: forall s l (d :: NodeWrap). s (Type l l d d) -> s (Type l l d d) -> Type Language l d s Source #

listType :: forall s l (d :: NodeWrap). s (Type l l d d) -> Type Language l d s Source #

strictType :: forall s l (d :: NodeWrap). s (Type l l d d) -> Type Language l d s Source #

tupleType :: forall s l (d :: NodeWrap). NonEmpty (s (Type l l d d)) -> Type Language l d s Source #

typeApplication :: forall s l (d :: NodeWrap). s (Type l l d d) -> s (Type l l d d) -> Type Language l d s Source #

typeVariable :: forall l (d :: NodeWrap) (s :: NodeWrap). Name Language -> Type Language l d s Source #

constructorReference :: forall l (d :: NodeWrap) (s :: NodeWrap). QualifiedName Language -> Constructor Language l d s Source #

emptyListConstructor :: forall l (d :: NodeWrap) (s :: NodeWrap). Constructor Language l d s Source #

tupleConstructor :: forall l (d :: NodeWrap) (s :: NodeWrap). Int -> Constructor Language l d s Source #

unitConstructor :: forall l (d :: NodeWrap) (s :: NodeWrap). Constructor Language l d s Source #

constructor :: forall s l (d :: NodeWrap). Name Language -> [s (Type l l d d)] -> DataConstructor Language l d s Source #

recordConstructor :: forall s l (d :: NodeWrap). Name Language -> [s (FieldDeclaration l l d d)] -> DataConstructor Language l d s Source #

constructorFields :: forall s l (d :: NodeWrap). NonEmpty (Name Language) -> s (Type l l d d) -> FieldDeclaration Language l d s Source #

fieldBinding :: forall s l (d :: NodeWrap). QualifiedName Language -> s (Expression l l d d) -> FieldBinding Language l d s Source #

fieldPattern :: forall s l (d :: NodeWrap). QualifiedName Language -> s (Pattern l l d d) -> FieldPattern Language l d s Source #

simpleDerive :: forall l (d :: NodeWrap) (s :: NodeWrap). QualifiedName Language -> DerivingClause Language l d s Source #

typeClassInstanceLHS :: forall s l (d :: NodeWrap). QualifiedName Language -> s (Type l l d d) -> ClassInstanceLHS Language l d s Source #

simpleTypeLHS :: forall l (d :: NodeWrap) (s :: NodeWrap). Name Language -> [Name Language] -> TypeLHS Language l d s Source #

prefixLHS :: forall s l (d :: NodeWrap). s (EquationLHS l l d d) -> NonEmpty (s (Pattern l l d d)) -> EquationLHS Language l d s Source #

infixLHS :: forall s l (d :: NodeWrap). s (Pattern l l d d) -> Name Language -> s (Pattern l l d d) -> EquationLHS Language l d s Source #

patternLHS :: forall s l (d :: NodeWrap). s (Pattern l l d d) -> EquationLHS Language l d s Source #

variableLHS :: forall l (d :: NodeWrap) (s :: NodeWrap). Name Language -> EquationLHS Language l d s Source #

caseAlternative :: forall s l (d :: NodeWrap). s (Pattern l l d d) -> s (EquationRHS l l d d) -> [s (Declaration l l d d)] -> CaseAlternative Language l d s Source #

guardedRHS :: forall s l (d :: NodeWrap). NonEmpty (s (GuardedExpression l l d d)) -> EquationRHS Language l d s Source #

normalRHS :: forall s l (d :: NodeWrap). s (Expression l l d d) -> EquationRHS Language l d s Source #

guardedExpression :: forall s l (d :: NodeWrap). [s (Statement l l d d)] -> s (Expression l l d d) -> GuardedExpression Language l d s Source #

classConstraint :: forall s l (d :: NodeWrap). QualifiedName Language -> s (Type l l d d) -> Context Language l d s Source #

constraints :: forall s l (d :: NodeWrap). [s (Context l l d d)] -> Context Language l d s Source #

noContext :: forall l (d :: NodeWrap) (s :: NodeWrap). Context Language l d s Source #

bindStatement :: forall s l (d :: NodeWrap). s (Pattern l l d d) -> s (Expression l l d d) -> Statement Language l d s Source #

expressionStatement :: forall s l (d :: NodeWrap). s (Expression l l d d) -> Statement Language l d s Source #

letStatement :: forall s l (d :: NodeWrap). [s (Declaration l l d d)] -> Statement Language l d s Source #

charLiteral :: forall l (d :: NodeWrap) (s :: NodeWrap). Char -> Value Language l d s Source #

floatingLiteral :: forall l (d :: NodeWrap) (s :: NodeWrap). Rational -> Value Language l d s Source #

integerLiteral :: forall l (d :: NodeWrap) (s :: NodeWrap). Integer -> Value Language l d s Source #

stringLiteral :: forall l (d :: NodeWrap) (s :: NodeWrap). Text -> Value Language l d s Source #

name :: Text -> Name Language Source #

moduleName :: NonEmpty (Name Language) -> ModuleName Language Source #

qualifiedName :: Maybe (ModuleName Language) -> Name Language -> QualifiedName Language Source #

nonAssociative :: Associativity Language Source #

leftAssociative :: Associativity Language Source #

rightAssociative :: Associativity Language Source #

cCall :: CallingConvention Language Source #

cppCall :: CallingConvention Language Source #

dotNetCall :: CallingConvention Language Source #

jvmCall :: CallingConvention Language Source #

stdCall :: CallingConvention Language Source #

safeCall :: CallSafety Language Source #

unsafeCall :: CallSafety Language Source #

type family Import λ = (x :: TreeNodeSubKind) | x -> λ Source #

Instances

Instances details
type Import Language Source # 
Instance details

Defined in Language.Haskell.AST

type Import Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

type family ImportItem λ = (x :: TreeNodeSubKind) | x -> λ Source #

Instances

Instances details
type ImportItem Language Source # 
Instance details

Defined in Language.Haskell.AST

type ImportItem Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

type family Members λ = (x :: Type) | x -> λ Source #

Instances

Instances details
type Members Language Source # 
Instance details

Defined in Language.Haskell.AST

type Members Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

type family Module λ = (x :: TreeNodeSubKind) | x -> λ Source #

Instances

Instances details
type Module Language Source # 
Instance details

Defined in Language.Haskell.AST

type Module Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

type family ModuleName λ = (x :: Type) | x -> λ Source #

Instances

Instances details
type ModuleName Language Source # 
Instance details

Defined in Language.Haskell.AST

type ModuleName Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

type family Name λ = (x :: Type) | x -> λ Source #

Instances

Instances details
type Name Language Source # 
Instance details

Defined in Language.Haskell.AST

type Name Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

type family Pattern λ = (x :: TreeNodeSubKind) | x -> λ Source #

Instances

Instances details
type Pattern Language Source # 
Instance details

Defined in Language.Haskell.AST

type Pattern Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

type family QualifiedName λ = (x :: Type) | x -> λ Source #

type Rank2lyFoldable l (f :: NodeWrap) = (Foldable (Module l l f), Foldable (Declaration l l f), Foldable (Expression l l f), Foldable (Type l l f), Foldable (EquationLHS l l f), Foldable (EquationRHS l l f), Foldable (GuardedExpression l l f), Foldable (Pattern l l f), Foldable (Statement l l f), Foldable (ClassInstanceLHS l l f), Foldable (TypeLHS l l f), Foldable (Import l l f), Foldable (ImportSpecification l l f), Foldable (ImportItem l l f), Foldable (Export l l f), Foldable (Context l l f), Foldable (DataConstructor l l f), Foldable (DerivingClause l l f), Foldable (FieldDeclaration l l f), Foldable (FieldBinding l l f), Foldable (FieldPattern l l f), Foldable (CaseAlternative l l f), Foldable (Constructor l l f), Foldable (Value l l f)) Source #

Named collection of constraints Rank2lyFoldable l f means that every AST node of language l with subtrees wrapped in f is Foldable.

type Rank2lyFunctor l (f :: NodeWrap) = (Functor (Module l l f), Functor (Declaration l l f), Functor (Expression l l f), Functor (Type l l f), Functor (EquationLHS l l f), Functor (EquationRHS l l f), Functor (GuardedExpression l l f), Functor (Pattern l l f), Functor (Statement l l f), Functor (ClassInstanceLHS l l f), Functor (TypeLHS l l f), Functor (Import l l f), Functor (ImportSpecification l l f), Functor (ImportItem l l f), Functor (Export l l f), Functor (Context l l f), Functor (DataConstructor l l f), Functor (DerivingClause l l f), Functor (FieldDeclaration l l f), Functor (FieldBinding l l f), Functor (FieldPattern l l f), Functor (CaseAlternative l l f), Functor (Constructor l l f), Functor (Value l l f)) Source #

Named collection of constraints Rank2lyFunctor l f means that every AST node of language l with subtrees wrapped in f is a Functor.

type Rank2lyTraversable l (f :: NodeWrap) = (Traversable (Module l l f), Traversable (Declaration l l f), Traversable (Expression l l f), Traversable (Type l l f), Traversable (EquationLHS l l f), Traversable (EquationRHS l l f), Traversable (GuardedExpression l l f), Traversable (Pattern l l f), Traversable (Statement l l f), Traversable (ClassInstanceLHS l l f), Traversable (TypeLHS l l f), Traversable (Import l l f), Traversable (ImportSpecification l l f), Traversable (ImportItem l l f), Traversable (Export l l f), Traversable (Context l l f), Traversable (DataConstructor l l f), Traversable (DerivingClause l l f), Traversable (FieldDeclaration l l f), Traversable (FieldBinding l l f), Traversable (FieldPattern l l f), Traversable (CaseAlternative l l f), Traversable (Constructor l l f), Traversable (Value l l f)) Source #

Named collection of constraints Rank2lyTraversable l f means that every AST node of language l with subtrees wrapped in f is Traversable.

type family Statement λ = (x :: TreeNodeSubKind) | x -> λ Source #

Instances

Instances details
type Statement Language Source # 
Instance details

Defined in Language.Haskell.AST

type Statement Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

type TreeNodeKind = Language -> TreeNodeSubKind Source #

The kind of a tree node with four type parameters:

  • the language of the node itself
  • the language of the node's subtrees
  • the wrapper for the node's subtrees' subtrees
  • the wrapper for the node's subtrees

type family Type λ = (x :: TreeNodeSubKind) | x -> λ Source #

Instances

Instances details
type Type Language Source # 
Instance details

Defined in Language.Haskell.AST

type Type Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

type family TypeLHS λ = (x :: TreeNodeSubKind) | x -> λ Source #

Instances

Instances details
type TypeLHS Language Source # 
Instance details

Defined in Language.Haskell.AST

type TypeLHS Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST

type family Value λ = (x :: TreeNodeSubKind) | x -> λ Source #

Instances

Instances details
type Value Language Source # 
Instance details

Defined in Language.Haskell.AST

type Value Language Source # 
Instance details

Defined in Language.Haskell.Extensions.AST