> -- | The AST for SQL. > {-# LANGUAGE DeriveDataTypeable #-} > module Language.SQL.SimpleSQL.Syntax > (-- * Scalar expressions > ScalarExpr(..) > ,Name(..) > ,TypeName(..) > ,IntervalTypeField(..) > ,Sign(..) > ,PrecMultiplier(..) > ,PrecUnits(..) > ,SetQuantifier(..) > ,SortSpec(..) > ,Direction(..) > ,NullsOrder(..) > ,InPredValue(..) > ,SubQueryExprType(..) > ,CompPredQuantifier(..) > ,Frame(..) > ,FrameRows(..) > ,FramePos(..) > ,OdbcLiteralType(..) > -- * Query expressions > ,QueryExpr(..) > ,makeSelect > ,SetOperatorName(..) > ,Corresponding(..) > ,Alias(..) > ,GroupingExpr(..) > -- ** From > ,TableRef(..) > ,JoinType(..) > ,JoinCondition(..) > -- * Statements > ,Statement(..) > ,DropBehaviour(..) > ,IdentityRestart(..) > ,InsertSource(..) > ,SetClause(..) > ,TableElement(..) > ,ColumnDef(..) > ,DefaultClause(..) > ,IdentityWhen(..) > ,SequenceGeneratorOption(..) > ,ColConstraintDef(..) > ,ColConstraint(..) > ,TableConstraint(..) > ,ReferenceMatch(..) > ,ReferentialAction(..) > ,AlterTableAction(..) > ,CheckOption(..) > ,AlterDomainAction(..) > ,AdminOption(..) > ,GrantOption(..) > ,PrivilegeObject(..) > ,PrivilegeAction(..) > ,AdminOptionFor(..) > ,GrantOptionFor(..) > -- * Comment > ,Comment(..) > ) where > import Data.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. > data ScalarExpr > = -- | a numeric literal optional decimal point, e+- > -- integral exponent, e.g > -- > -- * 10 > -- > -- * 10. > -- > -- * .1 > -- > -- * 10.1 > -- > -- * 1e5 > -- > -- * 12.34e-6 > NumLit String > -- | string literal, with the start and end quote > -- e.g. 'test' -> StringLit "'" "'" "test" > | StringLit String String String > -- | text of interval literal, units of interval precision, > -- e.g. interval 3 days (3) > | IntervalLit > {ilSign :: Maybe Sign -- ^ if + or - used > ,ilLiteral :: String -- ^ literal text > ,ilFrom :: IntervalTypeField > ,ilTo :: Maybe IntervalTypeField > } > -- | prefix 'typed literal', e.g. int '42' > | TypedLit TypeName String > -- | identifier with parts separated by dots > | Iden [Name] > -- | star, as in select *, t.*, count(*) > | Star > | Parameter -- ^ Represents a ? in a parameterized query > | PositionalArg Int -- ^ Represents an e.g. $1 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 > -- | 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) > | BinOp ScalarExpr [Name] ScalarExpr > -- | Prefix unary operators. This is used for symbol > -- operators, keyword operators and multiple keyword operators. > | PrefixOp [Name] ScalarExpr > -- | Postfix unary operators. This is used for symbol > -- operators, keyword operators and multiple keyword operators. > | PostfixOp [Name] ScalarExpr > -- | Used for ternary, mixfix and other non orthodox > -- operators. Currently used for row constructors, and for > -- between. > | SpecialOp [Name] [ScalarExpr] > -- | function application (anything that looks like c style > -- function application syntactically) > | App [Name] [ScalarExpr] > -- | aggregate application, which adds distinct or all, and > -- order by, to regular function application > | AggregateApp > {aggName :: [Name] -- ^ aggregate function name > ,aggDistinct :: SetQuantifier -- ^ distinct > ,aggArgs :: [ScalarExpr]-- ^ args > ,aggOrderBy :: [SortSpec] -- ^ order by > ,aggFilter :: Maybe ScalarExpr -- ^ filter > } > -- | aggregates with within group > | AggregateAppGroup > {aggName :: [Name] -- ^ aggregate function name > ,aggArgs :: [ScalarExpr] -- ^ 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 :: [ScalarExpr] -- ^ args > ,wnPartition :: [ScalarExpr] -- ^ partition by > ,wnOrderBy :: [SortSpec] -- ^ order by > ,wnFrame :: Maybe Frame -- ^ frame clause > } > -- | 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] (Maybe ScalarExpr) [(String,ScalarExpr)] > -- | cast(a as typename) > | Cast ScalarExpr TypeName > -- | case expression. both flavours supported > | Case > {caseTest :: Maybe ScalarExpr -- ^ test value > ,caseWhens :: [([ScalarExpr],ScalarExpr)] -- ^ when branches > ,caseElse :: Maybe ScalarExpr -- ^ else value > } > | Parens ScalarExpr > -- | in list literal and in subquery, if the bool is false it > -- means not in was used ('a not in (1,2)') > | In Bool ScalarExpr InPredValue > -- | exists, all, any, some subqueries > | SubQueryExpr SubQueryExprType QueryExpr > | QuantifiedComparison > ScalarExpr > [Name] -- operator > CompPredQuantifier > QueryExpr > | Match ScalarExpr Bool -- true if unique > QueryExpr > | Array ScalarExpr [ScalarExpr] -- ^ represents an array > -- access expression, or an array ctor > -- e.g. a[3]. The first > -- scalarExpr 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) todo: special syntax for like, similar with escape - escape cannot go in other places > -- | Escape ScalarExpr Char > -- | UEscape ScalarExpr Char > | Collate ScalarExpr [Name] > | MultisetBinOp ScalarExpr SetOperatorName SetQuantifier ScalarExpr > | MultisetCtor [ScalarExpr] > | MultisetQueryCtor QueryExpr > | NextValueFor [Name] > | VEComment [Comment] ScalarExpr > | OdbcLiteral OdbcLiteralType String > -- ^ an odbc literal e.g. {d '2000-01-01'} > | OdbcFunc ScalarExpr > -- ^ an odbc function call e.g. {fn CHARACTER_LENGTH('test')} > deriving (Eq,Show,Read,Data,Typeable) > -- | Represents an identifier name, which can be quoted or unquoted. > -- examples: > -- > -- * test -> Name Nothing "test" > -- * "test" -> Name (Just "\"","\"") "test" > -- * `something` -> Name (Just ("`","`") "something" > -- * [ms] -> Name (Just ("[","]") "ms" > data Name = Name (Maybe (String,String)) String > deriving (Eq,Show,Read,Data,Typeable) > -- | Represents a type name, used in casts. > data TypeName > = TypeName [Name] > | PrecTypeName [Name] Integer > | PrecScaleTypeName [Name] Integer Integer > | PrecLengthTypeName [Name] Integer (Maybe PrecMultiplier) (Maybe PrecUnits) > -- precision, characterset, collate > | CharTypeName [Name] (Maybe Integer) [Name] [Name] > | TimeTypeName [Name] (Maybe Integer) Bool -- true == with time zone > | RowTypeName [(Name,TypeName)] > | IntervalTypeName IntervalTypeField (Maybe IntervalTypeField) > | ArrayTypeName TypeName (Maybe Integer) > | MultisetTypeName TypeName > deriving (Eq,Show,Read,Data,Typeable) > data IntervalTypeField = Itf String (Maybe (Integer, Maybe Integer)) > deriving (Eq,Show,Read,Data,Typeable) > data Sign = Plus | Minus > deriving (Eq,Show,Read,Data,Typeable) > data PrecMultiplier = PrecK | PrecM | PrecG | PrecT | PrecP > deriving (Eq,Show,Read,Data,Typeable) > data PrecUnits = PrecCharacters > | PrecOctets > deriving (Eq,Show,Read,Data,Typeable) > -- | Used for 'expr in (scalar expression list)', and 'expr in > -- (subquery)' syntax. > data InPredValue = InList [ScalarExpr] > | InQueryExpr QueryExpr > deriving (Eq,Show,Read,Data,Typeable) not sure if scalar subquery, exists and unique should be represented like this > -- | A subquery in a scalar expression. > data SubQueryExprType > = -- | exists (query expr) > SqExists > -- | unique (query expr) > | SqUnique > -- | a scalar subquery > | SqSq > deriving (Eq,Show,Read,Data,Typeable) > data CompPredQuantifier > = CPAny > | CPSome > | CPAll > deriving (Eq,Show,Read,Data,Typeable) > -- | Represents one field in an order by list. > data SortSpec = SortSpec ScalarExpr Direction NullsOrder > deriving (Eq,Show,Read,Data,Typeable) > -- | Represents 'nulls first' or 'nulls last' in an order by clause. > data NullsOrder = 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 > data Frame = FrameFrom FrameRows FramePos > | FrameBetween FrameRows FramePos FramePos > deriving (Eq,Show,Read,Data,Typeable) > -- | Represents whether a window frame clause is over rows or ranges. > data FrameRows = FrameRows | FrameRange > deriving (Eq,Show,Read,Data,Typeable) > -- | represents the start or end of a frame > data FramePos = UnboundedPreceding > | Preceding ScalarExpr > | Current > | Following ScalarExpr > | UnboundedFollowing > deriving (Eq,Show,Read,Data,Typeable) > -- | the type of an odbc literal (e.g. {d '2000-01-01'}), > -- correpsonding to the letter after the opening { > data OdbcLiteralType = OLDate > | OLTime > | OLTimestamp > 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). > data QueryExpr > = Select > {qeSetQuantifier :: SetQuantifier > ,qeSelectList :: [(ScalarExpr,Maybe Name)] > -- ^ the expressions and the column aliases TODO: consider breaking this up. The SQL grammar has queryexpr = select