Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
The AST for SQL queries.
- data ValueExpr
- = NumLit String
- | StringLit String
- | IntervalLit { }
- | Iden Name
- | Star
- | App Name [ValueExpr]
- | AggregateApp {
- aggName :: Name
- aggDistinct :: Maybe SetQuantifier
- aggArgs :: [ValueExpr]
- aggOrderBy :: [SortSpec]
- | 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
- data Name
- data TypeName
- data SetQuantifier
- data SortSpec = SortSpec ValueExpr Direction NullsOrder
- data Direction
- data NullsOrder
- data InPredValue
- data SubQueryExprType
- 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
- = Select {
- makeSelect :: QueryExpr
- data CombineOp
- data Corresponding
- data Alias = Alias Name (Maybe [Name])
- data GroupingExpr
- data TableRef
- data JoinType
- data JoinCondition
- = JoinOn ValueExpr
- | JoinUsing [Name]
- | JoinNatural
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 without 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 |
| |
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 |
Represents an identifier name, which can be quoted or unquoted.
Represents a type name, used in casts.
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.
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 |
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 = All ,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.
The type of a join.
data JoinCondition Source
The join condition.
JoinOn ValueExpr | on expr |
JoinUsing [Name] | using (column list) |
JoinNatural | natural join was used |