>-- | The AST for SQL queries.>moduleLanguage.SQL.SimpleSQL.Syntax>(-- * Value expressions>ValueExpr(..)>,Name(..)>,TypeName(..)>,SetQuantifier(..)>,SortSpec(..)>,Direction(..)>,NullsOrder(..)>,InPredValue(..)>,SubQueryExprType(..)>,Frame(..)>,FrameRows(..)>,FramePos(..)>-- * Query expressions>,QueryExpr(..)>,makeSelect>,CombineOp(..)>,Corresponding(..)>,Alias(..)>,GroupingExpr(..)>-- ** From>,TableRef(..)>,JoinType(..)>,JoinCondition(..)>)where
>-- | 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.>dataValueExpr>=-- | a numeric literal optional decimal point, e+->-- integral exponent, e.g>-->-- * 10>-->-- * 10.>-->-- * .1>-->-- * 10.1>-->-- * 1e5>-->-- * 12.34e-6>NumLitString>-- | string literal, currently only basic strings between>-- single quotes with a single quote escaped using ''>|StringLitString>-- | text of interval literal, units of interval precision,>-- e.g. interval 3 days (3)>|IntervalLit>{ilLiteral::String-- ^ literal text>,ilUnits::String-- ^ units>,ilPrecision::MaybeInt-- ^ precision>}>-- | identifier without dots>|IdenName>-- | star, as in select *, t.*, count(*)>|Star>-- | function application (anything that looks like c style>-- function application syntactically)>|AppName[ValueExpr]>-- | aggregate application, which adds distinct or all, and>-- order by, to regular function application>|AggregateApp>{aggName::Name-- ^ aggregate function name>,aggDistinct::MaybeSetQuantifier-- ^ distinct>,aggArgs::[ValueExpr]-- ^ args>,aggOrderBy::[SortSpec]-- ^ order by>}>-- | window application, which adds over (partition by a order>-- by b) to regular function application. Explicit frames are>-- not currently supported>|WindowApp>{wnName::Name-- ^ window function name>,wnArgs::[ValueExpr]-- ^ args>,wnPartition::[ValueExpr]-- ^ partition by>,wnOrderBy::[SortSpec]-- ^ order by>,wnFrame::MaybeFrame-- ^ frame clause>}>-- | 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)>|BinOpValueExprNameValueExpr>-- | Prefix unary operators. This is used for symbol>-- operators, keyword operators and multiple keyword operators.>|PrefixOpNameValueExpr>-- | Postfix unary operators. This is used for symbol>-- operators, keyword operators and multiple keyword operators.>|PostfixOpNameValueExpr>-- | Used for ternary, mixfix and other non orthodox>-- operators. Currently used for row constructors, and for>-- between.>|SpecialOpName[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.>|SpecialOpKName(MaybeValueExpr)[(String,ValueExpr)]>-- | case expression. both flavours supported>|Case>{caseTest::MaybeValueExpr-- ^ test value>,caseWhens::[([ValueExpr],ValueExpr)]-- ^ when branches>,caseElse::MaybeValueExpr-- ^ else value>}>|ParensValueExpr>-- | cast(a as typename)>|CastValueExprTypeName>-- | prefix 'typed literal', e.g. int '42'>|TypedLitTypeNameString>-- | exists, all, any, some subqueries>|SubQueryExprSubQueryExprTypeQueryExpr>-- | in list literal and in subquery, if the bool is false it>-- means not in was used ('a not in (1,2)')>|InBoolValueExprInPredValue>|Parameter-- ^ Represents a ? in a parameterized query>deriving(Eq,Show,Read)
>-- | Represents an identifier name, which can be quoted or unquoted.>dataName=NameString>|QNameString>deriving(Eq,Show,Read)
>-- | Represents a type name, used in casts.>dataTypeName=TypeNameString>|PrecTypeNameStringInt>|PrecScaleTypeNameStringIntInt>deriving(Eq,Show,Read)
>-- | Used for 'expr in (value expression list)', and 'expr in>-- (subquery)' syntax.>dataInPredValue=InList[ValueExpr]>|InQueryExprQueryExpr>deriving(Eq,Show,Read)
>-- | A subquery in a value expression.>dataSubQueryExprType>=-- | exists (query expr)>SqExists>-- | a scalar subquery>|SqSq>-- | all (query expr)>|SqAll>-- | some (query expr)>|SqSome>-- | any (query expr)>|SqAny>deriving(Eq,Show,Read)
>-- | Represents one field in an order by list.>dataSortSpec=SortSpecValueExprDirectionNullsOrder>deriving(Eq,Show,Read)
>-- | Represents 'nulls first' or 'nulls last' in an order by clause.>dataNullsOrder=NullsOrderDefault>|NullsFirst>|NullsLast>deriving(Eq,Show,Read)
>-- | Represents the frame clause of a window>-- this can be [range | rows] frame_start>-- or [range | rows] between frame_start and frame_end>dataFrame=FrameFromFrameRowsFramePos>|FrameBetweenFrameRowsFramePosFramePos>deriving(Eq,Show,Read)
>-- | Represents whether a window frame clause is over rows or ranges.>dataFrameRows=FrameRows|FrameRange>deriving(Eq,Show,Read)
>-- | represents the start or end of a frame>dataFramePos=UnboundedPreceding>|PrecedingValueExpr>|Current>|FollowingValueExpr>|UnboundedFollowing>deriving(Eq,Show,Read)
>-- | 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).>dataQueryExpr>=Select>{qeSetQuantifier::SetQuantifier>,qeSelectList::[(ValueExpr,MaybeName)]>-- ^ the expressions and the column aliases
TODO: consider breaking this up. The SQL grammar has
queryexpr = select