Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module contains the ast node data types. They are very permissive, in that they allow a lot of invalid SQL to be represented. The type checking process should catch all invalid trees, but doesn't quite manage at the moment. Sorry about all the seemingly pointless type synonyms below, they are an artefact of using UUAGC. You can see labels for the fields by looking at the ag source here: http://jakewheat.github.com/hssqlppp/source/src/Database/HsSqlPpp/Internals/AstInternal.ag.html
- type StatementList = [Statement]
- data Statement
- = AlterSequence Annotation Name Name
- | AlterTable Annotation Name AlterTableActionList
- | AntiStatement String
- | Assignment Annotation Name ScalarExpr
- | Block Annotation (Maybe String) VarDefList StatementList
- | CaseStatement Annotation ScalarExprListStatementListPairList StatementList
- | CaseStatementSimple Annotation ScalarExpr ScalarExprListStatementListPairList StatementList
- | ContinueStatement Annotation (Maybe String)
- | Copy Annotation Name [NameComponent] CopySource
- | CopyData Annotation String
- | CreateDomain Annotation Name TypeName String MaybeBoolExpr
- | CreateFunction Annotation Name ParamDefList TypeName Replace Language FnBody Volatility
- | CreateLanguage Annotation String
- | CreateSequence Annotation Name Integer Integer Integer Integer Integer
- | CreateTable Annotation Name AttributeDefList ConstraintList
- | CreateTableAs Annotation Name QueryExpr
- | CreateTrigger Annotation NameComponent TriggerWhen [TriggerEvent] Name TriggerFire Name ScalarExprList
- | CreateType Annotation Name TypeAttributeDefList
- | CreateView Annotation Name MaybeNameComponentList QueryExpr
- | Delete Annotation Name TableRefList MaybeBoolExpr MaybeSelectList
- | DropFunction Annotation IfExists NameTypeNameListPairList Cascade
- | DropSomething Annotation DropType IfExists [Name] Cascade
- | Execute Annotation ScalarExpr
- | ExitStatement Annotation (Maybe String)
- | ForIntegerStatement Annotation (Maybe String) NameComponent ScalarExpr ScalarExpr StatementList
- | ForQueryStatement Annotation (Maybe String) NameComponent QueryExpr StatementList
- | If Annotation ScalarExprStatementListPairList StatementList
- | Insert Annotation Name [NameComponent] QueryExpr MaybeSelectList
- | Into Annotation Bool [Name] Statement
- | LoopStatement Annotation (Maybe String) StatementList
- | Notify Annotation String
- | NullStatement Annotation
- | Perform Annotation ScalarExpr
- | QueryStatement Annotation QueryExpr
- | Raise Annotation RaiseType String ScalarExprList
- | Return Annotation MaybeScalarExpr
- | ReturnNext Annotation ScalarExpr
- | ReturnQuery Annotation QueryExpr
- | Set Annotation String [SetValue]
- | Truncate Annotation [Name] RestartIdentity Cascade
- | Update Annotation Name SetClauseList TableRefList MaybeBoolExpr MaybeSelectList
- | WhileStatement Annotation (Maybe String) ScalarExpr StatementList
- data ScalarExpr
- = AggregateFn Annotation Distinct ScalarExpr ScalarExprDirectionPairList
- | AntiScalarExpr String
- | BooleanLit Annotation Bool
- | Case Annotation CaseScalarExprListScalarExprPairList MaybeScalarExpr
- | CaseSimple Annotation ScalarExpr CaseScalarExprListScalarExprPairList MaybeScalarExpr
- | Cast Annotation ScalarExpr TypeName
- | Exists Annotation QueryExpr
- | Extract Annotation ExtractField ScalarExpr
- | FunCall Annotation Name ScalarExprList
- | Identifier Annotation NameComponent
- | InPredicate Annotation ScalarExpr Bool InList
- | Interval Annotation String IntervalField (Maybe Int)
- | LiftOperator Annotation String LiftFlavour ScalarExprList
- | NullLit Annotation
- | NumberLit Annotation String
- | Placeholder Annotation
- | PositionalArg Annotation Integer
- | QIdentifier Annotation [NameComponent]
- | QStar Annotation NameComponent
- | ScalarSubQuery Annotation QueryExpr
- | Star Annotation
- | StringLit Annotation String
- | TypedStringLit Annotation TypeName String
- | WindowFn Annotation ScalarExpr ScalarExprList ScalarExprDirectionPairList FrameClause
- data QueryExpr
- = CombineQueryExpr Annotation CombineType QueryExpr QueryExpr
- | Select Annotation Distinct SelectList TableRefList MaybeBoolExpr ScalarExprList MaybeBoolExpr ScalarExprDirectionPairList MaybeScalarExpr MaybeScalarExpr
- | Values Annotation ScalarExprListList
- | WithQueryExpr Annotation WithQueryList QueryExpr
- data SelectList = SelectList Annotation SelectItemList
- data SelectItem
- data TableRef
- data TableAlias
- data JoinExpr
- data JoinType
- = Inner
- | LeftOuter
- | RightOuter
- | FullOuter
- | Cross
- data Natural
- data CombineType
- data Direction
- data Distinct
- data InList
- data LiftFlavour
- data FrameClause
- type WithQueryList = [WithQuery]
- data WithQuery = WithQuery Annotation NameComponent (Maybe [NameComponent]) QueryExpr
- data IntervalField
- data ExtractField
- = ExtractCentury
- | ExtractDay
- | ExtractDecade
- | ExtractDow
- | ExtractDoy
- | ExtractEpoch
- | ExtractHour
- | ExtractIsodow
- | ExtractIsoyear
- | ExtractMicroseconds
- | ExtractMillennium
- | ExtractMilliseconds
- | ExtractMinute
- | ExtractMonth
- | ExtractQuarter
- | ExtractSecond
- | ExtractTimezone
- | ExtractTimezoneHour
- | ExtractTimezoneMinute
- | ExtractWeek
- | ExtractYear
- data Name = Name Annotation [NameComponent]
- data NameComponent
- ncStr :: NameComponent -> String
- data CopySource
- data RestartIdentity
- data SetClause
- data AttributeDef = AttributeDef Annotation NameComponent TypeName MaybeScalarExpr RowConstraintList
- data RowConstraint
- data Constraint
- data AlterTableAction
- data TypeAttributeDef = TypeAttDef Annotation NameComponent TypeName
- data TypeName
- data DropType
- data IfExists
- data Replace
- data Cascade
- data TriggerWhen
- data TriggerEvent
- data TriggerFire
- data FnBody
- data ParamDef
- data VarDef
- data RaiseType
- = RNotice
- | RException
- | RError
- data Volatility
- data Language
- data SetValue
- type ScalarExprListStatementListPairList = [ScalarExprListStatementListPair]
- type ScalarExprListStatementListPair = (ScalarExprList, StatementList)
- type ScalarExprList = [ScalarExpr]
- type MaybeSelectList = Maybe SelectList
- type ParamDefList = [ParamDef]
- type AttributeDefList = [AttributeDef]
- type ConstraintList = [Constraint]
- type TypeAttributeDefList = [TypeAttributeDef]
- type TypeNameList = [TypeName]
- type NameTypeNameListPair = (Name, TypeNameList)
- type NameTypeNameListPairList = [NameTypeNameListPair]
- type ScalarExprStatementListPairList = [ScalarExprStatementListPair]
- type CaseScalarExprListScalarExprPairList = [CaseScalarExprListScalarExprPair]
- type MaybeScalarExpr = Maybe ScalarExpr
- type MaybeBoolExpr = Maybe ScalarExpr
- type TableRefList = [TableRef]
- type ScalarExprListList = [ScalarExprList]
- type SelectItemList = [SelectItem]
- type OnExpr = Maybe JoinExpr
- type RowConstraintList = [RowConstraint]
- type VarDefList = [VarDef]
- type ScalarExprStatementListPair = (ScalarExpr, StatementList)
- type CaseScalarExprListScalarExprPair = (ScalarExprList, ScalarExpr)
- type ScalarExprDirectionPair = (ScalarExpr, Direction)
- type ScalarExprDirectionPairList = [ScalarExprDirectionPair]
- type AlterTableActionList = [AlterTableAction]
- type SetClauseList = [SetClause]
Main nodes
type StatementList = [Statement] Source
data ScalarExpr Source
Components
Selects
data SelectList Source
data SelectItem Source
data TableAlias Source
data CombineType Source
data LiftFlavour Source
data FrameClause Source
type WithQueryList = [WithQuery] Source
data IntervalField Source
data ExtractField Source
data NameComponent Source
ncStr :: NameComponent -> String Source
dml
data CopySource Source
data RestartIdentity Source
ddl
data AttributeDef Source
data RowConstraint Source
data Constraint Source
data AlterTableAction Source
data TypeAttributeDef Source
data TriggerWhen Source
data TriggerEvent Source
data TriggerFire Source
functions
data Volatility Source
misc
typedefs
type ScalarExprList = [ScalarExpr] Source
type MaybeSelectList = Maybe SelectList Source
type ParamDefList = [ParamDef] Source
type AttributeDefList = [AttributeDef] Source
type ConstraintList = [Constraint] Source
type TypeAttributeDefList = [TypeAttributeDef] Source
type TypeNameList = [TypeName] Source
type NameTypeNameListPair = (Name, TypeNameList) Source
type MaybeScalarExpr = Maybe ScalarExpr Source
type MaybeBoolExpr = Maybe ScalarExpr Source
type TableRefList = [TableRef] Source
type ScalarExprListList = [ScalarExprList] Source
type SelectItemList = [SelectItem] Source
type RowConstraintList = [RowConstraint] Source
type VarDefList = [VarDef] Source
type ScalarExprDirectionPair = (ScalarExpr, Direction) Source
type AlterTableActionList = [AlterTableAction] Source
type SetClauseList = [SetClause] Source