>-- | The AST for SQL queries.>{-# LANGUAGE DeriveDataTypeable #-}>moduleLanguage.SQL.SimpleSQL.Syntax>(-- * Value expressions>ValueExpr(..)>,Name(..)>,TypeName(..)>,IntervalTypeField(..)>,PrecMultiplier(..)>,PrecUnits(..)>,SetQuantifier(..)>,SortSpec(..)>,Direction(..)>,NullsOrder(..)>,InPredValue(..)>,SubQueryExprType(..)>,CompPredQuantifier(..)>,Frame(..)>,FrameRows(..)>,FramePos(..)>-- * Query expressions>,QueryExpr(..)>,makeSelect>,CombineOp(..)>,Corresponding(..)>,Alias(..)>,GroupingExpr(..)>-- ** From>,TableRef(..)>,JoinType(..)>,JoinCondition(..)>-- * dialect>,Dialect(..)>-- * comment>,Comment(..)>)where
>importData.Data
>-- | 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>{ilSign::MaybeBool-- ^ true if + used, false if - used>,ilLiteral::String-- ^ literal text>,ilFrom::IntervalTypeField>,ilTo::MaybeIntervalTypeField>}>-- | identifier with parts separated by dots>|Iden[Name]>-- | star, as in select *, t.*, count(*)>|Star>-- | function application (anything that looks like c style>-- function application syntactically)>|App[Name][ValueExpr]>-- | aggregate application, which adds distinct or all, and>-- order by, to regular function application>|AggregateApp>{aggName::[Name]-- ^ aggregate function name>,aggDistinct::SetQuantifier-- ^ distinct>,aggArgs::[ValueExpr]-- ^ args>,aggOrderBy::[SortSpec]-- ^ order by>,aggFilter::MaybeValueExpr-- ^ filter>}>-- | aggregates with within group>|AggregateAppGroup>{aggName::[Name]-- ^ aggregate function name>,aggArgs::[ValueExpr]-- ^ args>,aggGroup::[SortSpec]-- ^ within group>}>-- | 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)>|BinOpValueExpr[Name]ValueExpr>-- | Prefix unary operators. This is used for symbol>-- operators, keyword operators and multiple keyword operators.>|PrefixOp[Name]ValueExpr>-- | Postfix unary operators. This is used for symbol>-- operators, keyword operators and multiple keyword operators.>|PostfixOp[Name]ValueExpr>-- | Used for ternary, mixfix and other non orthodox>-- operators. Currently used for row constructors, and for>-- between.>|SpecialOp[Name][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.>|SpecialOpK[Name](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>|HostParameterString(MaybeString)-- ^ represents a host>-- parameter, e.g. :a. The>-- Maybe String is for the>-- indicator, e.g. :var>-- indicator :nl>|QuantifiedComparison>ValueExpr>[Name]-- operator>CompPredQuantifier>QueryExpr>|MatchValueExprBool-- true if unique>QueryExpr>|ArrayValueExpr[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>|ArrayCtorQueryExpr-- ^ this is used for the query expression version of array constructors, e.g. array(select * from t)>|CSStringLitStringString>|EscapeValueExprChar>|UEscapeValueExprChar>|CollateValueExpr[Name]>|MultisetBinOpValueExprCombineOpSetQuantifierValueExpr>|MultisetCtor[ValueExpr]>|MultisetQueryCtorQueryExpr>|NextValueFor[Name]>|VEComment[Comment]ValueExpr>deriving(Eq,Show,Read,Data,Typeable)
>-- | Represents an identifier name, which can be quoted or unquoted.>dataName=NameString>|QNameString>|UQNameString>|DQNameStringStringString>-- ^ dialect quoted name, the fields are start quote, end quote and the string itself, e.g. `something` is parsed to DQName "`" "`" "something, and $a$ test $a$ is parsed to DQName "$a$" "$a" " test ">deriving(Eq,Show,Read,Data,Typeable)
>-- | Represents a type name, used in casts.>dataTypeName>=TypeName[Name]>|PrecTypeName[Name]Integer>|PrecScaleTypeName[Name]IntegerInteger>|PrecLengthTypeName[Name]Integer(MaybePrecMultiplier)(MaybePrecUnits)>-- precision, characterset, collate>|CharTypeName[Name](MaybeInteger)[Name][Name]>|TimeTypeName[Name](MaybeInteger)Bool-- true == with time zone>|RowTypeName[(Name,TypeName)]>|IntervalTypeNameIntervalTypeField(MaybeIntervalTypeField)>|ArrayTypeNameTypeName(MaybeInteger)>|MultisetTypeNameTypeName>deriving(Eq,Show,Read,Data,Typeable)
>-- | Used for 'expr in (value expression list)', and 'expr in>-- (subquery)' syntax.>dataInPredValue=InList[ValueExpr]>|InQueryExprQueryExpr>deriving(Eq,Show,Read,Data,Typeable)
not sure if scalar subquery, exists and unique should be represented like this
>-- | A subquery in a value expression.>dataSubQueryExprType>=-- | exists (query expr)>SqExists>-- | unique (query expr)>|SqUnique>-- | a scalar subquery>|SqSq>deriving(Eq,Show,Read,Data,Typeable)
>-- | Represents one field in an order by list.>dataSortSpec=SortSpecValueExprDirectionNullsOrder>deriving(Eq,Show,Read,Data,Typeable)
>-- | Represents 'nulls first' or 'nulls last' in an order by clause.>dataNullsOrder=NullsOrderDefault>|NullsFirst>|NullsLast>deriving(Eq,Show,Read,Data,Typeable)
>-- | 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,Data,Typeable)
>-- | Represents whether a window frame clause is over rows or ranges.>dataFrameRows=FrameRows|FrameRange>deriving(Eq,Show,Read,Data,Typeable)
>-- | represents the start or end of a frame>dataFramePos=UnboundedPreceding>|PrecedingValueExpr>|Current>|FollowingValueExpr>|UnboundedFollowing>deriving(Eq,Show,Read,Data,Typeable)
>-- | 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