haskell-tools-ast-0.9.0.0: Haskell AST for efficient tooling

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.Tools.AST

Contents

Description

A custom AST representation for Haskell tools. Different layers of the AST are recursive, to separate them into modules we introduced source imports.

Synopsis

Documentation

data UModule dom stage Source #

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

Constructors

UModule 

Fields

Instances

HasModuleInfo dom => HasModuleInfo' (Ann UModule dom st) Source # 
type Rep (UModule dom stage) Source # 
type Rep (UModule dom stage) = D1 (MetaData "UModule" "Language.Haskell.Tools.AST.Representation.Modules" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UModule" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_filePragmas") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UFilePragma dom stage))) (S1 (MetaSel (Just Symbol "_modHead") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UModuleHead dom stage)))) ((:*:) (S1 (MetaSel (Just Symbol "_modImports") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UImportDecl dom stage))) (S1 (MetaSel (Just Symbol "_modDecl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UDecl dom stage))))))

data UModuleHead dom stage Source #

Module declaration with name and (optional) exports

Constructors

UModuleHead 

Fields

Instances

type Rep (UModuleHead dom stage) Source # 
type Rep (UModuleHead dom stage) = D1 (MetaData "UModuleHead" "Language.Haskell.Tools.AST.Representation.Modules" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UModuleHead" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_mhName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UModuleName dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_mhPragma") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UModulePragma dom stage))) (S1 (MetaSel (Just Symbol "_mhExports") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UExportSpecs dom stage))))))

data UExportSpecs dom stage Source #

A list of export specifications surrounded by parentheses

Constructors

UExportSpecs 

Fields

Instances

type Rep (UExportSpecs dom stage) Source # 
type Rep (UExportSpecs dom stage) = D1 (MetaData "UExportSpecs" "Language.Haskell.Tools.AST.Representation.Modules" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UExportSpecs" PrefixI True) (S1 (MetaSel (Just Symbol "_espExports") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UExportSpec dom stage))))

data UExportSpec dom stage Source #

Export specifier

Constructors

UDeclExport

Export a name and related names

Fields

UModuleExport

The export of an imported module ( module A )

Fields

Instances

type Rep (UExportSpec dom stage) Source # 
type Rep (UExportSpec dom stage) = D1 (MetaData "UExportSpec" "Language.Haskell.Tools.AST.Representation.Modules" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "UDeclExport" PrefixI True) (S1 (MetaSel (Just Symbol "_exportDecl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UIESpec dom stage)))) (C1 (MetaCons "UModuleExport" PrefixI True) (S1 (MetaSel (Just Symbol "_exportModuleName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UModuleName dom stage)))))

data UIESpec dom stage Source #

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

Constructors

UIESpec 

Fields

Instances

type Rep (UIESpec dom stage) Source # 
type Rep (UIESpec dom stage) = D1 (MetaData "UIESpec" "Language.Haskell.Tools.AST.Representation.Modules" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UIESpec" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ieModifier") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UImportModifier dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_ieName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage))) (S1 (MetaSel (Just Symbol "_ieSubspec") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG USubSpec dom stage))))))

data UImportModifier dom stage Source #

Specifies the imported element

Constructors

UImportPattern

pattern: modifier for importing pattern synonyms

Instances

type Rep (UImportModifier dom stage) Source # 
type Rep (UImportModifier dom stage) = D1 (MetaData "UImportModifier" "Language.Haskell.Tools.AST.Representation.Modules" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UImportPattern" PrefixI False) U1)

data USubSpec dom stage Source #

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

Constructors

USubSpecAll

(..): a class exported with all of its methods, or a datatype exported with all of its constructors.

USubSpecList

(a,b,c): a class exported with some of its methods, or a datatype exported with some of its constructors.

Fields

Instances

type Rep (USubSpec dom stage) Source # 
type Rep (USubSpec dom stage) = D1 (MetaData "USubSpec" "Language.Haskell.Tools.AST.Representation.Modules" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "USubSpecAll" PrefixI False) U1) (C1 (MetaCons "USubSpecList" PrefixI True) (S1 (MetaSel (Just Symbol "_essList") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UName dom stage)))))

data UFilePragma dom stage Source #

Pragmas that must be used before defining the module

Constructors

ULanguagePragma

LANGUAGE pragma, listing the enabled language extensions in that file

UOptionsPragma

OPTIONS pragma, possibly qualified with a tool, e.g. OPTIONS_GHC

Fields

Instances

type Rep (UFilePragma dom stage) Source # 
type Rep (UFilePragma dom stage) = D1 (MetaData "UFilePragma" "Language.Haskell.Tools.AST.Representation.Modules" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "ULanguagePragma" PrefixI True) (S1 (MetaSel (Just Symbol "_lpPragmas") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG ULanguageExtension dom stage)))) (C1 (MetaCons "UOptionsPragma" PrefixI True) (S1 (MetaSel (Just Symbol "_opStr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UStringNode dom stage)))))

data UModulePragma dom stage Source #

Pragmas that must be used after the module head

Constructors

UModuleWarningPragma

A warning pragma attached to the module

Fields

UModuleDeprecatedPragma

A deprecated pragma attached to the module

Instances

type Rep (UModulePragma dom stage) Source # 
type Rep (UModulePragma dom stage) = D1 (MetaData "UModulePragma" "Language.Haskell.Tools.AST.Representation.Modules" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "UModuleWarningPragma" PrefixI True) (S1 (MetaSel (Just Symbol "_modWarningStr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UStringNode dom stage)))) (C1 (MetaCons "UModuleDeprecatedPragma" PrefixI True) (S1 (MetaSel (Just Symbol "_modDeprecatedPragma") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UStringNode dom stage)))))

data ULanguageExtension dom stage Source #

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

Constructors

ULanguageExtension 

Fields

Instances

type Rep (ULanguageExtension dom stage) Source # 
type Rep (ULanguageExtension dom stage) = D1 (MetaData "ULanguageExtension" "Language.Haskell.Tools.AST.Representation.Modules" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "ULanguageExtension" PrefixI True) (S1 (MetaSel (Just Symbol "_langExt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))

data UImportDecl dom stage Source #

An import declaration: import Module.Name

Instances

HasImportInfo dom => HasImportInfo' (Ann UImportDecl dom st) Source # 
type Rep (UImportDecl dom stage) Source # 
type Rep (UImportDecl dom stage) = D1 (MetaData "UImportDecl" "Language.Haskell.Tools.AST.Representation.Modules" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UImportDecl" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_importSource") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UImportSource dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_importQualified") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UImportQualified dom stage))) (S1 (MetaSel (Just Symbol "_importSafe") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UImportSafe dom stage))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_importPkg") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UStringNode dom stage))) (S1 (MetaSel (Just Symbol "_importModule") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UModuleName dom stage)))) ((:*:) (S1 (MetaSel (Just Symbol "_importAs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UImportRenaming dom stage))) (S1 (MetaSel (Just Symbol "_importSpec") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UImportSpec dom stage)))))))

data UImportSpec dom stage Source #

Restriction on the imported names

Constructors

UImportSpecList

Restrict the import definition to ONLY import the listed names

Fields

UImportSpecHiding

Restrict the import definition to DONT import the listed names

Fields

Instances

type Rep (UImportSpec dom stage) Source # 
type Rep (UImportSpec dom stage) = D1 (MetaData "UImportSpec" "Language.Haskell.Tools.AST.Representation.Modules" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "UImportSpecList" PrefixI True) (S1 (MetaSel (Just Symbol "_importSpecList") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UIESpec dom stage)))) (C1 (MetaCons "UImportSpecHiding" PrefixI True) (S1 (MetaSel (Just Symbol "_importSpecHiding") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UIESpec dom stage)))))

data UImportQualified dom stage Source #

Marks the import as qualified: qualified

Constructors

UImportQualified 

Instances

type Rep (UImportQualified dom stage) Source # 
type Rep (UImportQualified dom stage) = D1 (MetaData "UImportQualified" "Language.Haskell.Tools.AST.Representation.Modules" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UImportQualified" PrefixI False) U1)

data UImportSource dom stage Source #

Marks the import as source: {--}

Constructors

UImportSource 

Instances

type Rep (UImportSource dom stage) Source # 
type Rep (UImportSource dom stage) = D1 (MetaData "UImportSource" "Language.Haskell.Tools.AST.Representation.Modules" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UImportSource" PrefixI False) U1)

data UImportSafe dom stage Source #

Marks the import as safe: safe

Constructors

UImportSafe 

Instances

type Rep (UImportSafe dom stage) Source # 
type Rep (UImportSafe dom stage) = D1 (MetaData "UImportSafe" "Language.Haskell.Tools.AST.Representation.Modules" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UImportSafe" PrefixI False) U1)

data UTypeNamespace dom stage Source #

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

Constructors

UTypeNamespace 

Instances

type Rep (UTypeNamespace dom stage) Source # 
type Rep (UTypeNamespace dom stage) = D1 (MetaData "UTypeNamespace" "Language.Haskell.Tools.AST.Representation.Modules" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UTypeNamespace" PrefixI False) U1)

data UImportRenaming dom stage Source #

Renaming imports ( as A )

Constructors

UImportRenaming 

Fields

Instances

type Rep (UImportRenaming dom stage) Source # 
type Rep (UImportRenaming dom stage) = D1 (MetaData "UImportRenaming" "Language.Haskell.Tools.AST.Representation.Modules" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UImportRenaming" PrefixI True) (S1 (MetaSel (Just Symbol "_importRename") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UModuleName dom stage))))

data UModuleName dom stage Source #

The name of a module

Constructors

UModuleName 

Instances

type Rep (UModuleName dom stage) Source # 
type Rep (UModuleName dom stage) = D1 (MetaData "UModuleName" "Language.Haskell.Tools.AST.Representation.Modules" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UModuleName" PrefixI True) (S1 (MetaSel (Just Symbol "_moduleNameString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))

data TypeKeyword dom stage Source #

The type keyword used to qualify that the type and not the constructor of the same name is referred

Constructors

TypeKeyword 

Instances

type Rep (TypeKeyword dom stage) Source # 
type Rep (TypeKeyword dom stage) = D1 (MetaData "TypeKeyword" "Language.Haskell.Tools.AST.Representation.Modules" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "TypeKeyword" PrefixI False) U1)

data USplice dom stage Source #

A template haskell splice

Constructors

UIdSplice

A simple name splice: $generateX

Fields

UParenSplice

A splice with parentheses: $(generate input)

Fields

Instances

type Rep (USplice dom stage) Source # 
type Rep (USplice dom stage) = D1 (MetaData "USplice" "Language.Haskell.Tools.AST.Representation.TH" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "UIdSplice" PrefixI True) (S1 (MetaSel (Just Symbol "_spliceId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage)))) (C1 (MetaCons "UParenSplice" PrefixI True) (S1 (MetaSel (Just Symbol "_spliceExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage)))))

data UQuasiQuote dom stage Source #

Template haskell quasi-quotation: [quoter|str]

Constructors

UQuasiQuote 

Fields

Instances

type Rep (UQuasiQuote dom stage) Source # 
type Rep (UQuasiQuote dom stage) = D1 (MetaData "UQuasiQuote" "Language.Haskell.Tools.AST.Representation.TH" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UQuasiQuote" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_qqExprName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage))) (S1 (MetaSel (Just Symbol "_qqExprBody") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann QQString dom stage)))))

data QQString dom stage Source #

Template Haskell Quasi-quotation content

Constructors

QQString 

Fields

Instances

type Rep (QQString dom stage) Source # 
type Rep (QQString dom stage) = D1 (MetaData "QQString" "Language.Haskell.Tools.AST.Representation.TH" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "QQString" PrefixI True) (S1 (MetaSel (Just Symbol "_qqString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))

data UBracket dom stage Source #

Template Haskell bracket expressions

Constructors

UExprBracket

Expression bracket ( [| x + y |] )

Fields

UPatternBracket

Pattern bracket ( [p| Point x y |] )

Fields

UTypeBracket

Type bracket ( [t| (Int,Int) |] )

Fields

UDeclsBracket

Declaration bracket ( [d| f :: Int -> Int; f x = x*x |] )

Fields

Instances

type Rep (UBracket dom stage) Source # 
type Rep (UBracket dom stage) = D1 (MetaData "UBracket" "Language.Haskell.Tools.AST.Representation.TH" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) ((:+:) (C1 (MetaCons "UExprBracket" PrefixI True) (S1 (MetaSel (Just Symbol "_bracketExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage)))) (C1 (MetaCons "UPatternBracket" PrefixI True) (S1 (MetaSel (Just Symbol "_bracketPattern") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UPattern dom stage))))) ((:+:) (C1 (MetaCons "UTypeBracket" PrefixI True) (S1 (MetaSel (Just Symbol "_bracketType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage)))) (C1 (MetaCons "UDeclsBracket" PrefixI True) (S1 (MetaSel (Just Symbol "_bracketDecl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UDecl dom stage))))))

Declarations

data UDecl dom stage Source #

Haskell declarationw

Constructors

UTypeDecl

A type synonym ( type String = [Char] )

Fields

UTypeFamilyDecl

A type family declaration ( type family F x )

Fields

UClosedTypeFamilyDecl

A closed type family declaration

Fields

UDataDecl

A data or newtype declaration. Empty data type declarations without where keyword are always belong to DataDecl.

UGDataDecl

A GADT-style data or newtype declaration.

UTypeInstDecl

Type family instance declaration ( type instance Fam T = AssignedT )

Fields

UDataInstDecl

Data instance declaration ( data instance Fam T = Con1 | Con2 )

UGDataInstDecl

GADT-style data instance declaration ( data instance Fam T where ... )

UClassDecl

Type class declaration ( class X a [where f = ...] )

Fields

UInstDecl

Instance declaration ( instance X T [where f = ...] )

UPatternSynonymDecl

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

Fields

UDerivDecl

Standalone deriving declaration ( deriving instance X T )

UFixityDecl

Fixity declaration ( infixl 5 +, - )

Fields

UDefaultDecl

Default types ( default (T1, T2) )

Fields

UTypeSigDecl

Type signature declaration ( f :: Int -> Int )

Fields

UPatTypeSigDecl

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

UValueBinding

Function or value binding ( f x = 12 )

Fields

UForeignImport

Foreign import ( foreign import _foo :: Int -> IO Int )

Fields

UForeignExport

Foreign export ( foreign export ccall _foo :: Int -> IO Int )

Fields

UPragmaDecl

Top-level pragmas

Fields

URoleDecl

Role annotations ( type role Ptr representational )

Fields

USpliceDecl

A Template Haskell splice declaration ( $(generateDecls) )

Fields

Instances

NamedElement UDecl Source # 

Methods

elementName :: (RefMonads w r, MonadPlus r, Morph Maybe r, Morph [] r) => Reference w r (MU *) (MU *) (Ann UDecl dom st) (Ann UDecl dom st) (Ann UQualifiedName dom st) (Ann UQualifiedName dom st) Source #

type Rep (UDecl dom stage) Source # 
type Rep (UDecl dom stage) = D1 (MetaData "UDecl" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "UTypeDecl" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_declHead") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UDeclHead dom stage))) (S1 (MetaSel (Just Symbol "_declType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage))))) (C1 (MetaCons "UTypeFamilyDecl" PrefixI True) (S1 (MetaSel (Just Symbol "_declTypeFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UTypeFamily dom stage))))) ((:+:) (C1 (MetaCons "UClosedTypeFamilyDecl" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_declHead") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UDeclHead dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_declSpec") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UTypeFamilySpec dom stage))) (S1 (MetaSel (Just Symbol "_declDecl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UTypeEqn dom stage)))))) ((:+:) (C1 (MetaCons "UDataDecl" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_declNewtype") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UDataOrNewtypeKeyword dom stage))) (S1 (MetaSel (Just Symbol "_declCtx") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UContext dom stage)))) ((:*:) (S1 (MetaSel (Just Symbol "_declHead") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UDeclHead dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_declCons") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UConDecl dom stage))) (S1 (MetaSel (Just Symbol "_declDeriving") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UDeriving dom stage))))))) (C1 (MetaCons "UGDataDecl" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_declNewtype") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UDataOrNewtypeKeyword dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_declCtx") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UContext dom stage))) (S1 (MetaSel (Just Symbol "_declHead") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UDeclHead dom stage))))) ((:*:) (S1 (MetaSel (Just Symbol "_declKind") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UKindConstraint dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_declGadt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UGadtConDecl dom stage))) (S1 (MetaSel (Just Symbol "_declDeriving") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UDeriving dom stage)))))))))) ((:+:) ((:+:) (C1 (MetaCons "UTypeInstDecl" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_declInstance") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UInstanceRule dom stage))) (S1 (MetaSel (Just Symbol "_declAssignedType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage))))) ((:+:) (C1 (MetaCons "UDataInstDecl" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_declNewtype") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UDataOrNewtypeKeyword dom stage))) (S1 (MetaSel (Just Symbol "_declInstance") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UInstanceRule dom stage)))) ((:*:) (S1 (MetaSel (Just Symbol "_declCons") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UConDecl dom stage))) (S1 (MetaSel (Just Symbol "_declDeriving") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UDeriving dom stage)))))) (C1 (MetaCons "UGDataInstDecl" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_declNewtype") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UDataOrNewtypeKeyword dom stage))) (S1 (MetaSel (Just Symbol "_declInstance") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UInstanceRule dom stage)))) ((:*:) (S1 (MetaSel (Just Symbol "_declKind") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UKindConstraint dom stage))) (S1 (MetaSel (Just Symbol "_declGadt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UGadtConDecl dom stage)))))))) ((:+:) (C1 (MetaCons "UClassDecl" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_declCtx") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UContext dom stage))) (S1 (MetaSel (Just Symbol "_declHead") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UDeclHead dom stage)))) ((:*:) (S1 (MetaSel (Just Symbol "_declFunDeps") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UFunDeps dom stage))) (S1 (MetaSel (Just Symbol "_declBody") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UClassBody dom stage)))))) ((:+:) (C1 (MetaCons "UInstDecl" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_declOverlap") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UOverlapPragma dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_declInstRule") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UInstanceRule dom stage))) (S1 (MetaSel (Just Symbol "_declInstDecl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UInstBody dom stage)))))) (C1 (MetaCons "UPatternSynonymDecl" PrefixI True) (S1 (MetaSel (Just Symbol "_declPatSyn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UPatternSynonym dom stage)))))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "UDerivDecl" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_declOverlap") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UOverlapPragma dom stage))) (S1 (MetaSel (Just Symbol "_declInstRule") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UInstanceRule dom stage))))) (C1 (MetaCons "UFixityDecl" PrefixI True) (S1 (MetaSel (Just Symbol "_declFixity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UFixitySignature dom stage))))) ((:+:) (C1 (MetaCons "UDefaultDecl" PrefixI True) (S1 (MetaSel (Just Symbol "_declTypes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UType dom stage)))) ((:+:) (C1 (MetaCons "UTypeSigDecl" PrefixI True) (S1 (MetaSel (Just Symbol "_declTypeSig") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UTypeSignature dom stage)))) (C1 (MetaCons "UPatTypeSigDecl" PrefixI True) (S1 (MetaSel (Just Symbol "_declPatTypeSig") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UPatternTypeSignature dom stage))))))) ((:+:) ((:+:) (C1 (MetaCons "UValueBinding" PrefixI True) (S1 (MetaSel (Just Symbol "_declValBind") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UValueBind dom stage)))) ((:+:) (C1 (MetaCons "UForeignImport" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_declCallConv") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UCallConv dom stage))) (S1 (MetaSel (Just Symbol "_declSafety") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG USafety dom stage)))) ((:*:) (S1 (MetaSel (Just Symbol "_declName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage))) (S1 (MetaSel (Just Symbol "_declForeignType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage)))))) (C1 (MetaCons "UForeignExport" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_declCallConv") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UCallConv dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_declName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage))) (S1 (MetaSel (Just Symbol "_declForeignType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage)))))))) ((:+:) (C1 (MetaCons "UPragmaDecl" PrefixI True) (S1 (MetaSel (Just Symbol "_declPragma") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UTopLevelPragma dom stage)))) ((:+:) (C1 (MetaCons "URoleDecl" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_declRoleType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UQualifiedName dom stage))) (S1 (MetaSel (Just Symbol "_declRoles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG URole dom stage))))) (C1 (MetaCons "USpliceDecl" PrefixI True) (S1 (MetaSel (Just Symbol "_declSplice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann USplice dom stage)))))))))

data UDeclHead dom stage Source #

Constructors

UDeclHead

Type or class name

Fields

UDHParen

Parenthesized type

Fields

UDHApp

Type application

Fields

UDHInfix

Infix application of the type/class name to the left operand

Fields

Instances

type Rep (UDeclHead dom stage) Source # 
type Rep (UDeclHead dom stage) = D1 (MetaData "UDeclHead" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) ((:+:) (C1 (MetaCons "UDeclHead" PrefixI True) (S1 (MetaSel (Just Symbol "_dhName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage)))) (C1 (MetaCons "UDHParen" PrefixI True) (S1 (MetaSel (Just Symbol "_dhBody") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UDeclHead dom stage))))) ((:+:) (C1 (MetaCons "UDHApp" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_dhAppFun") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UDeclHead dom stage))) (S1 (MetaSel (Just Symbol "_dhAppOperand") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UTyVar dom stage))))) (C1 (MetaCons "UDHInfix" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_dhLeft") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UTyVar dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_dhOperator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UOperator dom stage))) (S1 (MetaSel (Just Symbol "_dhRight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UTyVar dom stage))))))))

Type class definitions

data UClassBody dom stage Source #

The list of declarations that can appear in a typeclass

Constructors

UClassBody 

Fields

Instances

type Rep (UClassBody dom stage) Source # 
type Rep (UClassBody dom stage) = D1 (MetaData "UClassBody" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UClassBody" PrefixI True) (S1 (MetaSel (Just Symbol "_cbElements") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UClassElement dom stage))))

data UClassElement dom stage Source #

Members of a class declaration

Constructors

UClsSig

Signature: f :: A -> B

Fields

UClsFixity

Fixity signature in class: infixl 1 >>-

Fields

UClsDef

Default binding: f x = "aaa"

Fields

UClsTypeFam

Declaration of an associated type synonym: type T x :: *

Fields

UClsTypeDef

Default choice for type synonym: type T x = TE or type instance T x = TE

Fields

UClsDefSig

Default signature (by using DefaultSignatures): default _enum :: (Generic a, GEnum (Rep a)) => [a]

Fields

UClsMinimal

Minimal pragma: {--}

Fields

UClsInline

Inline-like pragma in class definition not supported yet (GHC 8.0.1) | UClsPatSig { _cePatSig :: Ann UPatternTypeSignature dom stage } -- ^ Pattern signature in a class declaration (by using PatternSynonyms)

Fields

Instances

type Rep (UClassElement dom stage) Source # 
type Rep (UClassElement dom stage) = D1 (MetaData "UClassElement" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "UClsSig" PrefixI True) (S1 (MetaSel (Just Symbol "_ceTypeSig") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UTypeSignature dom stage)))) (C1 (MetaCons "UClsFixity" PrefixI True) (S1 (MetaSel (Just Symbol "_clsFixity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UFixitySignature dom stage))))) ((:+:) (C1 (MetaCons "UClsDef" PrefixI True) (S1 (MetaSel (Just Symbol "_ceBind") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UValueBind dom stage)))) (C1 (MetaCons "UClsTypeFam" PrefixI True) (S1 (MetaSel (Just Symbol "_ceTypeFam") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UTypeFamily dom stage)))))) ((:+:) ((:+:) (C1 (MetaCons "UClsTypeDef" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ceHead") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UDeclHead dom stage))) (S1 (MetaSel (Just Symbol "_ceKind") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage))))) (C1 (MetaCons "UClsDefSig" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ceName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage))) (S1 (MetaSel (Just Symbol "_ceType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage)))))) ((:+:) (C1 (MetaCons "UClsMinimal" PrefixI True) (S1 (MetaSel (Just Symbol "_pragmaFormula") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UMinimalFormula dom stage)))) (C1 (MetaCons "UClsInline" PrefixI True) (S1 (MetaSel (Just Symbol "_clsInline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UInlinePragma dom stage)))))))

Type class instances

data UInstanceRule dom stage Source #

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

Constructors

UInstanceRule

Instance head as an instance rule ( X a => Y a )

Fields

Instances

type Rep (UInstanceRule dom stage) Source # 
type Rep (UInstanceRule dom stage) = D1 (MetaData "UInstanceRule" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UInstanceRule" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_irVars") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG (AnnListG UTyVar) dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_irCtx") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UContext dom stage))) (S1 (MetaSel (Just Symbol "_irHead") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UInstanceHead dom stage))))))

data UInstanceHead dom stage Source #

The specification of the class instance declaration

Constructors

UInstanceHeadCon

Type or class name

Fields

UInstanceHeadInfix

Infix application of the type/class name to the left operand

Fields

UInstanceHeadParen

Parenthesized instance head

Fields

UInstanceHeadApp

Application to one more type

Fields

Instances

type Rep (UInstanceHead dom stage) Source # 
type Rep (UInstanceHead dom stage) = D1 (MetaData "UInstanceHead" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) ((:+:) (C1 (MetaCons "UInstanceHeadCon" PrefixI True) (S1 (MetaSel (Just Symbol "_ihConName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage)))) (C1 (MetaCons "UInstanceHeadInfix" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ihLeftOp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage))) (S1 (MetaSel (Just Symbol "_ihOperator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UOperator dom stage)))))) ((:+:) (C1 (MetaCons "UInstanceHeadParen" PrefixI True) (S1 (MetaSel (Just Symbol "_ihHead") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UInstanceHead dom stage)))) (C1 (MetaCons "UInstanceHeadApp" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ihFun") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UInstanceHead dom stage))) (S1 (MetaSel (Just Symbol "_ihType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage)))))))

data UInstBody dom stage Source #

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

Constructors

UInstBody 

Instances

type Rep (UInstBody dom stage) Source # 
type Rep (UInstBody dom stage) = D1 (MetaData "UInstBody" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UInstBody" PrefixI True) (S1 (MetaSel (Just Symbol "_instBodyDecls") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UInstBodyDecl dom stage))))

data UInstBodyDecl dom stage Source #

Declarations inside an instance declaration.

Constructors

UInstBodyNormalDecl

A normal value binding ( f x = 12 )

Fields

UInstBodyTypeSig

Type signature in instance definition with InstanceSigs

Fields

UInstBodyTypeDecl

An associated type definition ( type A X = B )

Fields

UInstBodyDataDecl

An associated data type implementation ( data A X = C1 | C2 )

UInstBodyGadtDataDecl

An associated data type implemented using GADT style

USpecializeInstance

Specialize instance pragma (no phase selection is allowed)

Fields

UInlineInstance

Inline-like pragma in a class instance

Fields

UInstanceSpecialize

Specialize pragma not supported yet | UInstBodyPatSyn { _instBodyPatSyn :: Ann UPatternSynonym dom stage } -- ^ A pattern synonym in a class instance

Instances

type Rep (UInstBodyDecl dom stage) Source # 
type Rep (UInstBodyDecl dom stage) = D1 (MetaData "UInstBodyDecl" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "UInstBodyNormalDecl" PrefixI True) (S1 (MetaSel (Just Symbol "_instBodyDeclFunbind") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UValueBind dom stage)))) (C1 (MetaCons "UInstBodyTypeSig" PrefixI True) (S1 (MetaSel (Just Symbol "_instBodyTypeSig") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UTypeSignature dom stage))))) ((:+:) (C1 (MetaCons "UInstBodyTypeDecl" PrefixI True) (S1 (MetaSel (Just Symbol "_instBodyTypeEqn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UTypeEqn dom stage)))) (C1 (MetaCons "UInstBodyDataDecl" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_instBodyDataNew") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UDataOrNewtypeKeyword dom stage))) (S1 (MetaSel (Just Symbol "_instBodyLhsType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UInstanceRule dom stage)))) ((:*:) (S1 (MetaSel (Just Symbol "_instBodyDataCons") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UConDecl dom stage))) (S1 (MetaSel (Just Symbol "_instBodyDerivings") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UDeriving dom stage)))))))) ((:+:) ((:+:) (C1 (MetaCons "UInstBodyGadtDataDecl" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_instBodyDataNew") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UDataOrNewtypeKeyword dom stage))) (S1 (MetaSel (Just Symbol "_instBodyLhsType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UInstanceRule dom stage)))) ((:*:) (S1 (MetaSel (Just Symbol "_instBodyDataKind") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UKindConstraint dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_instBodyGadtCons") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UGadtConDecl dom stage))) (S1 (MetaSel (Just Symbol "_instBodyDerivings") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UDeriving dom stage))))))) (C1 (MetaCons "USpecializeInstance" PrefixI True) (S1 (MetaSel (Just Symbol "_specializeInstanceType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage))))) ((:+:) (C1 (MetaCons "UInlineInstance" PrefixI True) (S1 (MetaSel (Just Symbol "_instanceInline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UInlinePragma dom stage)))) (C1 (MetaCons "UInstanceSpecialize" PrefixI True) (S1 (MetaSel (Just Symbol "_specializeInstance") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann USpecializePragma dom stage)))))))

data UOverlapPragma dom stage Source #

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

Constructors

UEnableOverlap

OVERLAP pragma

UDisableOverlap

NO_OVERLAP pragma

UOverlappable

OVERLAPPABLE pragma

UOverlapping

OVERLAPPING pragma

UOverlaps

OVERLAPS pragma

UIncoherentOverlap

INCOHERENT pragma

Instances

type Rep (UOverlapPragma dom stage) Source # 
type Rep (UOverlapPragma dom stage) = D1 (MetaData "UOverlapPragma" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) ((:+:) (C1 (MetaCons "UEnableOverlap" PrefixI False) U1) ((:+:) (C1 (MetaCons "UDisableOverlap" PrefixI False) U1) (C1 (MetaCons "UOverlappable" PrefixI False) U1))) ((:+:) (C1 (MetaCons "UOverlapping" PrefixI False) U1) ((:+:) (C1 (MetaCons "UOverlaps" PrefixI False) U1) (C1 (MetaCons "UIncoherentOverlap" PrefixI False) U1))))

Type families

data UTypeFamily dom stage Source #

Open type and data families

Constructors

UTypeFamily

Type family declaration ( type family A a :: * -> * )

Fields

UDataFamily

Data family declaration ( data family A a :: * -> * )

Fields

Instances

type Rep (UTypeFamily dom stage) Source # 
type Rep (UTypeFamily dom stage) = D1 (MetaData "UTypeFamily" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "UTypeFamily" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_tfHead") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UDeclHead dom stage))) (S1 (MetaSel (Just Symbol "_tfSpec") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UTypeFamilySpec dom stage))))) (C1 (MetaCons "UDataFamily" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_tfHead") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UDeclHead dom stage))) (S1 (MetaSel (Just Symbol "_tfKind") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UKindConstraint dom stage))))))

data UTypeFamilySpec dom stage Source #

Type family specification with kinds specification and injectivity.

Constructors

UTypeFamilyKind

Specifies the kind of a type family ( :: * -> * )

Fields

UTypeFamilyTyVar

Specifies the kind of a type family ( = t :: * -> * )

Fields

UTypeFamilyInjectivity

Specifies the injectivity of a type family ( = r | r -> a )

Fields

Instances

type Rep (UTypeFamilySpec dom stage) Source # 
type Rep (UTypeFamilySpec dom stage) = D1 (MetaData "UTypeFamilySpec" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "UTypeFamilyKind" PrefixI True) (S1 (MetaSel (Just Symbol "_tfSpecKind") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UKindConstraint dom stage)))) ((:+:) (C1 (MetaCons "UTypeFamilyTyVar" PrefixI True) (S1 (MetaSel (Just Symbol "_tfTypeVar") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UTyVar dom stage)))) (C1 (MetaCons "UTypeFamilyInjectivity" PrefixI True) (S1 (MetaSel (Just Symbol "_tfInjectivity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UInjectivityAnn dom stage))))))

data UInjectivityAnn dom stage Source #

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

Constructors

UInjectivityAnn 

Fields

Instances

type Rep (UInjectivityAnn dom stage) Source # 
type Rep (UInjectivityAnn dom stage) = D1 (MetaData "UInjectivityAnn" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UInjectivityAnn" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_injAnnRes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UTyVar dom stage))) (S1 (MetaSel (Just Symbol "_injAnnDeps") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UName dom stage)))))

data UTypeEqn dom stage Source #

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

Constructors

UTypeEqn 

Fields

Instances

type Rep (UTypeEqn dom stage) Source # 
type Rep (UTypeEqn dom stage) = D1 (MetaData "UTypeEqn" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UTypeEqn" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_teLhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage))) (S1 (MetaSel (Just Symbol "_teRhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage)))))

Type definitions

data UGadtConDecl dom stage Source #

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

Constructors

UGadtConDecl 

Instances

type Rep (UGadtConDecl dom stage) Source # 
type Rep (UGadtConDecl dom stage) = D1 (MetaData "UGadtConDecl" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UGadtConDecl" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_gadtConNames") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UName dom stage))) (S1 (MetaSel (Just Symbol "_gadtConTypeArgs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UTyVar dom stage)))) ((:*:) (S1 (MetaSel (Just Symbol "_gadtConTypeCtx") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UContext dom stage))) (S1 (MetaSel (Just Symbol "_gadtConType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UGadtConType dom stage))))))

data UDataOrNewtypeKeyword dom stage Source #

The data or the newtype keyword to define ADTs.

Instances

type Rep (UDataOrNewtypeKeyword dom stage) Source # 
type Rep (UDataOrNewtypeKeyword dom stage) = D1 (MetaData "UDataOrNewtypeKeyword" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "UDataKeyword" PrefixI False) U1) (C1 (MetaCons "UNewtypeKeyword" PrefixI False) U1))

data UGadtConType dom stage Source #

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

Instances

type Rep (UGadtConType dom stage) Source # 
type Rep (UGadtConType dom stage) = D1 (MetaData "UGadtConType" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "UGadtNormalType" PrefixI True) (S1 (MetaSel (Just Symbol "_gadtConNormalType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage)))) (C1 (MetaCons "UGadtRecordType" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_gadtConRecordFields") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UFieldDecl dom stage))) (S1 (MetaSel (Just Symbol "_gadtConResultType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage))))))

data UFunDeps dom stage Source #

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

Constructors

UFunDeps 

Fields

Instances

type Rep (UFunDeps dom stage) Source # 
type Rep (UFunDeps dom stage) = D1 (MetaData "UFunDeps" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UFunDeps" PrefixI True) (S1 (MetaSel (Just Symbol "_funDeps") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UFunDep dom stage))))

data UFunDep dom stage Source #

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

Constructors

UFunDep 

Fields

Instances

type Rep (UFunDep dom stage) Source # 
type Rep (UFunDep dom stage) = D1 (MetaData "UFunDep" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UFunDep" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_funDepLhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UName dom stage))) (S1 (MetaSel (Just Symbol "_funDepRhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UName dom stage)))))

data UConDecl dom stage Source #

A constructor declaration for a datatype

Constructors

UConDecl

Ordinary data constructor ( C t1 t2 )

Fields

URecordDecl

Record data constructor ( C { _n1 :: t1, _n2 :: t2 } )

Fields

UInfixConDecl

Infix data constructor ( t1 :+: t2 )

Fields

Instances

type Rep (UConDecl dom stage) Source # 
type Rep (UConDecl dom stage) = D1 (MetaData "UConDecl" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "UConDecl" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_conTypeArgs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UTyVar dom stage))) (S1 (MetaSel (Just Symbol "_conTypeCtx") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UContext dom stage)))) ((:*:) (S1 (MetaSel (Just Symbol "_conDeclName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage))) (S1 (MetaSel (Just Symbol "_conDeclArgs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UType dom stage)))))) ((:+:) (C1 (MetaCons "URecordDecl" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_conTypeArgs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UTyVar dom stage))) (S1 (MetaSel (Just Symbol "_conTypeCtx") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UContext dom stage)))) ((:*:) (S1 (MetaSel (Just Symbol "_conDeclName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage))) (S1 (MetaSel (Just Symbol "_conDeclFields") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UFieldDecl dom stage)))))) (C1 (MetaCons "UInfixConDecl" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_conTypeArgs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UTyVar dom stage))) (S1 (MetaSel (Just Symbol "_conTypeCtx") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UContext dom stage)))) ((:*:) (S1 (MetaSel (Just Symbol "_conDeclLhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_conDeclOp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UOperator dom stage))) (S1 (MetaSel (Just Symbol "_conDeclRhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage)))))))))

data UFieldDecl dom stage Source #

Field declaration ( fld :: Int )

Constructors

UFieldDecl 

Fields

Instances

type Rep (UFieldDecl dom stage) Source # 
type Rep (UFieldDecl dom stage) = D1 (MetaData "UFieldDecl" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UFieldDecl" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_fieldNames") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UName dom stage))) (S1 (MetaSel (Just Symbol "_fieldType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage)))))

data UDeriving dom stage Source #

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

Constructors

UDerivingOne 

Fields

UDerivings 

Fields

Instances

type Rep (UDeriving dom stage) Source # 
type Rep (UDeriving dom stage) = D1 (MetaData "UDeriving" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "UDerivingOne" PrefixI True) (S1 (MetaSel (Just Symbol "_oneDerived") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UInstanceHead dom stage)))) (C1 (MetaCons "UDerivings" PrefixI True) (S1 (MetaSel (Just Symbol "_allDerived") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UInstanceHead dom stage)))))

Pattern synonyms

data UPatternTypeSignature dom stage Source #

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

Constructors

UPatternTypeSignature 

Fields

Instances

type Rep (UPatternTypeSignature dom stage) Source # 
type Rep (UPatternTypeSignature dom stage) = D1 (MetaData "UPatternTypeSignature" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UPatternTypeSignature" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_patSigName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage))) (S1 (MetaSel (Just Symbol "_patSigType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage)))))

data UPatternSynonym dom stage Source #

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

Constructors

UPatternSynonym 

Fields

Instances

type Rep (UPatternSynonym dom stage) Source # 
type Rep (UPatternSynonym dom stage) = D1 (MetaData "UPatternSynonym" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UPatternSynonym" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_patLhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UPatSynLhs dom stage))) (S1 (MetaSel (Just Symbol "_patRhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UPatSynRhs dom stage)))))

data UPatSynLhs dom stage Source #

Left hand side of a pattern synonym

Constructors

UNormalPatSyn

A left hand side with a constructor name and arguments ( Arrow t1 t2 )

Fields

UInfixPatSyn

An infix pattern synonym left-hand side ( t1 :+: t2 )

Fields

URecordPatSyn

A record-style pattern synonym left-hand side ( Arrow { arrowFrom, arrowTo } )

Fields

Instances

type Rep (UPatSynLhs dom stage) Source # 
type Rep (UPatSynLhs dom stage) = D1 (MetaData "UPatSynLhs" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "UNormalPatSyn" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_patName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage))) (S1 (MetaSel (Just Symbol "_patArgs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UName dom stage))))) ((:+:) (C1 (MetaCons "UInfixPatSyn" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_patSynLhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_patSynOp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UOperator dom stage))) (S1 (MetaSel (Just Symbol "_patSynRhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage)))))) (C1 (MetaCons "URecordPatSyn" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_patName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage))) (S1 (MetaSel (Just Symbol "_patArgs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UName dom stage)))))))

data UPatSynRhs dom stage Source #

Right-hand side of pattern synonym

Constructors

UBidirectionalPatSyn

pattern Int = App Int [] or pattern Int <- App Int [] where Int = App Int []

Fields

UOneDirectionalPatSyn
 pattern Int <- App Int []

Fields

Instances

type Rep (UPatSynRhs dom stage) Source # 
type Rep (UPatSynRhs dom stage) = D1 (MetaData "UPatSynRhs" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "UBidirectionalPatSyn" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_patRhsPat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UPattern dom stage))) (S1 (MetaSel (Just Symbol "_patRhsOpposite") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UPatSynWhere dom stage))))) (C1 (MetaCons "UOneDirectionalPatSyn" PrefixI True) (S1 (MetaSel (Just Symbol "_patRhsPat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UPattern dom stage)))))

data UPatSynWhere dom stage Source #

Where clause of pattern synonym (explicit expression direction)

Constructors

UPatSynWhere 

Fields

Instances

type Rep (UPatSynWhere dom stage) Source # 
type Rep (UPatSynWhere dom stage) = D1 (MetaData "UPatSynWhere" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UPatSynWhere" PrefixI True) (S1 (MetaSel (Just Symbol "_patOpposite") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UMatch dom stage))))

Foreign imports

data UCallConv dom stage Source #

Call conventions of foreign functions

Instances

type Rep (UCallConv dom stage) Source # 
type Rep (UCallConv dom stage) = D1 (MetaData "UCallConv" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "UStdCall" PrefixI False) U1) (C1 (MetaCons "UCCall" PrefixI False) U1)) ((:+:) (C1 (MetaCons "UCPlusPlus" PrefixI False) U1) (C1 (MetaCons "UDotNet" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "UJvm" PrefixI False) U1) (C1 (MetaCons "UJs" PrefixI False) U1)) ((:+:) (C1 (MetaCons "UJavaScript" PrefixI False) U1) (C1 (MetaCons "UCApi" PrefixI False) U1))))

data USafety dom stage Source #

Safety annotations for foreign calls

Instances

type Rep (USafety dom stage) Source # 
type Rep (USafety dom stage) = D1 (MetaData "USafety" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) ((:+:) (C1 (MetaCons "USafe" PrefixI False) U1) (C1 (MetaCons "UThreadSafe" PrefixI False) U1)) ((:+:) (C1 (MetaCons "UUnsafe" PrefixI False) U1) (C1 (MetaCons "UInterruptible" PrefixI False) U1)))

Role annotations

data URole dom stage Source #

Role annotations for types

Instances

type Rep (URole dom stage) Source # 
type Rep (URole dom stage) = D1 (MetaData "URole" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "UNominal" PrefixI False) U1) ((:+:) (C1 (MetaCons "URepresentational" PrefixI False) U1) (C1 (MetaCons "UPhantom" PrefixI False) U1)))

Pragmas

data UTopLevelPragma dom stage Source #

Top level pragmas

Constructors

URulePragma

A pragma that introduces source rewrite rules ( {--} )

Fields

UDeprPragma

A pragma that marks definitions as deprecated ( {-# DEPRECATED f "f will be replaced by g" )

Fields

UWarningPragma

A pragma that marks definitions as deprecated ( {-# WARNING unsafePerformIO "you should know what you are doing" )

Fields

UAnnPragma

A pragma that annotates a definition with an arbitrary value ( {-# ANN f 42 ) TODO: extract pragmas that appear both in top-level and in instances (inline, inlinable, noinline)

Fields

UInlinePragmaDecl 

Fields

ULinePragma

A pragma for maintaining line numbers in generated sources ( {--} )

USpecializeDecl 

Instances

type Rep (UTopLevelPragma dom stage) Source # 
type Rep (UTopLevelPragma dom stage) = D1 (MetaData "UTopLevelPragma" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) ((:+:) (C1 (MetaCons "URulePragma" PrefixI True) (S1 (MetaSel (Just Symbol "_pragmaRule") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG URule dom stage)))) ((:+:) (C1 (MetaCons "UDeprPragma" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_pragmaObjects") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UName dom stage))) (S1 (MetaSel (Just Symbol "_deprMessage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UStringNode dom stage))))) (C1 (MetaCons "UWarningPragma" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_pragmaObjects") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UName dom stage))) (S1 (MetaSel (Just Symbol "_warnMessage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UStringNode dom stage))))))) ((:+:) ((:+:) (C1 (MetaCons "UAnnPragma" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_annotationSubject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UAnnotationSubject dom stage))) (S1 (MetaSel (Just Symbol "_annotateExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))))) (C1 (MetaCons "UInlinePragmaDecl" PrefixI True) (S1 (MetaSel (Just Symbol "_pragmaInline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UInlinePragma dom stage))))) ((:+:) (C1 (MetaCons "ULinePragma" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_pragmaLineNum") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann LineNumber dom stage))) (S1 (MetaSel (Just Symbol "_pragmaFileName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UStringNode dom stage))))) (C1 (MetaCons "USpecializeDecl" PrefixI True) (S1 (MetaSel (Just Symbol "_specializePragma") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann USpecializePragma dom stage)))))))

data USpecializePragma dom stage Source #

Constructors

USpecializePragma

A pragma that tells the compiler that a polymorph function should be optimized for a given type ( {--} )

Fields

Instances

type Rep (USpecializePragma dom stage) Source # 
type Rep (USpecializePragma dom stage) = D1 (MetaData "USpecializePragma" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "USpecializePragma" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_pragmaPhase") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UPhaseControl dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_specializeDef") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage))) (S1 (MetaSel (Just Symbol "_specializeType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UType dom stage))))))

data URule dom stage Source #

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

Constructors

URule 

Fields

Instances

type Rep (URule dom stage) Source # 
type Rep (URule dom stage) = D1 (MetaData "URule" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "URule" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ruleName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UStringNode dom stage))) (S1 (MetaSel (Just Symbol "_rulePhase") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UPhaseControl dom stage)))) ((:*:) (S1 (MetaSel (Just Symbol "_ruleBounded") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG URuleVar dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_ruleLhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))) (S1 (MetaSel (Just Symbol "_ruleRhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage)))))))

data URuleVar dom stage Source #

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

Constructors

URuleVar

A simple rule variable

Fields

USigRuleVar

A rule variable with signature

Fields

Instances

type Rep (URuleVar dom stage) Source # 
type Rep (URuleVar dom stage) = D1 (MetaData "URuleVar" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "URuleVar" PrefixI True) (S1 (MetaSel (Just Symbol "_ruleVarName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage)))) (C1 (MetaCons "USigRuleVar" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ruleVarName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage))) (S1 (MetaSel (Just Symbol "_ruleVarType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage))))))

data UAnnotationSubject dom stage Source #

Annotation allows you to connect an expression to any declaration.

Constructors

UNameAnnotation

The definition with the given name is annotated

Fields

UTypeAnnotation

A type with the given name is annotated

Fields

UModuleAnnotation

The whole module is annotated

Instances

type Rep (UAnnotationSubject dom stage) Source # 
type Rep (UAnnotationSubject dom stage) = D1 (MetaData "UAnnotationSubject" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "UNameAnnotation" PrefixI True) (S1 (MetaSel (Just Symbol "_annotateName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage)))) ((:+:) (C1 (MetaCons "UTypeAnnotation" PrefixI True) (S1 (MetaSel (Just Symbol "_annotateName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage)))) (C1 (MetaCons "UModuleAnnotation" PrefixI False) U1)))

data UMinimalFormula dom stage Source #

Formulas of minimal annotations declaring which functions should be defined.

Constructors

UMinimalName 

Fields

UMinimalParen 

Fields

UMinimalOr

One of the minimal formulas are needed ( min1 | min2 )

Fields

UMinimalAnd

Both of the minimal formulas are needed ( min1 , min2 )

Instances

type Rep (UMinimalFormula dom stage) Source # 
type Rep (UMinimalFormula dom stage) = D1 (MetaData "UMinimalFormula" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) ((:+:) (C1 (MetaCons "UMinimalName" PrefixI True) (S1 (MetaSel (Just Symbol "_minimalName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage)))) (C1 (MetaCons "UMinimalParen" PrefixI True) (S1 (MetaSel (Just Symbol "_minimalInner") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UMinimalFormula dom stage))))) ((:+:) (C1 (MetaCons "UMinimalOr" PrefixI True) (S1 (MetaSel (Just Symbol "_minimalOrs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UMinimalFormula dom stage)))) (C1 (MetaCons "UMinimalAnd" PrefixI True) (S1 (MetaSel (Just Symbol "_minimalAnds") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UMinimalFormula dom stage))))))

data LineNumber dom stage Source #

A line number for a line pragma.

Constructors

LineNumber 

Fields

Instances

type Rep (LineNumber dom stage) Source # 
type Rep (LineNumber dom stage) = D1 (MetaData "LineNumber" "Language.Haskell.Tools.AST.Representation.Decls" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "LineNumber" PrefixI True) (S1 (MetaSel (Just Symbol "_lineNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

data UValueBind dom stage Source #

Value binding for top-level and local bindings

Constructors

USimpleBind

Non-function binding ( v = "12" ) TODO: use one name for a function instead of names in each match

Fields

UFunBind

Function binding ( f 0 = 1; f x = x ). All matches must have the same name.

Fields

Instances

type Rep (UValueBind dom stage) Source # 
type Rep (UValueBind dom stage) = D1 (MetaData "UValueBind" "Language.Haskell.Tools.AST.Representation.Binds" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "USimpleBind" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_valBindPat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UPattern dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_valBindRhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann URhs dom stage))) (S1 (MetaSel (Just Symbol "_valBindLocals") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG ULocalBinds dom stage)))))) (C1 (MetaCons "UFunBind" PrefixI True) (S1 (MetaSel (Just Symbol "_funBindMatches") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UMatch dom stage)))))

data UMatch dom stage Source #

Clause of function binding

Constructors

UMatch 

Fields

Instances

type Rep (UMatch dom stage) Source # 
type Rep (UMatch dom stage) = D1 (MetaData "UMatch" "Language.Haskell.Tools.AST.Representation.Binds" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UMatch" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_matchLhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UMatchLhs dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_matchRhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann URhs dom stage))) (S1 (MetaSel (Just Symbol "_matchBinds") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG ULocalBinds dom stage))))))

data UMatchLhs dom stage Source #

Something on the left side of the match

Constructors

UNormalLhs

A match lhs with the function name and parameter names ( f a b )

Fields

UInfixLhs

An infix match lhs for an operator ( a + b )

Fields

Instances

type Rep (UMatchLhs dom stage) Source # 
type Rep (UMatchLhs dom stage) = D1 (MetaData "UMatchLhs" "Language.Haskell.Tools.AST.Representation.Binds" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "UNormalLhs" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_matchLhsName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage))) (S1 (MetaSel (Just Symbol "_matchLhsArgs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UPattern dom stage))))) (C1 (MetaCons "UInfixLhs" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_matchLhsLhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UPattern dom stage))) (S1 (MetaSel (Just Symbol "_matchLhsOperator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UOperator dom stage)))) ((:*:) (S1 (MetaSel (Just Symbol "_matchLhsRhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UPattern dom stage))) (S1 (MetaSel (Just Symbol "_matchLhsArgs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UPattern dom stage)))))))

data ULocalBinds dom stage Source #

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

Constructors

ULocalBinds 

Fields

Instances

type Rep (ULocalBinds dom stage) Source # 
type Rep (ULocalBinds dom stage) = D1 (MetaData "ULocalBinds" "Language.Haskell.Tools.AST.Representation.Binds" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "ULocalBinds" PrefixI True) (S1 (MetaSel (Just Symbol "_localBinds") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG ULocalBind dom stage))))

data ULocalBind dom stage Source #

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

Constructors

ULocalValBind

A local binding for a value

Fields

ULocalSignature

A local type signature

Fields

ULocalFixity

A local fixity declaration

Fields

ULocalInline

A local inline pragma

Fields

Instances

NamedElement ULocalBind Source # 

Methods

elementName :: (RefMonads w r, MonadPlus r, Morph Maybe r, Morph [] r) => Reference w r (MU *) (MU *) (Ann ULocalBind dom st) (Ann ULocalBind dom st) (Ann UQualifiedName dom st) (Ann UQualifiedName dom st) Source #

type Rep (ULocalBind dom stage) Source # 
type Rep (ULocalBind dom stage) = D1 (MetaData "ULocalBind" "Language.Haskell.Tools.AST.Representation.Binds" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) ((:+:) (C1 (MetaCons "ULocalValBind" PrefixI True) (S1 (MetaSel (Just Symbol "_localVal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UValueBind dom stage)))) (C1 (MetaCons "ULocalSignature" PrefixI True) (S1 (MetaSel (Just Symbol "_localSig") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UTypeSignature dom stage))))) ((:+:) (C1 (MetaCons "ULocalFixity" PrefixI True) (S1 (MetaSel (Just Symbol "_localFixity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UFixitySignature dom stage)))) (C1 (MetaCons "ULocalInline" PrefixI True) (S1 (MetaSel (Just Symbol "_localInline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UInlinePragma dom stage))))))

data UTypeSignature dom stage Source #

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

Constructors

UTypeSignature 

Fields

Instances

type Rep (UTypeSignature dom stage) Source # 
type Rep (UTypeSignature dom stage) = D1 (MetaData "UTypeSignature" "Language.Haskell.Tools.AST.Representation.Binds" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UTypeSignature" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_tsName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UName dom stage))) (S1 (MetaSel (Just Symbol "_tsType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage)))))

Fixities

data UFixitySignature dom stage Source #

A fixity signature ( infixl 5 +, - ).

Constructors

UFixitySignature 

Instances

type Rep (UFixitySignature dom stage) Source # 
type Rep (UFixitySignature dom stage) = D1 (MetaData "UFixitySignature" "Language.Haskell.Tools.AST.Representation.Binds" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UFixitySignature" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_fixityAssoc") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann Assoc dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_fixityPrecedence") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG Precedence dom stage))) (S1 (MetaSel (Just Symbol "_fixityOperators") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UOperator dom stage))))))

data Assoc dom stage Source #

Associativity of an operator.

Constructors

AssocNone

non-associative operator (declared with infix)

AssocLeft

left-associative operator (declared with infixl)

AssocRight

right-associative operator (declared with infixr)

Instances

type Rep (Assoc dom stage) Source # 
type Rep (Assoc dom stage) = D1 (MetaData "Assoc" "Language.Haskell.Tools.AST.Representation.Binds" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "AssocNone" PrefixI False) U1) ((:+:) (C1 (MetaCons "AssocLeft" PrefixI False) U1) (C1 (MetaCons "AssocRight" PrefixI False) U1)))

data Precedence dom stage Source #

Numeric precedence of an operator

Constructors

Precedence 

Instances

type Rep (Precedence dom stage) Source # 
type Rep (Precedence dom stage) = D1 (MetaData "Precedence" "Language.Haskell.Tools.AST.Representation.Binds" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "Precedence" PrefixI True) (S1 (MetaSel (Just Symbol "_precedenceValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

data URhs dom stage Source #

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

Constructors

UUnguardedRhs

An unguarded right-hand-side ( = 3 )

Fields

UGuardedRhss

An unguarded right-hand-side ( | x == 1 = 3; | otherwise = 4 )

Fields

Instances

type Rep (URhs dom stage) Source # 
type Rep (URhs dom stage) = D1 (MetaData "URhs" "Language.Haskell.Tools.AST.Representation.Binds" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "UUnguardedRhs" PrefixI True) (S1 (MetaSel (Just Symbol "_rhsExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage)))) (C1 (MetaCons "UGuardedRhss" PrefixI True) (S1 (MetaSel (Just Symbol "_rhsGuards") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UGuardedRhs dom stage)))))

data UGuardedRhs dom stage Source #

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

Constructors

UGuardedRhs 

Fields

Instances

type Rep (UGuardedRhs dom stage) Source # 
type Rep (UGuardedRhs dom stage) = D1 (MetaData "UGuardedRhs" "Language.Haskell.Tools.AST.Representation.Binds" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UGuardedRhs" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_guardStmts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG URhsGuard dom stage))) (S1 (MetaSel (Just Symbol "_guardExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage)))))

data URhsGuard dom stage Source #

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

Constructors

UGuardBind

A bind statement in a pattern guard ( Just v <- x )

Fields

UGuardLet

A let statement in a pattern guard ( let x = 3 )

Fields

UGuardCheck

An expression to check for a pattern guard

Fields

Instances

type Rep (URhsGuard dom stage) Source # 
type Rep (URhsGuard dom stage) = D1 (MetaData "URhsGuard" "Language.Haskell.Tools.AST.Representation.Binds" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "UGuardBind" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_guardPat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UPattern dom stage))) (S1 (MetaSel (Just Symbol "_guardRhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))))) ((:+:) (C1 (MetaCons "UGuardLet" PrefixI True) (S1 (MetaSel (Just Symbol "_guardBinds") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG ULocalBind dom stage)))) (C1 (MetaCons "UGuardCheck" PrefixI True) (S1 (MetaSel (Just Symbol "_guardCheck") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))))))

data UInlinePragma dom stage Source #

Pragmas that control how the definitions will be inlined

Constructors

UInlinePragma

A pragma that marks a function for inlining to the compiler ( {--} )

UNoInlinePragma

A pragma that forbids a function from being inlined by the compiler ( {--} )

Fields

UInlinablePragma

A pragma that marks a function that it may be inlined by the compiler ( {--} )

Fields

Instances

type Rep (UInlinePragma dom stage) Source # 
type Rep (UInlinePragma dom stage) = D1 (MetaData "UInlinePragma" "Language.Haskell.Tools.AST.Representation.Binds" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "UInlinePragma" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_inlineConlike") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UConlikeAnnot dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_inlinePhase") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UPhaseControl dom stage))) (S1 (MetaSel (Just Symbol "_inlineDef") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage)))))) ((:+:) (C1 (MetaCons "UNoInlinePragma" PrefixI True) (S1 (MetaSel (Just Symbol "_noInlineDef") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage)))) (C1 (MetaCons "UInlinablePragma" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_inlinePhase") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UPhaseControl dom stage))) (S1 (MetaSel (Just Symbol "_inlinableDef") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage)))))))

data UConlikeAnnot dom stage Source #

A CONLIKE modifier for an INLINE pragma.

Constructors

UConlikeAnnot 

Instances

type Rep (UConlikeAnnot dom stage) Source # 
type Rep (UConlikeAnnot dom stage) = D1 (MetaData "UConlikeAnnot" "Language.Haskell.Tools.AST.Representation.Binds" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UConlikeAnnot" PrefixI False) U1)

data UPhaseControl dom stage Source #

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

Constructors

UPhaseControl 

Instances

type Rep (UPhaseControl dom stage) Source # 
type Rep (UPhaseControl dom stage) = D1 (MetaData "UPhaseControl" "Language.Haskell.Tools.AST.Representation.Binds" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UPhaseControl" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_phaseUntil") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG PhaseInvert dom stage))) (S1 (MetaSel (Just Symbol "_phaseNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG PhaseNumber dom stage)))))

data PhaseNumber dom stage Source #

Phase number for rewrite rules

Constructors

PhaseNumber 

Fields

Instances

type Rep (PhaseNumber dom stage) Source # 
type Rep (PhaseNumber dom stage) = D1 (MetaData "PhaseNumber" "Language.Haskell.Tools.AST.Representation.Binds" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "PhaseNumber" PrefixI True) (S1 (MetaSel (Just Symbol "_phaseNum") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)))

data PhaseInvert dom stage Source #

A tilde that marks the inversion of the phase number

Constructors

PhaseInvert 

Instances

type Rep (PhaseInvert dom stage) Source # 
type Rep (PhaseInvert dom stage) = D1 (MetaData "PhaseInvert" "Language.Haskell.Tools.AST.Representation.Binds" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "PhaseInvert" PrefixI False) U1)

data UExpr dom stage Source #

Haskell expressions

Constructors

UVar

A variable or a data constructor ( a )

Fields

ULit

Literal expression ( 42 )

Fields

UInfixApp

An infix operator application ( a + b )

Fields

UPrefixApp

Prefix operator application ( -x )

Fields

UApp

Function application ( f 4 )

Fields

ULambda

Lambda expression ( a b -> a + b )

Fields

ULet

Local binding ( let x = 2; y = 3 in e x y )

Fields

UIf

If expression ( if a then b else c )

Fields

UMultiIf

Multi way if expressions with MultiWayIf extension ( if | guard1 -> expr1; guard2 -> expr2 )

Fields

UCase

Pattern matching expression ( case expr of pat1 -> expr1; pat2 -> expr2 )

Fields

UDo

Do-notation expressions ( do x <- act1; act2 )

Fields

UTuple

Tuple expression ( (e1, e2, e3) )

Fields

UUnboxedTuple

Unboxed tuple expression ( () )

Fields

UTupleSection

Tuple section, enabled with TupleSections ( (a,,b) ). One of the elements must be missing.

UUnboxedTupSec

Unboxed tuple section enabled with TupleSections ( () ). One of the elements must be missing.

UList

List expression: [1,2,3]

Fields

UParArray

Parallel array expression: [: 1,2,3 :]

Fields

UParen

Parenthesized expression: ( a + b )

Fields

ULeftSection

Left operator section: (1+)

Fields

URightSection

Right operator section: (+1)

Fields

URecCon

Record value construction: Point { x = 3, y = -2 }

Fields

URecUpdate

Record value update: p1 { x = 3, y = -2 }

Fields

UEnum

Enumeration expression ( [1,3..10] )

Fields

UParArrayEnum

Parallel array enumeration ( [: 1,3 .. 10 :] )

Fields

UListComp

List comprehension ( [ (x, y) | x <- xs | y <- ys ] )

Fields

UParArrayComp

Parallel array comprehensions [: (x, y) | x <- xs , y <- ys :] enabled by ParallelArrays

Fields

UTypeSig

Explicit type signature ( x :: Int )

Fields

UExplTypeApp

Explicit type application ( show @Integer (read "5") )

Fields

UVarQuote

'x for template haskell reifying of expressions

Fields

UTypeQuote

''T for template haskell reifying of types

Fields

UBracketExpr

Template haskell bracket expression

Fields

USplice

Template haskell splice expression, for example: $(gen a) or $x

Fields

UQuasiQuoteExpr

Template haskell quasi-quotation: [$quoter|str]

Fields

UExprPragma 

Fields

UProc

Arrow definition: proc a -> f -< a+1

Fields

UArrowApp

Arrow application: f -< a+1

Fields

ULamCase

Lambda case ( case 0 -> 1; 1 -> 2 )

Fields

UStaticPtr

Static pointer expression ( static e ). The inner expression must be closed (cannot have variables bound outside) XML expressions omitted

Fields

Instances

HasScopeInfo dom => HasScopeInfo' (Ann UExpr dom st) Source # 

Methods

semanticsScope :: Ann UExpr dom st -> Scope Source #

type Rep (UExpr dom stage) Source # 
type Rep (UExpr dom stage) = D1 (MetaData "UExpr" "Language.Haskell.Tools.AST.Representation.Exprs" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "UVar" PrefixI True) (S1 (MetaSel (Just Symbol "_exprName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage)))) (C1 (MetaCons "ULit" PrefixI True) (S1 (MetaSel (Just Symbol "_exprLit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann ULiteral dom stage))))) ((:+:) (C1 (MetaCons "UInfixApp" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_exprLhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_exprOperator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UOperator dom stage))) (S1 (MetaSel (Just Symbol "_exprRhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage)))))) (C1 (MetaCons "UPrefixApp" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_exprOperator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UOperator dom stage))) (S1 (MetaSel (Just Symbol "_exprRhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))))))) ((:+:) ((:+:) (C1 (MetaCons "UApp" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_exprFun") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))) (S1 (MetaSel (Just Symbol "_exprArg") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))))) (C1 (MetaCons "ULambda" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_exprBindings") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UPattern dom stage))) (S1 (MetaSel (Just Symbol "_exprInner") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage)))))) ((:+:) (C1 (MetaCons "ULet" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_exprFunBind") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG ULocalBind dom stage))) (S1 (MetaSel (Just Symbol "_exprInner") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))))) ((:+:) (C1 (MetaCons "UIf" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_exprCond") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_exprThen") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))) (S1 (MetaSel (Just Symbol "_exprElse") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage)))))) (C1 (MetaCons "UMultiIf" PrefixI True) (S1 (MetaSel (Just Symbol "_exprIfAlts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UGuardedCaseRhs dom stage)))))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "UCase" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_exprCase") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))) (S1 (MetaSel (Just Symbol "_exprAlts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UAlt dom stage))))) (C1 (MetaCons "UDo" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_doKind") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UDoKind dom stage))) (S1 (MetaSel (Just Symbol "_exprStmts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UStmt dom stage)))))) ((:+:) (C1 (MetaCons "UTuple" PrefixI True) (S1 (MetaSel (Just Symbol "_tupleElems") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UExpr dom stage)))) ((:+:) (C1 (MetaCons "UUnboxedTuple" PrefixI True) (S1 (MetaSel (Just Symbol "_tupleElems") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UExpr dom stage)))) (C1 (MetaCons "UTupleSection" PrefixI True) (S1 (MetaSel (Just Symbol "_tupleSectionElems") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UTupSecElem dom stage))))))) ((:+:) ((:+:) (C1 (MetaCons "UUnboxedTupSec" PrefixI True) (S1 (MetaSel (Just Symbol "_tupleSectionElems") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UTupSecElem dom stage)))) (C1 (MetaCons "UList" PrefixI True) (S1 (MetaSel (Just Symbol "_listElems") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UExpr dom stage))))) ((:+:) (C1 (MetaCons "UParArray" PrefixI True) (S1 (MetaSel (Just Symbol "_listElems") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UExpr dom stage)))) ((:+:) (C1 (MetaCons "UParen" PrefixI True) (S1 (MetaSel (Just Symbol "_exprInner") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage)))) (C1 (MetaCons "ULeftSection" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_exprLhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))) (S1 (MetaSel (Just Symbol "_exprOperator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UOperator dom stage)))))))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "URightSection" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_exprOperator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UOperator dom stage))) (S1 (MetaSel (Just Symbol "_exprRhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))))) (C1 (MetaCons "URecCon" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_exprRecName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage))) (S1 (MetaSel (Just Symbol "_exprRecFields") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UFieldUpdate dom stage)))))) ((:+:) (C1 (MetaCons "URecUpdate" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_exprInner") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))) (S1 (MetaSel (Just Symbol "_exprRecFields") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UFieldUpdate dom stage))))) (C1 (MetaCons "UEnum" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_enumFrom") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_enumThen") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UExpr dom stage))) (S1 (MetaSel (Just Symbol "_enumTo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UExpr dom stage)))))))) ((:+:) ((:+:) (C1 (MetaCons "UParArrayEnum" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_enumFrom") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_enumThen") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UExpr dom stage))) (S1 (MetaSel (Just Symbol "_enumToFix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage)))))) (C1 (MetaCons "UListComp" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_compExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))) (S1 (MetaSel (Just Symbol "_compBody") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UListCompBody dom stage)))))) ((:+:) (C1 (MetaCons "UParArrayComp" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_compExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))) (S1 (MetaSel (Just Symbol "_compBody") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UListCompBody dom stage))))) ((:+:) (C1 (MetaCons "UTypeSig" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_exprInner") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))) (S1 (MetaSel (Just Symbol "_exprSig") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage))))) (C1 (MetaCons "UExplTypeApp" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_exprInner") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))) (S1 (MetaSel (Just Symbol "_exprType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage))))))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "UVarQuote" PrefixI True) (S1 (MetaSel (Just Symbol "_quotedName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage)))) (C1 (MetaCons "UTypeQuote" PrefixI True) (S1 (MetaSel (Just Symbol "_quotedName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage))))) ((:+:) (C1 (MetaCons "UBracketExpr" PrefixI True) (S1 (MetaSel (Just Symbol "_exprBracket") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UBracket dom stage)))) ((:+:) (C1 (MetaCons "USplice" PrefixI True) (S1 (MetaSel (Just Symbol "_exprSplice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann USplice dom stage)))) (C1 (MetaCons "UQuasiQuoteExpr" PrefixI True) (S1 (MetaSel (Just Symbol "_exprQQ") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UQuasiQuote dom stage))))))) ((:+:) ((:+:) (C1 (MetaCons "UExprPragma" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_exprPragma") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExprPragma dom stage))) (S1 (MetaSel (Just Symbol "_innerExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))))) (C1 (MetaCons "UProc" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_procPattern") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UPattern dom stage))) (S1 (MetaSel (Just Symbol "_procExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UCmd dom stage)))))) ((:+:) (C1 (MetaCons "UArrowApp" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_exprLhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_arrowAppl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UArrowAppl dom stage))) (S1 (MetaSel (Just Symbol "_exprRhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage)))))) ((:+:) (C1 (MetaCons "ULamCase" PrefixI True) (S1 (MetaSel (Just Symbol "_exprAlts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UAlt dom stage)))) (C1 (MetaCons "UStaticPtr" PrefixI True) (S1 (MetaSel (Just Symbol "_exprInner") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))))))))))

data UFieldUpdate dom stage Source #

Field update expressions

Constructors

UNormalFieldUpdate

Update of a field ( x = 1 )

Fields

UFieldPun

Update the field to the value of the same name ( x )

Fields

UFieldWildcard

Update the fields of the bounded names to their values ( .. ). Must be the last initializer. Cannot be used in a record update expression.

Fields

Instances

type Rep (UFieldUpdate dom stage) Source # 
type Rep (UFieldUpdate dom stage) = D1 (MetaData "UFieldUpdate" "Language.Haskell.Tools.AST.Representation.Exprs" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "UNormalFieldUpdate" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_fieldName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage))) (S1 (MetaSel (Just Symbol "_fieldValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))))) ((:+:) (C1 (MetaCons "UFieldPun" PrefixI True) (S1 (MetaSel (Just Symbol "_fieldUpdateName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage)))) (C1 (MetaCons "UFieldWildcard" PrefixI True) (S1 (MetaSel (Just Symbol "_fieldWildcard") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UFieldWildcard dom stage))))))

data UFieldWildcard dom stage Source #

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

Constructors

FldWildcard 

Instances

HasImplicitFieldsInfo dom => HasImplicitFieldsInfo' (Ann UFieldWildcard dom st) Source # 
type Rep (UFieldWildcard dom stage) Source # 
type Rep (UFieldWildcard dom stage) = D1 (MetaData "UFieldWildcard" "Language.Haskell.Tools.AST.Representation.Exprs" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "FldWildcard" PrefixI False) U1)

data UTupSecElem dom stage Source #

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

Constructors

Present

An existing element in a tuple section

Fields

Missing

A missing element in a tuple section

Instances

type Rep (UTupSecElem dom stage) Source # 
type Rep (UTupSecElem dom stage) = D1 (MetaData "UTupSecElem" "Language.Haskell.Tools.AST.Representation.Exprs" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "Present" PrefixI True) (S1 (MetaSel (Just Symbol "_tupSecExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage)))) (C1 (MetaCons "Missing" PrefixI False) U1))

data UAlt' expr dom stage Source #

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

Constructors

UAlt 

Fields

Instances

type Rep (UAlt' expr dom stage) Source # 
type Rep (UAlt' expr dom stage) = D1 (MetaData "UAlt'" "Language.Haskell.Tools.AST.Representation.Exprs" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UAlt" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_altPattern") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UPattern dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_altRhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann (UCaseRhs' expr) dom stage))) (S1 (MetaSel (Just Symbol "_altBinds") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG ULocalBinds dom stage))))))

data UCaseRhs' expr dom stage Source #

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

Constructors

UUnguardedCaseRhs

Unguarded right-hand side a pattern match ( -> 3 )

Fields

UGuardedCaseRhss

Guarded right-hand sides of a pattern match ( | x == 1 -> 3; | otherwise -> 4 )

Fields

Instances

type Rep (UCaseRhs' expr dom stage) Source # 
type Rep (UCaseRhs' expr dom stage) = D1 (MetaData "UCaseRhs'" "Language.Haskell.Tools.AST.Representation.Exprs" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "UUnguardedCaseRhs" PrefixI True) (S1 (MetaSel (Just Symbol "_rhsCaseExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann expr dom stage)))) (C1 (MetaCons "UGuardedCaseRhss" PrefixI True) (S1 (MetaSel (Just Symbol "_rhsCaseGuards") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG (UGuardedCaseRhs' expr) dom stage)))))

data UGuardedCaseRhs' expr dom stage Source #

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

Constructors

UGuardedCaseRhs 

Fields

Instances

type Rep (UGuardedCaseRhs' expr dom stage) Source # 
type Rep (UGuardedCaseRhs' expr dom stage) = D1 (MetaData "UGuardedCaseRhs'" "Language.Haskell.Tools.AST.Representation.Exprs" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UGuardedCaseRhs" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_caseGuardStmts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG URhsGuard dom stage))) (S1 (MetaSel (Just Symbol "_caseGuardExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann expr dom stage)))))

data UExprPragma dom stage Source #

Pragmas that can be applied to expressions

Constructors

UCorePragma

A CORE pragma for adding notes to expressions.

Fields

USccPragma

An SCC pragma for defining cost centers for profiling

Fields

UGeneratedPragma

A pragma that describes if an expression was generated from a code fragment by an external tool ( {--} )

Fields

Instances

type Rep (UExprPragma dom stage) Source # 
type Rep (UExprPragma dom stage) = D1 (MetaData "UExprPragma" "Language.Haskell.Tools.AST.Representation.Exprs" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "UCorePragma" PrefixI True) (S1 (MetaSel (Just Symbol "_pragmaStr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UStringNode dom stage)))) ((:+:) (C1 (MetaCons "USccPragma" PrefixI True) (S1 (MetaSel (Just Symbol "_pragmaStr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UStringNode dom stage)))) (C1 (MetaCons "UGeneratedPragma" PrefixI True) (S1 (MetaSel (Just Symbol "_pragmaSrcRange") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann USourceRange dom stage))))))

data USourceRange dom stage Source #

In-AST source ranges (for generated pragmas)

Constructors

USourceRange 

Fields

Instances

type Rep (USourceRange dom stage) Source # 
type Rep (USourceRange dom stage) = D1 (MetaData "USourceRange" "Language.Haskell.Tools.AST.Representation.Exprs" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "USourceRange" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_srFileName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UStringNode dom stage))) (S1 (MetaSel (Just Symbol "_srFromLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann Number dom stage)))) ((:*:) (S1 (MetaSel (Just Symbol "_srFromCol") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann Number dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_srToLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann Number dom stage))) (S1 (MetaSel (Just Symbol "_srToCol") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann Number dom stage)))))))

data Number dom stage Source #

Constructors

Number 

Instances

type Rep (Number dom stage) Source # 
type Rep (Number dom stage) = D1 (MetaData "Number" "Language.Haskell.Tools.AST.Representation.Exprs" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "Number" PrefixI True) (S1 (MetaSel (Just Symbol "_numberInteger") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)))

Arrows

data UCmd dom stage Source #

Constructors

UArrowAppCmd

An arrow application command ( f -< x + 1 )

Fields

UArrowFormCmd

A form command ( (|untilA (increment -< x+y) (within 0.5 -< x)|) )

Fields

UAppCmd

A function application command

Fields

UInfixCmd

An infix command application

Fields

ULambdaCmd

A lambda command

Fields

UParenCmd

A parenthesized command

Fields

UCaseCmd

A pattern match command

Fields

UIfCmd

An if command ( if f x y then g -< x+1 else h -< y+2 )

Fields

ULetCmd

A local binding command ( let z = x+y )

Fields

UDoCmd

A do-notation in a command

Fields

Instances

type Rep (UCmd dom stage) Source # 
type Rep (UCmd dom stage) = D1 (MetaData "UCmd" "Language.Haskell.Tools.AST.Representation.Exprs" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "UArrowAppCmd" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cmdLhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_cmdArrowOp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UArrowAppl dom stage))) (S1 (MetaSel (Just Symbol "_cmdRhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage)))))) (C1 (MetaCons "UArrowFormCmd" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cmdExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))) (S1 (MetaSel (Just Symbol "_cmdInnerCmds") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UCmd dom stage)))))) ((:+:) (C1 (MetaCons "UAppCmd" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cmdInnerCmd") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UCmd dom stage))) (S1 (MetaSel (Just Symbol "_cmdApplied") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))))) ((:+:) (C1 (MetaCons "UInfixCmd" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cmdLeftCmd") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UCmd dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_cmdOperator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage))) (S1 (MetaSel (Just Symbol "_cmdRightCmd") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UCmd dom stage)))))) (C1 (MetaCons "ULambdaCmd" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cmdBindings") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UPattern dom stage))) (S1 (MetaSel (Just Symbol "_cmdInner") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UCmd dom stage)))))))) ((:+:) ((:+:) (C1 (MetaCons "UParenCmd" PrefixI True) (S1 (MetaSel (Just Symbol "_cmdInner") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UCmd dom stage)))) (C1 (MetaCons "UCaseCmd" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cmdExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))) (S1 (MetaSel (Just Symbol "_cmdAlts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UCmdAlt dom stage)))))) ((:+:) (C1 (MetaCons "UIfCmd" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cmdExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_cmdThen") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UCmd dom stage))) (S1 (MetaSel (Just Symbol "_cmdElse") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UCmd dom stage)))))) ((:+:) (C1 (MetaCons "ULetCmd" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cmdBinds") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG ULocalBind dom stage))) (S1 (MetaSel (Just Symbol "_cmdInner") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UCmd dom stage))))) (C1 (MetaCons "UDoCmd" PrefixI True) (S1 (MetaSel (Just Symbol "_cmdStmts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UCmdStmt dom stage))))))))

data UArrowAppl dom stage Source #

Constructors

ULeftAppl

Left arrow application: -<

URightAppl

Right arrow application: >-

ULeftHighApp

Left arrow high application: -<<

URightHighApp

Right arrow high application: >>-

Instances

type Rep (UArrowAppl dom stage) Source # 
type Rep (UArrowAppl dom stage) = D1 (MetaData "UArrowAppl" "Language.Haskell.Tools.AST.Representation.Exprs" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) ((:+:) (C1 (MetaCons "ULeftAppl" PrefixI False) U1) (C1 (MetaCons "URightAppl" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ULeftHighApp" PrefixI False) U1) (C1 (MetaCons "URightHighApp" PrefixI False) U1)))

data UStmt' expr dom stage Source #

Normal monadic statements

Constructors

UBindStmt

Binding statement ( x <- action )

Fields

UExprStmt

Non-binding statement ( action )

Fields

ULetStmt

Let statement ( let x = 3; y = 4 )

Fields

URecStmt

A recursive binding statement with ( rec b <- f a c; c <- f b a )

Fields

Instances

type Rep (UStmt' expr dom stage) Source # 
type Rep (UStmt' expr dom stage) = D1 (MetaData "UStmt'" "Language.Haskell.Tools.AST.Representation.Stmts" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) ((:+:) (C1 (MetaCons "UBindStmt" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_stmtPattern") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UPattern dom stage))) (S1 (MetaSel (Just Symbol "_stmtExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann expr dom stage))))) (C1 (MetaCons "UExprStmt" PrefixI True) (S1 (MetaSel (Just Symbol "_stmtExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann expr dom stage))))) ((:+:) (C1 (MetaCons "ULetStmt" PrefixI True) (S1 (MetaSel (Just Symbol "_stmtBinds") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG ULocalBind dom stage)))) (C1 (MetaCons "URecStmt" PrefixI True) (S1 (MetaSel (Just Symbol "_cmdStmtBinds") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG (UStmt' expr) dom stage))))))

data UListCompBody dom stage Source #

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

Constructors

UListCompBody 

Fields

Instances

type Rep (UListCompBody dom stage) Source # 
type Rep (UListCompBody dom stage) = D1 (MetaData "UListCompBody" "Language.Haskell.Tools.AST.Representation.Stmts" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UListCompBody" PrefixI True) (S1 (MetaSel (Just Symbol "_compStmts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UCompStmt dom stage))))

data UCompStmt dom stage Source #

List comprehension statement

Constructors

UCompStmt

Normal monadic statement of a list comprehension

Fields

UThenStmt

Then statements by TransformListComp ( then sortWith by (x + y) )

Fields

UGroupStmt

Grouping statements by TransformListComp ( then group by (x + y) using groupWith ) Note: either byExpr or usingExpr must have a value

Fields

Instances

type Rep (UCompStmt dom stage) Source # 
type Rep (UCompStmt dom stage) = D1 (MetaData "UCompStmt" "Language.Haskell.Tools.AST.Representation.Stmts" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "UCompStmt" PrefixI True) (S1 (MetaSel (Just Symbol "_compStmt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UStmt dom stage)))) ((:+:) (C1 (MetaCons "UThenStmt" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_thenExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))) (S1 (MetaSel (Just Symbol "_byExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UExpr dom stage))))) (C1 (MetaCons "UGroupStmt" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_byExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UExpr dom stage))) (S1 (MetaSel (Just Symbol "_usingExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UExpr dom stage)))))))

data UDoKind dom stage Source #

Keywords do or mdo to start a do-block

Constructors

UDoKeyword 
UMDoKeyword 

Instances

type Rep (UDoKind dom stage) Source # 
type Rep (UDoKind dom stage) = D1 (MetaData "UDoKind" "Language.Haskell.Tools.AST.Representation.Stmts" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "UDoKeyword" PrefixI False) U1) (C1 (MetaCons "UMDoKeyword" PrefixI False) U1))

data UPattern dom stage Source #

Representation of patterns for pattern bindings

Constructors

UVarPat

Pattern name binding

Fields

ULitPat

Literal pattern

Fields

UInfixAppPat

Infix constructor application pattern ( a :+: b )

Fields

UAppPat

Constructor application pattern ( Point x y )

Fields

UTuplePat

Tuple pattern ( (x,y) )

Fields

UUnboxTuplePat

Unboxed tuple pattern ( () )

Fields

UListPat

List pattern ( [1,2,a,x] )

Fields

UParArrPat

Parallel array pattern ( [:1,2,a,x:] )

Fields

UParenPat

Parenthesised patterns

Fields

URecPat

Record pattern ( Point { x = 3, y } )

Fields

UAsPat

As-pattern (explicit name binding) ( ls@(hd:_) )

Fields

UWildPat

Wildcard pattern: ( _ )

UIrrefutablePat

Irrefutable pattern ( ~(x:_) )

Fields

UBangPat

Bang pattern ( !x )

Fields

UTypeSigPat

Pattern with explicit type signature ( x :: Int )

Fields

UViewPat

View pattern ( f -> Just 1 ) regular list pattern omitted xml patterns omitted

Fields

USplicePat

Splice patterns: $(generateX inp)

Fields

UQuasiQuotePat

Quasi-quoted patterns: [| 1 + 2 |]

Fields

UNPlusKPat 

Fields

Instances

type Rep (UPattern dom stage) Source # 
type Rep (UPattern dom stage) = D1 (MetaData "UPattern" "Language.Haskell.Tools.AST.Representation.Patterns" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "UVarPat" PrefixI True) (S1 (MetaSel (Just Symbol "_patternName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage)))) (C1 (MetaCons "ULitPat" PrefixI True) (S1 (MetaSel (Just Symbol "_patternLiteral") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann ULiteral dom stage))))) ((:+:) (C1 (MetaCons "UInfixAppPat" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_patternLhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UPattern dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_patternOperator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UOperator dom stage))) (S1 (MetaSel (Just Symbol "_patternRhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UPattern dom stage)))))) (C1 (MetaCons "UAppPat" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_patternName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage))) (S1 (MetaSel (Just Symbol "_patternArgs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UPattern dom stage))))))) ((:+:) ((:+:) (C1 (MetaCons "UTuplePat" PrefixI True) (S1 (MetaSel (Just Symbol "_patternElems") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UPattern dom stage)))) (C1 (MetaCons "UUnboxTuplePat" PrefixI True) (S1 (MetaSel (Just Symbol "_patternElems") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UPattern dom stage))))) ((:+:) (C1 (MetaCons "UListPat" PrefixI True) (S1 (MetaSel (Just Symbol "_patternElems") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UPattern dom stage)))) ((:+:) (C1 (MetaCons "UParArrPat" PrefixI True) (S1 (MetaSel (Just Symbol "_patternElems") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UPattern dom stage)))) (C1 (MetaCons "UParenPat" PrefixI True) (S1 (MetaSel (Just Symbol "_patternInner") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UPattern dom stage)))))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "URecPat" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_patternName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage))) (S1 (MetaSel (Just Symbol "_patternFields") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UPatternField dom stage))))) (C1 (MetaCons "UAsPat" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_patternName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage))) (S1 (MetaSel (Just Symbol "_patternInner") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UPattern dom stage)))))) ((:+:) (C1 (MetaCons "UWildPat" PrefixI False) U1) ((:+:) (C1 (MetaCons "UIrrefutablePat" PrefixI True) (S1 (MetaSel (Just Symbol "_patternInner") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UPattern dom stage)))) (C1 (MetaCons "UBangPat" PrefixI True) (S1 (MetaSel (Just Symbol "_patternInner") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UPattern dom stage))))))) ((:+:) ((:+:) (C1 (MetaCons "UTypeSigPat" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_patternInner") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UPattern dom stage))) (S1 (MetaSel (Just Symbol "_patternType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage))))) (C1 (MetaCons "UViewPat" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_patternExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UExpr dom stage))) (S1 (MetaSel (Just Symbol "_patternInner") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UPattern dom stage)))))) ((:+:) (C1 (MetaCons "USplicePat" PrefixI True) (S1 (MetaSel (Just Symbol "_patternSplice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann USplice dom stage)))) ((:+:) (C1 (MetaCons "UQuasiQuotePat" PrefixI True) (S1 (MetaSel (Just Symbol "_patQQ") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UQuasiQuote dom stage)))) (C1 (MetaCons "UNPlusKPat" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_patternName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage))) (S1 (MetaSel (Just Symbol "_patternLit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann ULiteral dom stage))))))))))

data UPatternField dom stage Source #

Constructors

UNormalFieldPattern

Named field pattern ( p = Point 3 2 )

Fields

UFieldPunPattern

Named field pun ( p )

Fields

UFieldWildcardPattern

Wildcard field pattern ( .. )

Instances

type Rep (UPatternField dom stage) Source # 
type Rep (UPatternField dom stage) = D1 (MetaData "UPatternField" "Language.Haskell.Tools.AST.Representation.Patterns" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "UNormalFieldPattern" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_fieldPatternName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage))) (S1 (MetaSel (Just Symbol "_fieldPattern") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UPattern dom stage))))) ((:+:) (C1 (MetaCons "UFieldPunPattern" PrefixI True) (S1 (MetaSel (Just Symbol "_fieldPatternName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage)))) (C1 (MetaCons "UFieldWildcardPattern" PrefixI True) (S1 (MetaSel (Just Symbol "_fieldPatternWildcard") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UFieldWildcard dom stage))))))

data UTyVar dom stage Source #

Type variable declaration

Constructors

UTyVarDecl 

Fields

Instances

type Rep (UTyVar dom stage) Source # 
type Rep (UTyVar dom stage) = D1 (MetaData "UTyVar" "Language.Haskell.Tools.AST.Representation.Types" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UTyVarDecl" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_tyVarName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage))) (S1 (MetaSel (Just Symbol "_tyVarKind") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnMaybeG UKindConstraint dom stage)))))

data UType dom stage Source #

Haskell types

Constructors

UTyForall

Forall types ( forall x y . type )

Fields

UTyCtx

Type with a context ( forall x y . type )

Fields

UTyFun

Function types ( a -> b )

Fields

UTyTuple

Tuple types ( (a,b) )

Fields

UTyUnbTuple

Unboxed tuple types ( () )

Fields

UTyList

List type with special syntax ( [a] )

Fields

UTyParArray

Parallel array type ( [:a:] )

Fields

UTyApp

Type application ( F a )

Fields

UTyVar

Type variable or constructor ( a )

Fields

UTyParen

Type surrounded by parentheses ( (T a) )

Fields

UTyInfix

Infix type constructor ( (a <: b) )

Fields

UTyKinded

Type with explicit kind signature ( a :: * )

Fields

UTyPromoted 

Fields

UTySplice

A Template Haskell splice type ( $(genType) ).

Fields

UTyQuasiQuote

A Template Haskell quasi-quote type ( [quoter| ... ] ).

Fields

UTyBang

Strict type marked with !.

Fields

UTyLazy

Lazy type marked with ~. (Should only be used if Strict or StrictData language extension is used)

Fields

UTyUnpack

Strict type marked with UNPACK pragma. (Usually contains the bang mark.)

Fields

UTyNoUnpack

Strict type marked with NOUNPACK pragma. (Usually contains the bang mark.)

Fields

UTyWildcard

A wildcard type ( _ ) with -XPartialTypeSignatures

UTyNamedWildc

A named wildcard type ( _t ) with -XPartialTypeSignatures

Fields

Instances

type Rep (UType dom stage) Source # 
type Rep (UType dom stage) = D1 (MetaData "UType" "Language.Haskell.Tools.AST.Representation.Types" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "UTyForall" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_typeBounded") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UTyVar dom stage))) (S1 (MetaSel (Just Symbol "_typeType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage))))) (C1 (MetaCons "UTyCtx" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_typeCtx") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UContext dom stage))) (S1 (MetaSel (Just Symbol "_typeType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage)))))) ((:+:) (C1 (MetaCons "UTyFun" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_typeParam") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage))) (S1 (MetaSel (Just Symbol "_typeResult") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage))))) ((:+:) (C1 (MetaCons "UTyTuple" PrefixI True) (S1 (MetaSel (Just Symbol "_typeElements") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UType dom stage)))) (C1 (MetaCons "UTyUnbTuple" PrefixI True) (S1 (MetaSel (Just Symbol "_typeElements") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UType dom stage))))))) ((:+:) ((:+:) (C1 (MetaCons "UTyList" PrefixI True) (S1 (MetaSel (Just Symbol "_typeElement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage)))) (C1 (MetaCons "UTyParArray" PrefixI True) (S1 (MetaSel (Just Symbol "_typeElement") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage))))) ((:+:) (C1 (MetaCons "UTyApp" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_typeCon") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage))) (S1 (MetaSel (Just Symbol "_typeArg") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage))))) ((:+:) (C1 (MetaCons "UTyVar" PrefixI True) (S1 (MetaSel (Just Symbol "_typeName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage)))) (C1 (MetaCons "UTyParen" PrefixI True) (S1 (MetaSel (Just Symbol "_typeInner") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage)))))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "UTyInfix" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_typeLeft") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_typeOperator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UOperator dom stage))) (S1 (MetaSel (Just Symbol "_typeRight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage)))))) (C1 (MetaCons "UTyKinded" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_typeInner") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage))) (S1 (MetaSel (Just Symbol "_typeKind") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UKind dom stage)))))) ((:+:) (C1 (MetaCons "UTyPromoted" PrefixI True) (S1 (MetaSel (Just Symbol "_tpPromoted") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann (UPromoted UType) dom stage)))) ((:+:) (C1 (MetaCons "UTySplice" PrefixI True) (S1 (MetaSel (Just Symbol "_tsSplice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann USplice dom stage)))) (C1 (MetaCons "UTyQuasiQuote" PrefixI True) (S1 (MetaSel (Just Symbol "_typeQQ") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UQuasiQuote dom stage))))))) ((:+:) ((:+:) (C1 (MetaCons "UTyBang" PrefixI True) (S1 (MetaSel (Just Symbol "_typeInner") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage)))) ((:+:) (C1 (MetaCons "UTyLazy" PrefixI True) (S1 (MetaSel (Just Symbol "_typeInner") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage)))) (C1 (MetaCons "UTyUnpack" PrefixI True) (S1 (MetaSel (Just Symbol "_typeInner") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage)))))) ((:+:) (C1 (MetaCons "UTyNoUnpack" PrefixI True) (S1 (MetaSel (Just Symbol "_typeInner") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage)))) ((:+:) (C1 (MetaCons "UTyWildcard" PrefixI False) U1) (C1 (MetaCons "UTyNamedWildc" PrefixI True) (S1 (MetaSel (Just Symbol "_typeWildcardName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage)))))))))

data UContext dom stage Source #

Constructors

UContext

Assertions with the fat arrow ( C a => ... )

Fields

Instances

type Rep (UContext dom stage) Source # 
type Rep (UContext dom stage) = D1 (MetaData "UContext" "Language.Haskell.Tools.AST.Representation.Types" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UContext" PrefixI True) (S1 (MetaSel (Just Symbol "_contextAssertion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UAssertion dom stage))))

data UAssertion dom stage Source #

A single assertion in the context

Constructors

UClassAssert

Class assertion (Cls x)

Fields

UInfixAssert

Infix class assertion, also contains type equations ( a ~ X y )

Fields

UImplicitAssert

Assertion for implicit parameter binding ( ?cmp :: a -> a -> Bool )

Fields

UTupleAssert

Multiple assertions in one ( (Ord a, Show a) )

Fields

UWildcardAssert

Wildcard assertion ( _ ), enabled by PartialTypeSignatures

Instances

type Rep (UAssertion dom stage) Source # 
type Rep (UAssertion dom stage) = D1 (MetaData "UAssertion" "Language.Haskell.Tools.AST.Representation.Types" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) ((:+:) (C1 (MetaCons "UClassAssert" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_assertClsName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage))) (S1 (MetaSel (Just Symbol "_assertTypes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UType dom stage))))) (C1 (MetaCons "UInfixAssert" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_assertLhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_assertOp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UOperator dom stage))) (S1 (MetaSel (Just Symbol "_assertRhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage))))))) ((:+:) (C1 (MetaCons "UImplicitAssert" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_assertImplVar") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage))) (S1 (MetaSel (Just Symbol "_assertImplType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage))))) ((:+:) (C1 (MetaCons "UTupleAssert" PrefixI True) (S1 (MetaSel (Just Symbol "_innerAsserts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UAssertion dom stage)))) (C1 (MetaCons "UWildcardAssert" PrefixI False) U1))))

data UKindConstraint dom stage Source #

Kind constraint ( :: * -> * )

Constructors

UKindConstraint 

Fields

Instances

type Rep (UKindConstraint dom stage) Source # 
type Rep (UKindConstraint dom stage) = D1 (MetaData "UKindConstraint" "Language.Haskell.Tools.AST.Representation.Kinds" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UKindConstraint" PrefixI True) (S1 (MetaSel (Just Symbol "_kindConstr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UKind dom stage))))

data UKind dom stage Source #

Haskell kinds

Constructors

UStarKind

*, the kind of types

UUnboxKind

#, the kind of unboxed types

UFunKind

->, the kind of type constructor

Fields

UParenKind

A parenthesised kind

Fields

UVarKind

Kind variable (using PolyKinds extension)

Fields

UAppKind

Kind application ( k1 k2 )

Fields

UInfixAppKind

Infix kind application ( k1 ~> k2 )

Fields

UListKind

A list kind ( [k] )

Fields

UTupleKind

A tuple kind ( (Symbol, *) )

Fields

UPromotedKind

A promoted kind ( '(k1,k2,k3) )

Fields

UTypeKind

A type on the kind level with TypeInType

Fields

Instances

type Rep (UKind dom stage) Source # 
type Rep (UKind dom stage) = D1 (MetaData "UKind" "Language.Haskell.Tools.AST.Representation.Kinds" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "UStarKind" PrefixI False) U1) (C1 (MetaCons "UUnboxKind" PrefixI False) U1)) ((:+:) (C1 (MetaCons "UFunKind" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_kindLeft") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UKind dom stage))) (S1 (MetaSel (Just Symbol "_kindRight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UKind dom stage))))) ((:+:) (C1 (MetaCons "UParenKind" PrefixI True) (S1 (MetaSel (Just Symbol "_kindParen") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UKind dom stage)))) (C1 (MetaCons "UVarKind" PrefixI True) (S1 (MetaSel (Just Symbol "_kindVar") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage))))))) ((:+:) ((:+:) (C1 (MetaCons "UAppKind" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_kindAppFun") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UKind dom stage))) (S1 (MetaSel (Just Symbol "_kindAppArg") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UKind dom stage))))) ((:+:) (C1 (MetaCons "UInfixAppKind" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_kindLhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UKind dom stage))) ((:*:) (S1 (MetaSel (Just Symbol "_kindAppOp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UOperator dom stage))) (S1 (MetaSel (Just Symbol "_kindRhs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UKind dom stage)))))) (C1 (MetaCons "UListKind" PrefixI True) (S1 (MetaSel (Just Symbol "_kindElem") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UKind dom stage)))))) ((:+:) (C1 (MetaCons "UTupleKind" PrefixI True) (S1 (MetaSel (Just Symbol "_kindElems") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UKind dom stage)))) ((:+:) (C1 (MetaCons "UPromotedKind" PrefixI True) (S1 (MetaSel (Just Symbol "_kindPromoted") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann (UPromoted UKind) dom stage)))) (C1 (MetaCons "UTypeKind" PrefixI True) (S1 (MetaSel (Just Symbol "_kindType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UType dom stage))))))))

data UPromoted t dom stage Source #

Constructors

UPromotedInt

Numeric value promoted to the kind level.

UPromotedString

String value promoted to the kind level.

UPromotedCon

A data constructor value promoted to the kind level.

Fields

UPromotedList

A list of elements as a kind.

Fields

UPromotedTuple

A tuple of elements as a kind.

Fields

UPromotedUnit

Kind of the unit value ().

Instances

type Rep (UPromoted k dom stage) Source # 
type Rep (UPromoted k dom stage) = D1 (MetaData "UPromoted" "Language.Haskell.Tools.AST.Representation.Kinds" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) ((:+:) (C1 (MetaCons "UPromotedInt" PrefixI True) (S1 (MetaSel (Just Symbol "_promotedIntValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer))) ((:+:) (C1 (MetaCons "UPromotedString" PrefixI True) (S1 (MetaSel (Just Symbol "_promotedStringValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) (C1 (MetaCons "UPromotedCon" PrefixI True) (S1 (MetaSel (Just Symbol "_promotedConName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UName dom stage)))))) ((:+:) (C1 (MetaCons "UPromotedList" PrefixI True) (S1 (MetaSel (Just Symbol "_promotedElements") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG k dom stage)))) ((:+:) (C1 (MetaCons "UPromotedTuple" PrefixI True) (S1 (MetaSel (Just Symbol "_promotedElements") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG k dom stage)))) (C1 (MetaCons "UPromotedUnit" PrefixI False) U1))))

data ULiteral dom stage Source #

Haskell literals

Constructors

UCharLit

Character literal: c

Fields

UStringLit

String literal: "abc"

UIntLit

Integer literal: 12

UFracLit

Fractional literal: 3.14

UPrimIntLit

Primitive integer literal (of type Int#): 32#

UPrimWordLit

Primitive word literal (of type Word#): 32##

UPrimFloatLit

Primitive float literal (of type Float#): 3.14#

UPrimDoubleLit

Primitive double literal (of type Double#): 3.14##

UPrimCharLit

Primitive character literal (of type Char#): c#

Fields

UPrimStringLit

Primitive string literal (of type Addr#): "xxx"#

Instances

type Rep (ULiteral dom stage) Source # 
type Rep (ULiteral dom stage) = D1 (MetaData "ULiteral" "Language.Haskell.Tools.AST.Representation.Literals" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "UCharLit" PrefixI True) (S1 (MetaSel (Just Symbol "_charLitValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Char))) (C1 (MetaCons "UStringLit" PrefixI True) (S1 (MetaSel (Just Symbol "_stringLitValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) ((:+:) (C1 (MetaCons "UIntLit" PrefixI True) (S1 (MetaSel (Just Symbol "_intLitValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer))) ((:+:) (C1 (MetaCons "UFracLit" PrefixI True) (S1 (MetaSel (Just Symbol "_fracLitValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Rational))) (C1 (MetaCons "UPrimIntLit" PrefixI True) (S1 (MetaSel (Just Symbol "_intLitValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)))))) ((:+:) ((:+:) (C1 (MetaCons "UPrimWordLit" PrefixI True) (S1 (MetaSel (Just Symbol "_intLitValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer))) (C1 (MetaCons "UPrimFloatLit" PrefixI True) (S1 (MetaSel (Just Symbol "_floatLitValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Rational)))) ((:+:) (C1 (MetaCons "UPrimDoubleLit" PrefixI True) (S1 (MetaSel (Just Symbol "_floatLitValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Rational))) ((:+:) (C1 (MetaCons "UPrimCharLit" PrefixI True) (S1 (MetaSel (Just Symbol "_charLitValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Char))) (C1 (MetaCons "UPrimStringLit" PrefixI True) (S1 (MetaSel (Just Symbol "_stringLitValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))))))

data UOperator dom stage Source #

Constructors

UBacktickOp

A normal name used as an operator with backticks: a mod b

Fields

UNormalOp

A normal operator used as an operator.

Fields

Instances

type Rep (UOperator dom stage) Source # 
type Rep (UOperator dom stage) = D1 (MetaData "UOperator" "Language.Haskell.Tools.AST.Representation.Names" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "UBacktickOp" PrefixI True) (S1 (MetaSel (Just Symbol "_operatorName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UQualifiedName dom stage)))) (C1 (MetaCons "UNormalOp" PrefixI True) (S1 (MetaSel (Just Symbol "_operatorName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UQualifiedName dom stage)))))

data UName dom stage Source #

Constructors

UParenName

Parenthesized name: foldl (+) 0

Fields

UNormalName

A normal, non-operator name.

Fields

UImplicitName

Implicit name: ?var

Fields

Instances

type Rep (UName dom stage) Source # 
type Rep (UName dom stage) = D1 (MetaData "UName" "Language.Haskell.Tools.AST.Representation.Names" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) ((:+:) (C1 (MetaCons "UParenName" PrefixI True) (S1 (MetaSel (Just Symbol "_simpleName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UQualifiedName dom stage)))) ((:+:) (C1 (MetaCons "UNormalName" PrefixI True) (S1 (MetaSel (Just Symbol "_simpleName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UQualifiedName dom stage)))) (C1 (MetaCons "UImplicitName" PrefixI True) (S1 (MetaSel (Just Symbol "_simpleName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UQualifiedName dom stage))))))

data UQualifiedName dom stage Source #

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

Constructors

UQualifiedName 

Fields

Instances

HasDefiningInfo dom => HasDefiningInfo' (Ann UQualifiedName dom st) Source # 
HasScopeInfo dom => HasScopeInfo' (Ann UQualifiedName dom st) Source # 
HasFixityInfo dom => HasFixityInfo' (Ann UQualifiedName dom st) Source # 
HasIdInfo dom => HasIdInfo' (Ann UQualifiedName dom st) Source # 

Methods

semanticsId :: Ann UQualifiedName dom st -> Id Source #

HasNameInfo dom => HasNameInfo' (Ann UQualifiedName dom st) Source # 
type Rep (UQualifiedName dom stage) Source # 
type Rep (UQualifiedName dom stage) = D1 (MetaData "UQualifiedName" "Language.Haskell.Tools.AST.Representation.Names" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UQualifiedName" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_qualifiers") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnListG UNamePart dom stage))) (S1 (MetaSel (Just Symbol "_unqualifiedName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann UNamePart dom stage)))))

data UNamePart dom stage Source #

Parts of a qualified name.

Constructors

UNamePart 

Instances

type Rep (UNamePart dom stage) Source # 
type Rep (UNamePart dom stage) = D1 (MetaData "UNamePart" "Language.Haskell.Tools.AST.Representation.Names" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UNamePart" PrefixI True) (S1 (MetaSel (Just Symbol "_simpleNameStr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))

data UStringNode dom stage Source #

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

Constructors

UStringNode 

Instances

type Rep (UStringNode dom stage) Source # 
type Rep (UStringNode dom stage) = D1 (MetaData "UStringNode" "Language.Haskell.Tools.AST.Representation.Names" "haskell-tools-ast-0.9.0.0-uQcvnXetRULGIWJQydNPz" False) (C1 (MetaCons "UStringNode" PrefixI True) (S1 (MetaSel (Just Symbol "_stringNodeStr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))