Safe Haskell | Safe-Inferred |
---|
Language.SQL.SimpleSQL.Syntax
Contents
Description
The AST for SQL queries.
- data ScalarExpr
- = NumLit String
- | StringLit String
- | IntervalLit { }
- | Iden Name
- | Star
- | App Name [ScalarExpr]
- | AggregateApp {
- aggName :: Name
- aggDistinct :: Maybe Duplicates
- aggArgs :: [ScalarExpr]
- aggOrderBy :: [OrderField]
- | WindowApp {
- wnName :: Name
- wnArgs :: [ScalarExpr]
- wnPartition :: [ScalarExpr]
- wnOrderBy :: [OrderField]
- wnFrame :: Maybe Frame
- | BinOp ScalarExpr Name ScalarExpr
- | PrefixOp Name ScalarExpr
- | PostfixOp Name ScalarExpr
- | SpecialOp Name [ScalarExpr]
- | Case {
- caseTest :: Maybe ScalarExpr
- caseWhens :: [([ScalarExpr], ScalarExpr)]
- caseElse :: Maybe ScalarExpr
- | Parens ScalarExpr
- | Cast ScalarExpr TypeName
- | TypedLit TypeName String
- | SubQueryExpr SubQueryExprType QueryExpr
- | In Bool ScalarExpr InThing
- data Name
- data TypeName
- data Duplicates
- data OrderField = OrderField ScalarExpr Direction NullsOrder
- data Direction
- data NullsOrder
- data InThing
- = InList [ScalarExpr]
- | InQueryExpr QueryExpr
- data SubQueryExprType
- data Frame
- data FrameRows
- = FrameRows
- | FrameRange
- data FramePos
- data QueryExpr
- = Select {
- qeDuplicates :: Duplicates
- qeSelectList :: [(Maybe Name, ScalarExpr)]
- qeFrom :: [TableRef]
- qeWhere :: Maybe ScalarExpr
- qeGroupBy :: [GroupingExpr]
- qeHaving :: Maybe ScalarExpr
- qeOrderBy :: [OrderField]
- qeOffset :: Maybe ScalarExpr
- qeFetch :: Maybe ScalarExpr
- | CombineQueryExpr { }
- | With {
- qeWithRecursive :: Bool
- qeViews :: [(Alias, QueryExpr)]
- qeQueryExpression :: QueryExpr
- | Values [[ScalarExpr]]
- | Table Name
- = Select {
- makeSelect :: QueryExpr
- data CombineOp
- data Corresponding
- data Alias = Alias Name (Maybe [Name])
- data GroupingExpr
- = GroupingParens [GroupingExpr]
- | Cube [GroupingExpr]
- | Rollup [GroupingExpr]
- | GroupingSets [GroupingExpr]
- | SimpleGroup ScalarExpr
- data TableRef
- data JoinType
- data JoinCondition
- = JoinOn ScalarExpr
- | JoinUsing [Name]
- | JoinNatural
Scalar expressions
data ScalarExpr Source
Represents a scalar expression.
Constructors
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 [ScalarExpr] | 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 |
Fields
| |
WindowApp | window application, which adds over (partition by a order by b) to regular function application. Explicit frames are not currently supported |
Fields
| |
BinOp ScalarExpr Name ScalarExpr | 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 ScalarExpr | Prefix unary operators. This is used for symbol operators, keyword operators and multiple keyword operators |
PostfixOp Name ScalarExpr | Postfix unary operators. This is used for symbol operators, keyword operators and multiple keyword operators |
SpecialOp Name [ScalarExpr] | Used for ternary, mixfix and other non orthodox operators, including the function looking calls which use keywords instead of commas to separate the arguments, e.g. substring(t from 1 to 5) |
Case | case expression. both flavours supported |
Fields
| |
Parens ScalarExpr | |
Cast ScalarExpr 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 ScalarExpr InThing | in list literal and in subquery, if the bool is false it means not in was used ('a not in (1,2)') |
Instances
Represents an identifier name, which can be quoted or unquoted.
Represents a type name, used in casts.
Constructors
TypeName String | |
PrecTypeName String Int | |
PrecScaleTypeName String Int Int |
data Duplicates 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.
Instances
data OrderField Source
Represents one field in an order by list.
Constructors
OrderField ScalarExpr Direction NullsOrder |
Instances
The direction for a column in order by.
data NullsOrder Source
Represents 'nulls first' or 'nulls last' in an order by clause.
Constructors
NullsOrderDefault | |
NullsFirst | |
NullsLast |
Instances
Used for 'expr in (scalar expression list)', and 'expr in (subquery)' syntax.
Constructors
InList [ScalarExpr] | |
InQueryExpr QueryExpr |
data SubQueryExprType Source
A subquery in a scalar 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.
Constructors
FrameRows | |
FrameRange |
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 values expression;
- or the table syntax - 'table t', shorthand for 'select * from t'.
Constructors
Select | |
Fields
| |
CombineQueryExpr | |
Fields
| |
With | |
Fields
| |
Values [[ScalarExpr]] | |
Table Name |
Helper/'default' value for query exprs to make creating query expr values a little easier.
Query expression set operators.
data Corresponding Source
Corresponding, an option for the set operators.
Constructors
Corresponding | |
Respectively |
Instances
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.
Constructors
GroupingParens [GroupingExpr] | |
Cube [GroupingExpr] | |
Rollup [GroupingExpr] | |
GroupingSets [GroupingExpr] | |
SimpleGroup ScalarExpr |
Instances
From
Represents a entry in the csv of tables in the from clause.
Constructors
TRSimple Name | from t |
TRJoin TableRef JoinType TableRef (Maybe JoinCondition) | from a join b |
TRParens TableRef | from (a) |
TRAlias TableRef Alias | from a as b(c,d) |
TRQueryExpr QueryExpr | from (query expr) |
TRFunction Name [ScalarExpr] | from function(args) |
TRLateral TableRef | from lateral t |
The type of a join.
data JoinCondition Source
The join condition.
Constructors
JoinOn ScalarExpr | on expr |
JoinUsing [Name] | using (column list) |
JoinNatural | natural join was used |
Instances