hssqlppp-0.0.6: Sql parser and type checkerSource codeContentsIndex
Database.HsSqlPpp.TypeChecking.Ast
Contents
Main nodes
Components
Selects
dml
ddl
functions
typedefs
operator utils
type aliases
Description
This module contains the ast node data types.
Synopsis
type StatementList = [Statement]
data Statement
= Assignment Annotation String Expression
| CaseStatement Annotation Expression ExpressionListStatementListPairList StatementList
| ContinueStatement Annotation
| Copy Annotation String StringList CopySource
| CopyData Annotation String
| CreateDomain Annotation String TypeName (Maybe Expression)
| CreateFunction Annotation Language String ParamDefList TypeName String FnBody Volatility
| CreateTable Annotation String AttributeDefList ConstraintList
| CreateTableAs Annotation String SelectExpression
| CreateType Annotation String TypeAttributeDefList
| CreateView Annotation String SelectExpression
| Delete Annotation String Where (Maybe SelectList)
| DropFunction Annotation IfExists StringStringListPairList Cascade
| DropSomething Annotation DropType IfExists StringList Cascade
| Execute Annotation Expression
| ExecuteInto Annotation Expression StringList
| ForIntegerStatement Annotation String Expression Expression StatementList
| ForSelectStatement Annotation String SelectExpression StatementList
| If Annotation ExpressionStatementListPairList StatementList
| Insert Annotation String StringList SelectExpression (Maybe SelectList)
| NullStatement Annotation
| Perform Annotation Expression
| Raise Annotation RaiseType String ExpressionList
| Return Annotation (Maybe Expression)
| ReturnNext Annotation Expression
| ReturnQuery Annotation SelectExpression
| SelectStatement Annotation SelectExpression
| Truncate Annotation StringList RestartIdentity Cascade
| Update Annotation String SetClauseList Where (Maybe SelectList)
| WhileStatement Annotation Expression StatementList
data Expression
= BooleanLit Annotation Bool
| Case Annotation CaseExpressionListExpressionPairList MaybeExpression
| CaseSimple Annotation Expression CaseExpressionListExpressionPairList MaybeExpression
| Cast Annotation Expression TypeName
| Exists Annotation SelectExpression
| FloatLit Annotation Double
| FunCall Annotation String ExpressionList
| Identifier Annotation String
| InPredicate Annotation Expression Bool InList
| IntegerLit Annotation Integer
| NullLit Annotation
| PositionalArg Annotation Integer
| ScalarSubQuery Annotation SelectExpression
| StringLit Annotation String String
| WindowFn Annotation Expression ExpressionList ExpressionList Direction
data SelectExpression
= CombineSelect Annotation CombineType SelectExpression SelectExpression
| Select Annotation Distinct SelectList MTableRef Where ExpressionList MExpression ExpressionList Direction MExpression MExpression
| Values Annotation ExpressionListList
data SelectList = SelectList SelectItemList StringList
data SelectItem
= SelExp Expression
| SelectItem Expression String
data TableRef
= JoinedTref Annotation TableRef Natural JoinType TableRef OnExpr
| SubTref Annotation SelectExpression String
| Tref Annotation String
| TrefAlias Annotation String String
| TrefFun Annotation Expression
| TrefFunAlias Annotation Expression String
data JoinExpression
= JoinOn Expression
| JoinUsing StringList
data JoinType
= Cross
| FullOuter
| Inner
| LeftOuter
| RightOuter
data Natural
= Natural
| Unnatural
data CombineType
= Except
| Intersect
| Union
| UnionAll
data Direction
= Asc
| Desc
data Distinct
= Distinct
| Dupes
data InList
= InList ExpressionList
| InSelect SelectExpression
data SetClause
= RowSetClause StringList ExpressionList
| SetClause String Expression
data CopySource
= CopyFilename String
| Stdin
data RestartIdentity
= ContinueIdentity
| RestartIdentity
data AttributeDef = AttributeDef String TypeName (Maybe Expression) RowConstraintList
data RowConstraint
= NotNullConstraint
| NullConstraint
| RowCheckConstraint Expression
| RowPrimaryKeyConstraint
| RowReferenceConstraint String (Maybe String) Cascade Cascade
| RowUniqueConstraint
data Constraint
= CheckConstraint Expression
| PrimaryKeyConstraint StringList
| ReferenceConstraint StringList String StringList Cascade Cascade
| UniqueConstraint StringList
data TypeAttributeDef = TypeAttDef String TypeName
data TypeName
= ArrayTypeName TypeName
| PrecTypeName String Integer
| SetOfTypeName TypeName
| SimpleTypeName String
data DropType
= Domain
| Table
| Type
| View
data IfExists
= IfExists
| Require
data Cascade
= Cascade
| Restrict
data FnBody
= PlpgsqlFnBody VarDefList StatementList
| SqlFnBody StatementList
data ParamDef
= ParamDef String TypeName
| ParamDefTp TypeName
data VarDef = VarDef String TypeName (Maybe Expression)
data RaiseType
= RError
| RException
| RNotice
data Volatility
= Immutable
| Stable
| Volatile
data Language
= Plpgsql
| Sql
type ExpressionListStatementListPairList = [ExpressionListStatementListPair]
type ExpressionListStatementListPair = (ExpressionList, StatementList)
type ExpressionList = [Expression]
type StringList = [String]
type ParamDefList = [ParamDef]
type AttributeDefList = [AttributeDef]
type ConstraintList = [Constraint]
type TypeAttributeDefList = [TypeAttributeDef]
type Where = Maybe Expression
type StringStringListPairList = [StringStringListPair]
type StringStringListPair = (String, StringList)
type ExpressionStatementListPairList = [ExpressionStatementListPair]
type SetClauseList = [SetClause]
type CaseExpressionListExpressionPairList = [CaseExpressionListExpressionPair]
type MaybeExpression = Maybe Expression
type MTableRef = Maybe TableRef
type ExpressionListList = [ExpressionList]
type SelectItemList = [SelectItem]
type OnExpr = Maybe JoinExpression
type RowConstraintList = [RowConstraint]
type VarDefList = [VarDef]
type ExpressionStatementListPair = (Expression, StatementList)
type MExpression = Maybe Expression
type CaseExpressionListExpressionPair = (CaseExpressionList, Expression)
type CaseExpressionList = [Expression]
data OperatorType
= BinaryOp
| PrefixOp
| PostfixOp
getOperatorType :: String -> OperatorType
typeSmallInt :: Type
typeBigInt :: Type
typeInt :: Type
typeNumeric :: Type
typeFloat4 :: Type
typeFloat8 :: Type
typeVarChar :: Type
typeChar :: Type
typeBool :: Type
Main nodes
type StatementList = [Statement]Source
data Statement Source
Constructors
Assignment Annotation String Expression
CaseStatement Annotation Expression ExpressionListStatementListPairList StatementList
ContinueStatement Annotation
Copy Annotation String StringList CopySource
CopyData Annotation String
CreateDomain Annotation String TypeName (Maybe Expression)
CreateFunction Annotation Language String ParamDefList TypeName String FnBody Volatility
CreateTable Annotation String AttributeDefList ConstraintList
CreateTableAs Annotation String SelectExpression
CreateType Annotation String TypeAttributeDefList
CreateView Annotation String SelectExpression
Delete Annotation String Where (Maybe SelectList)
DropFunction Annotation IfExists StringStringListPairList Cascade
DropSomething Annotation DropType IfExists StringList Cascade
Execute Annotation Expression
ExecuteInto Annotation Expression StringList
ForIntegerStatement Annotation String Expression Expression StatementList
ForSelectStatement Annotation String SelectExpression StatementList
If Annotation ExpressionStatementListPairList StatementList
Insert Annotation String StringList SelectExpression (Maybe SelectList)
NullStatement Annotation
Perform Annotation Expression
Raise Annotation RaiseType String ExpressionList
Return Annotation (Maybe Expression)
ReturnNext Annotation Expression
ReturnQuery Annotation SelectExpression
SelectStatement Annotation SelectExpression
Truncate Annotation StringList RestartIdentity Cascade
Update Annotation String SetClauseList Where (Maybe SelectList)
WhileStatement Annotation Expression StatementList
show/hide Instances
data Expression Source
Constructors
BooleanLit Annotation Bool
Case Annotation CaseExpressionListExpressionPairList MaybeExpression
CaseSimple Annotation Expression CaseExpressionListExpressionPairList MaybeExpression
Cast Annotation Expression TypeName
Exists Annotation SelectExpression
FloatLit Annotation Double
FunCall Annotation String ExpressionList
Identifier Annotation String
InPredicate Annotation Expression Bool InList
IntegerLit Annotation Integer
NullLit Annotation
PositionalArg Annotation Integer
ScalarSubQuery Annotation SelectExpression
StringLit Annotation String String
WindowFn Annotation Expression ExpressionList ExpressionList Direction
show/hide Instances
data SelectExpression Source
Constructors
CombineSelect Annotation CombineType SelectExpression SelectExpression
Select Annotation Distinct SelectList MTableRef Where ExpressionList MExpression ExpressionList Direction MExpression MExpression
Values Annotation ExpressionListList
show/hide Instances
Components
Selects
data SelectList Source
Constructors
SelectList SelectItemList StringList
show/hide Instances
data SelectItem Source
Constructors
SelExp Expression
SelectItem Expression String
show/hide Instances
data TableRef Source
Constructors
JoinedTref Annotation TableRef Natural JoinType TableRef OnExpr
SubTref Annotation SelectExpression String
Tref Annotation String
TrefAlias Annotation String String
TrefFun Annotation Expression
TrefFunAlias Annotation Expression String
show/hide Instances
data JoinExpression Source
Constructors
JoinOn Expression
JoinUsing StringList
show/hide Instances
data JoinType Source
Constructors
Cross
FullOuter
Inner
LeftOuter
RightOuter
show/hide Instances
data Natural Source
Constructors
Natural
Unnatural
show/hide Instances
data CombineType Source
Constructors
Except
Intersect
Union
UnionAll
show/hide Instances
data Direction Source
Constructors
Asc
Desc
show/hide Instances
data Distinct Source
Constructors
Distinct
Dupes
show/hide Instances
data InList Source
Constructors
InList ExpressionList
InSelect SelectExpression
show/hide Instances
dml
data SetClause Source
Constructors
RowSetClause StringList ExpressionList
SetClause String Expression
show/hide Instances
data CopySource Source
Constructors
CopyFilename String
Stdin
show/hide Instances
data RestartIdentity Source
Constructors
ContinueIdentity
RestartIdentity
show/hide Instances
ddl
data AttributeDef Source
Constructors
AttributeDef String TypeName (Maybe Expression) RowConstraintList
show/hide Instances
data RowConstraint Source
Constructors
NotNullConstraint
NullConstraint
RowCheckConstraint Expression
RowPrimaryKeyConstraint
RowReferenceConstraint String (Maybe String) Cascade Cascade
RowUniqueConstraint
show/hide Instances
data Constraint Source
Constructors
CheckConstraint Expression
PrimaryKeyConstraint StringList
ReferenceConstraint StringList String StringList Cascade Cascade
UniqueConstraint StringList
show/hide Instances
data TypeAttributeDef Source
Constructors
TypeAttDef String TypeName
show/hide Instances
data TypeName Source
Constructors
ArrayTypeName TypeName
PrecTypeName String Integer
SetOfTypeName TypeName
SimpleTypeName String
show/hide Instances
data DropType Source
Constructors
Domain
Table
Type
View
show/hide Instances
data IfExists Source
Constructors
IfExists
Require
show/hide Instances
data Cascade Source
Constructors
Cascade
Restrict
show/hide Instances
functions
data FnBody Source
Constructors
PlpgsqlFnBody VarDefList StatementList
SqlFnBody StatementList
show/hide Instances
data ParamDef Source
Constructors
ParamDef String TypeName
ParamDefTp TypeName
show/hide Instances
data VarDef Source
Constructors
VarDef String TypeName (Maybe Expression)
show/hide Instances
data RaiseType Source
Constructors
RError
RException
RNotice
show/hide Instances
data Volatility Source
Constructors
Immutable
Stable
Volatile
show/hide Instances
data Language Source
Constructors
Plpgsql
Sql
show/hide Instances
typedefs
type ExpressionListStatementListPairList = [ExpressionListStatementListPair]Source
type ExpressionListStatementListPair = (ExpressionList, StatementList)Source
type ExpressionList = [Expression]Source
type StringList = [String]Source
type ParamDefList = [ParamDef]Source
type AttributeDefList = [AttributeDef]Source
type ConstraintList = [Constraint]Source
type TypeAttributeDefList = [TypeAttributeDef]Source
type Where = Maybe ExpressionSource
type StringStringListPairList = [StringStringListPair]Source
type StringStringListPair = (String, StringList)Source
type ExpressionStatementListPairList = [ExpressionStatementListPair]Source
type SetClauseList = [SetClause]Source
type CaseExpressionListExpressionPairList = [CaseExpressionListExpressionPair]Source
type MaybeExpression = Maybe ExpressionSource
type MTableRef = Maybe TableRefSource
type ExpressionListList = [ExpressionList]Source
type SelectItemList = [SelectItem]Source
type OnExpr = Maybe JoinExpressionSource
type RowConstraintList = [RowConstraint]Source
type VarDefList = [VarDef]Source
type ExpressionStatementListPair = (Expression, StatementList)Source
type MExpression = Maybe ExpressionSource
type CaseExpressionListExpressionPair = (CaseExpressionList, Expression)Source
type CaseExpressionList = [Expression]Source
operator utils
data OperatorType Source
Constructors
BinaryOp
PrefixOp
PostfixOp
show/hide Instances
getOperatorType :: String -> OperatorTypeSource
type aliases
aliases for all the sql types with multiple names these give you the canonical names
typeSmallInt :: TypeSource
typeBigInt :: TypeSource
typeInt :: TypeSource
typeNumeric :: TypeSource
typeFloat4 :: TypeSource
typeFloat8 :: TypeSource
typeVarChar :: TypeSource
typeChar :: TypeSource
typeBool :: TypeSource
Produced by Haddock version 2.6.0