Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
The AST for SQL queries.
- data ValueExpr
- = NumLit String
- | StringLit String
- | IntervalLit { }
- | Iden [Name]
- | Star
- | App [Name] [ValueExpr]
- | AggregateApp {
- aggName :: [Name]
- aggDistinct :: SetQuantifier
- aggArgs :: [ValueExpr]
- aggOrderBy :: [SortSpec]
- aggFilter :: Maybe ValueExpr
- | AggregateAppGroup { }
- | WindowApp { }
- | BinOp ValueExpr [Name] ValueExpr
- | PrefixOp [Name] ValueExpr
- | PostfixOp [Name] ValueExpr
- | SpecialOp [Name] [ValueExpr]
- | SpecialOpK [Name] (Maybe ValueExpr) [(String, ValueExpr)]
- | Case { }
- | Parens ValueExpr
- | Cast ValueExpr TypeName
- | TypedLit TypeName String
- | SubQueryExpr SubQueryExprType QueryExpr
- | In Bool ValueExpr InPredValue
- | Parameter
- | HostParameter String (Maybe String)
- | QuantifiedComparison ValueExpr [Name] CompPredQuantifier QueryExpr
- | Match ValueExpr Bool QueryExpr
- | Array ValueExpr [ValueExpr]
- | ArrayCtor QueryExpr
- | CSStringLit String String
- | Escape ValueExpr Char
- | UEscape ValueExpr Char
- | Collate ValueExpr [Name]
- | MultisetBinOp ValueExpr CombineOp SetQuantifier ValueExpr
- | MultisetCtor [ValueExpr]
- | MultisetQueryCtor QueryExpr
- | NextValueFor [Name]
- | VEComment [Comment] ValueExpr
- data Name
- data TypeName
- = TypeName [Name]
- | PrecTypeName [Name] Integer
- | PrecScaleTypeName [Name] Integer Integer
- | PrecLengthTypeName [Name] Integer (Maybe PrecMultiplier) (Maybe PrecUnits)
- | CharTypeName [Name] (Maybe Integer) [Name] [Name]
- | TimeTypeName [Name] (Maybe Integer) Bool
- | RowTypeName [(Name, TypeName)]
- | IntervalTypeName IntervalTypeField (Maybe IntervalTypeField)
- | ArrayTypeName TypeName (Maybe Integer)
- | MultisetTypeName TypeName
- data IntervalTypeField = Itf String (Maybe (Integer, Maybe Integer))
- data PrecMultiplier
- data PrecUnits
- data SetQuantifier
- data SortSpec = SortSpec ValueExpr Direction NullsOrder
- data Direction
- = DirDefault
- | Asc
- | Desc
- data NullsOrder
- data InPredValue
- data SubQueryExprType
- data CompPredQuantifier
- data Frame
- data FrameRows
- data FramePos
- data QueryExpr
- = Select {
- qeSetQuantifier :: SetQuantifier
- qeSelectList :: [(ValueExpr, Maybe Name)]
- qeFrom :: [TableRef]
- qeWhere :: Maybe ValueExpr
- qeGroupBy :: [GroupingExpr]
- qeHaving :: Maybe ValueExpr
- qeOrderBy :: [SortSpec]
- qeOffset :: Maybe ValueExpr
- qeFetchFirst :: Maybe ValueExpr
- | CombineQueryExpr { }
- | With {
- qeWithRecursive :: Bool
- qeViews :: [(Alias, QueryExpr)]
- qeQueryExpression :: QueryExpr
- | Values [[ValueExpr]]
- | Table [Name]
- | QEComment [Comment] QueryExpr
- = Select {
- makeSelect :: QueryExpr
- data CombineOp
- data Corresponding
- data Alias = Alias Name (Maybe [Name])
- data GroupingExpr
- data TableRef
- data JoinType
- data JoinCondition
- data Dialect
- data Comment = BlockComment String
Value expressions
Represents a value expression. This is used for the expressions in select lists. It is also used for expressions in where, group by, having, order by and so on.
NumLit String | a numeric literal optional decimal point, e+- integral exponent, e.g
|
StringLit String | string literal, currently only basic strings between single quotes with a single quote escaped using '' |
IntervalLit | text of interval literal, units of interval precision, e.g. interval 3 days (3) |
| |
Iden [Name] | identifier with parts separated by dots |
Star | star, as in select *, t.*, count(*) |
App [Name] [ValueExpr] | function application (anything that looks like c style function application syntactically) |
AggregateApp | aggregate application, which adds distinct or all, and order by, to regular function application |
| |
AggregateAppGroup | aggregates with within group |
WindowApp | window application, which adds over (partition by a order by b) to regular function application. Explicit frames are not currently supported |
BinOp ValueExpr [Name] ValueExpr | Infix binary operators. This is used for symbol operators (a + b), keyword operators (a and b) and multiple keyword operators (a is similar to b) |
PrefixOp [Name] ValueExpr | Prefix unary operators. This is used for symbol operators, keyword operators and multiple keyword operators. |
PostfixOp [Name] ValueExpr | Postfix unary operators. This is used for symbol operators, keyword operators and multiple keyword operators. |
SpecialOp [Name] [ValueExpr] | Used for ternary, mixfix and other non orthodox operators. Currently used for row constructors, and for between. |
SpecialOpK [Name] (Maybe ValueExpr) [(String, ValueExpr)] | Used for the operators which look like functions except the arguments are separated by keywords instead of commas. The maybe is for the first unnamed argument if it is present, and the list is for the keyword argument pairs. |
Case | case expression. both flavours supported |
Parens ValueExpr | |
Cast ValueExpr TypeName | cast(a as typename) |
TypedLit TypeName String | prefix 'typed literal', e.g. int '42' |
SubQueryExpr SubQueryExprType QueryExpr | exists, all, any, some subqueries |
In Bool ValueExpr InPredValue | in list literal and in subquery, if the bool is false it means not in was used ('a not in (1,2)') |
Parameter | Represents a ? in a parameterized query |
HostParameter String (Maybe String) | represents a host parameter, e.g. :a. The Maybe String is for the indicator, e.g. :var indicator :nl |
QuantifiedComparison ValueExpr [Name] CompPredQuantifier QueryExpr | |
Match ValueExpr Bool QueryExpr | |
Array ValueExpr [ValueExpr] | represents an array access expression, or an array ctor e.g. a[3]. The first valueExpr is the array, the second is the subscripts/ctor args |
ArrayCtor QueryExpr | this is used for the query expression version of array constructors, e.g. array(select * from t) |
CSStringLit String String | |
Escape ValueExpr Char | |
UEscape ValueExpr Char | |
Collate ValueExpr [Name] | |
MultisetBinOp ValueExpr CombineOp SetQuantifier ValueExpr | |
MultisetCtor [ValueExpr] | |
MultisetQueryCtor QueryExpr | |
NextValueFor [Name] | |
VEComment [Comment] ValueExpr |
Represents an identifier name, which can be quoted or unquoted.
Represents a type name, used in casts.
data IntervalTypeField Source #
data PrecMultiplier Source #
data SetQuantifier Source #
Represents the Distinct or All keywords, which can be used before a select list, in an aggregate/window function application, or in a query expression set operator.
Represents one field in an order by list.
The direction for a column in order by.
data NullsOrder Source #
Represents 'nulls first' or 'nulls last' in an order by clause.
data InPredValue Source #
Used for 'expr in (value expression list)', and 'expr in (subquery)' syntax.
data SubQueryExprType Source #
A subquery in a value expression.
data CompPredQuantifier Source #
Represents the frame clause of a window this can be [range | rows] frame_start or [range | rows] between frame_start and frame_end
Represents whether a window frame clause is over rows or ranges.
represents the start or end of a frame
Query expressions
Represents a query expression, which can be:
- a regular select;
- a set operator (union, except, intersect);
- a common table expression (with);
- a table value constructor (values (1,2),(3,4)); or
- an explicit table (table t).
Select | |
| |
CombineQueryExpr | |
With | |
| |
Values [[ValueExpr]] | |
Table [Name] | |
QEComment [Comment] QueryExpr |
makeSelect :: QueryExpr Source #
Helper/'default' value for query exprs to make creating query expr values a little easier. It is defined like this:
makeSelect :: QueryExpr makeSelect = Select {qeSetQuantifier = SQDefault ,qeSelectList = [] ,qeFrom = [] ,qeWhere = Nothing ,qeGroupBy = [] ,qeHaving = Nothing ,qeOrderBy = [] ,qeOffset = Nothing ,qeFetchFirst = Nothing}
Query expression set operators.
data Corresponding Source #
Corresponding, an option for the set operators.
Represents an alias for a table valued expression, used in with queries and in from alias, e.g. select a from t u, select a from t u(b), with a(c) as select 1, select * from a.
data GroupingExpr Source #
Represents an item in a group by clause.
From
Represents a entry in the csv of tables in the from clause.
TRSimple [Name] | from t / from s.t |
TRJoin TableRef Bool JoinType TableRef (Maybe JoinCondition) | from a join b, the bool is true if natural was used |
TRParens TableRef | from (a) |
TRAlias TableRef Alias | from a as b(c,d) |
TRQueryExpr QueryExpr | from (query expr) |
TRFunction [Name] [ValueExpr] | from function(args) |
TRLateral TableRef | from lateral t |
The type of a join.
data JoinCondition Source #
The join condition.
dialect
Used to set the dialect used for parsing and pretty printing, very unfinished at the moment.