2013-12-13 11:39:26 +01:00
|
|
|
|
2013-12-17 21:15:19 +01:00
|
|
|
> -- | The AST for SQL queries.
|
2014-04-10 17:53:11 +02:00
|
|
|
> {-# LANGUAGE DeriveDataTypeable #-}
|
2013-12-13 15:04:48 +01:00
|
|
|
> module Language.SQL.SimpleSQL.Syntax
|
2013-12-19 10:46:51 +01:00
|
|
|
> (-- * Value expressions
|
|
|
|
> ValueExpr(..)
|
2013-12-17 12:21:36 +01:00
|
|
|
> ,Name(..)
|
2013-12-13 17:50:41 +01:00
|
|
|
> ,TypeName(..)
|
2013-12-19 09:34:32 +01:00
|
|
|
> ,SetQuantifier(..)
|
2013-12-18 15:27:06 +01:00
|
|
|
> ,SortSpec(..)
|
2013-12-14 12:33:15 +01:00
|
|
|
> ,Direction(..)
|
2013-12-17 17:28:31 +01:00
|
|
|
> ,NullsOrder(..)
|
2013-12-18 15:27:06 +01:00
|
|
|
> ,InPredValue(..)
|
2013-12-14 12:33:15 +01:00
|
|
|
> ,SubQueryExprType(..)
|
2013-12-17 16:29:49 +01:00
|
|
|
> ,Frame(..)
|
|
|
|
> ,FrameRows(..)
|
|
|
|
> ,FramePos(..)
|
2013-12-14 12:33:15 +01:00
|
|
|
> -- * Query expressions
|
2013-12-13 17:50:41 +01:00
|
|
|
> ,QueryExpr(..)
|
2013-12-13 15:04:48 +01:00
|
|
|
> ,makeSelect
|
2013-12-13 22:41:12 +01:00
|
|
|
> ,CombineOp(..)
|
2013-12-13 22:49:22 +01:00
|
|
|
> ,Corresponding(..)
|
2013-12-17 12:41:06 +01:00
|
|
|
> ,Alias(..)
|
2013-12-17 18:17:03 +01:00
|
|
|
> ,GroupingExpr(..)
|
2013-12-14 12:33:15 +01:00
|
|
|
> -- ** From
|
2013-12-13 15:04:48 +01:00
|
|
|
> ,TableRef(..)
|
|
|
|
> ,JoinType(..)
|
|
|
|
> ,JoinCondition(..)
|
|
|
|
> ) where
|
2013-12-13 11:39:26 +01:00
|
|
|
|
2014-04-10 17:53:11 +02:00
|
|
|
> import Data.Data
|
2013-12-19 10:46:51 +01:00
|
|
|
|
2013-12-19 11:15:05 +01:00
|
|
|
> -- | 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.
|
2013-12-19 10:46:51 +01:00
|
|
|
> data ValueExpr
|
2013-12-14 15:58:35 +01:00
|
|
|
> = -- | a numeric literal optional decimal point, e+-
|
|
|
|
> -- integral exponent, e.g
|
|
|
|
> --
|
|
|
|
> -- * 10
|
|
|
|
> --
|
|
|
|
> -- * 10.
|
|
|
|
> --
|
|
|
|
> -- * .1
|
|
|
|
> --
|
|
|
|
> -- * 10.1
|
|
|
|
> --
|
|
|
|
> -- * 1e5
|
|
|
|
> --
|
|
|
|
> -- * 12.34e-6
|
|
|
|
> NumLit String
|
|
|
|
> -- | string literal, currently only basic strings between
|
2013-12-17 19:46:29 +01:00
|
|
|
> -- single quotes with a single quote escaped using ''
|
2013-12-14 15:58:35 +01:00
|
|
|
> | StringLit String
|
|
|
|
> -- | text of interval literal, units of interval precision,
|
|
|
|
> -- e.g. interval 3 days (3)
|
2013-12-17 16:29:49 +01:00
|
|
|
> | IntervalLit
|
|
|
|
> {ilLiteral :: String -- ^ literal text
|
|
|
|
> ,ilUnits :: String -- ^ units
|
|
|
|
> ,ilPrecision :: Maybe Int -- ^ precision
|
|
|
|
> }
|
2013-12-14 15:58:35 +01:00
|
|
|
> -- | identifier without dots
|
2013-12-17 12:21:36 +01:00
|
|
|
> | Iden Name
|
2013-12-17 14:21:43 +01:00
|
|
|
> -- | star, as in select *, t.*, count(*)
|
2013-12-14 15:58:35 +01:00
|
|
|
> | Star
|
|
|
|
> -- | function application (anything that looks like c style
|
|
|
|
> -- function application syntactically)
|
2013-12-19 10:46:51 +01:00
|
|
|
> | App Name [ValueExpr]
|
2013-12-14 15:58:35 +01:00
|
|
|
> -- | aggregate application, which adds distinct or all, and
|
|
|
|
> -- order by, to regular function application
|
2013-12-17 16:29:49 +01:00
|
|
|
> | AggregateApp
|
|
|
|
> {aggName :: Name -- ^ aggregate function name
|
2013-12-19 09:34:32 +01:00
|
|
|
> ,aggDistinct :: Maybe SetQuantifier -- ^ distinct
|
2013-12-19 10:46:51 +01:00
|
|
|
> ,aggArgs :: [ValueExpr]-- ^ args
|
2013-12-18 15:27:06 +01:00
|
|
|
> ,aggOrderBy :: [SortSpec] -- ^ order by
|
2013-12-17 16:29:49 +01:00
|
|
|
> }
|
2013-12-14 15:58:35 +01:00
|
|
|
> -- | window application, which adds over (partition by a order
|
|
|
|
> -- by b) to regular function application. Explicit frames are
|
|
|
|
> -- not currently supported
|
2013-12-17 16:29:49 +01:00
|
|
|
> | WindowApp
|
|
|
|
> {wnName :: Name -- ^ window function name
|
2013-12-19 10:46:51 +01:00
|
|
|
> ,wnArgs :: [ValueExpr] -- ^ args
|
|
|
|
> ,wnPartition :: [ValueExpr] -- ^ partition by
|
2013-12-18 15:27:06 +01:00
|
|
|
> ,wnOrderBy :: [SortSpec] -- ^ order by
|
2013-12-17 16:29:49 +01:00
|
|
|
> ,wnFrame :: Maybe Frame -- ^ frame clause
|
|
|
|
> }
|
2013-12-14 15:58:35 +01:00
|
|
|
> -- | 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)
|
2013-12-19 10:46:51 +01:00
|
|
|
> | BinOp ValueExpr Name ValueExpr
|
2013-12-14 15:58:35 +01:00
|
|
|
> -- | Prefix unary operators. This is used for symbol
|
2013-12-18 14:51:55 +01:00
|
|
|
> -- operators, keyword operators and multiple keyword operators.
|
2013-12-19 10:46:51 +01:00
|
|
|
> | PrefixOp Name ValueExpr
|
2013-12-14 15:58:35 +01:00
|
|
|
> -- | Postfix unary operators. This is used for symbol
|
2013-12-18 14:51:55 +01:00
|
|
|
> -- operators, keyword operators and multiple keyword operators.
|
2013-12-19 10:46:51 +01:00
|
|
|
> | PostfixOp Name ValueExpr
|
2013-12-14 15:58:35 +01:00
|
|
|
> -- | Used for ternary, mixfix and other non orthodox
|
2013-12-18 14:51:55 +01:00
|
|
|
> -- operators. Currently used for row constructors, and for
|
|
|
|
> -- between.
|
2013-12-19 10:46:51 +01:00
|
|
|
> | SpecialOp Name [ValueExpr]
|
2013-12-18 14:51:55 +01:00
|
|
|
> -- | 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.
|
2013-12-19 10:46:51 +01:00
|
|
|
> | SpecialOpK Name (Maybe ValueExpr) [(String,ValueExpr)]
|
2013-12-17 19:46:29 +01:00
|
|
|
> -- | case expression. both flavours supported
|
2013-12-17 16:29:49 +01:00
|
|
|
> | Case
|
2013-12-19 10:46:51 +01:00
|
|
|
> {caseTest :: Maybe ValueExpr -- ^ test value
|
|
|
|
> ,caseWhens :: [([ValueExpr],ValueExpr)] -- ^ when branches
|
|
|
|
> ,caseElse :: Maybe ValueExpr -- ^ else value
|
2013-12-17 16:29:49 +01:00
|
|
|
> }
|
2013-12-19 10:46:51 +01:00
|
|
|
> | Parens ValueExpr
|
2013-12-14 15:58:35 +01:00
|
|
|
> -- | cast(a as typename)
|
2013-12-19 10:46:51 +01:00
|
|
|
> | Cast ValueExpr TypeName
|
2013-12-14 15:58:35 +01:00
|
|
|
> -- | prefix 'typed literal', e.g. int '42'
|
2013-12-17 11:51:14 +01:00
|
|
|
> | TypedLit TypeName String
|
2013-12-14 15:58:35 +01:00
|
|
|
> -- | exists, all, any, some subqueries
|
|
|
|
> | SubQueryExpr SubQueryExprType QueryExpr
|
|
|
|
> -- | in list literal and in subquery, if the bool is false it
|
|
|
|
> -- means not in was used ('a not in (1,2)')
|
2013-12-19 10:46:51 +01:00
|
|
|
> | In Bool ValueExpr InPredValue
|
2013-12-19 09:44:20 +01:00
|
|
|
> | Parameter -- ^ Represents a ? in a parameterized query
|
2014-04-10 17:53:11 +02:00
|
|
|
> deriving (Eq,Show,Read,Data,Typeable)
|
2013-12-13 11:39:26 +01:00
|
|
|
|
2013-12-17 21:15:19 +01:00
|
|
|
> -- | Represents an identifier name, which can be quoted or unquoted.
|
2013-12-17 12:21:36 +01:00
|
|
|
> data Name = Name String
|
|
|
|
> | QName String
|
2014-04-10 17:53:11 +02:00
|
|
|
> deriving (Eq,Show,Read,Data,Typeable)
|
2013-12-17 12:21:36 +01:00
|
|
|
|
2013-12-14 13:10:46 +01:00
|
|
|
> -- | Represents a type name, used in casts.
|
2013-12-17 18:52:14 +01:00
|
|
|
> data TypeName = TypeName String
|
|
|
|
> | PrecTypeName String Int
|
2013-12-17 19:46:29 +01:00
|
|
|
> | PrecScaleTypeName String Int Int
|
2014-04-10 17:53:11 +02:00
|
|
|
> deriving (Eq,Show,Read,Data,Typeable)
|
2013-12-14 12:33:15 +01:00
|
|
|
|
|
|
|
|
2013-12-19 10:46:51 +01:00
|
|
|
> -- | Used for 'expr in (value expression list)', and 'expr in
|
2013-12-17 21:15:19 +01:00
|
|
|
> -- (subquery)' syntax.
|
2013-12-19 10:46:51 +01:00
|
|
|
> data InPredValue = InList [ValueExpr]
|
2013-12-18 15:27:06 +01:00
|
|
|
> | InQueryExpr QueryExpr
|
2014-04-10 17:53:11 +02:00
|
|
|
> deriving (Eq,Show,Read,Data,Typeable)
|
2013-12-13 17:50:41 +01:00
|
|
|
|
2013-12-19 10:46:51 +01:00
|
|
|
> -- | A subquery in a value expression.
|
2013-12-14 13:10:46 +01:00
|
|
|
> data SubQueryExprType
|
|
|
|
> = -- | exists (query expr)
|
|
|
|
> SqExists
|
|
|
|
> -- | a scalar subquery
|
|
|
|
> | SqSq
|
|
|
|
> -- | all (query expr)
|
|
|
|
> | SqAll
|
|
|
|
> -- | some (query expr)
|
|
|
|
> | SqSome
|
|
|
|
> -- | any (query expr)
|
|
|
|
> | SqAny
|
2014-04-10 17:53:11 +02:00
|
|
|
> deriving (Eq,Show,Read,Data,Typeable)
|
2013-12-13 19:43:28 +01:00
|
|
|
|
2013-12-17 21:15:19 +01:00
|
|
|
> -- | Represents one field in an order by list.
|
2013-12-19 10:46:51 +01:00
|
|
|
> data SortSpec = SortSpec ValueExpr Direction NullsOrder
|
2014-04-10 17:53:11 +02:00
|
|
|
> deriving (Eq,Show,Read,Data,Typeable)
|
2013-12-17 17:28:31 +01:00
|
|
|
|
2013-12-17 21:15:19 +01:00
|
|
|
> -- | Represents 'nulls first' or 'nulls last' in an order by clause.
|
2013-12-17 17:28:31 +01:00
|
|
|
> data NullsOrder = NullsOrderDefault
|
|
|
|
> | NullsFirst
|
|
|
|
> | NullsLast
|
2014-04-10 17:53:11 +02:00
|
|
|
> deriving (Eq,Show,Read,Data,Typeable)
|
2013-12-17 17:28:31 +01:00
|
|
|
|
2013-12-17 21:15:19 +01:00
|
|
|
> -- | Represents the frame clause of a window
|
2013-12-17 16:29:49 +01:00
|
|
|
> -- 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
|
2014-04-10 17:53:11 +02:00
|
|
|
> deriving (Eq,Show,Read,Data,Typeable)
|
2013-12-17 16:29:49 +01:00
|
|
|
|
2013-12-17 21:15:19 +01:00
|
|
|
> -- | Represents whether a window frame clause is over rows or ranges.
|
2013-12-17 16:29:49 +01:00
|
|
|
> data FrameRows = FrameRows | FrameRange
|
2014-04-10 17:53:11 +02:00
|
|
|
> deriving (Eq,Show,Read,Data,Typeable)
|
2013-12-17 16:29:49 +01:00
|
|
|
|
|
|
|
> -- | represents the start or end of a frame
|
|
|
|
> data FramePos = UnboundedPreceding
|
2013-12-19 10:46:51 +01:00
|
|
|
> | Preceding ValueExpr
|
2013-12-17 16:29:49 +01:00
|
|
|
> | Current
|
2013-12-19 10:46:51 +01:00
|
|
|
> | Following ValueExpr
|
2013-12-17 16:29:49 +01:00
|
|
|
> | UnboundedFollowing
|
2014-04-10 17:53:11 +02:00
|
|
|
> deriving (Eq,Show,Read,Data,Typeable)
|
2013-12-17 16:29:49 +01:00
|
|
|
|
2013-12-14 13:10:46 +01:00
|
|
|
> -- | Represents a query expression, which can be:
|
|
|
|
> --
|
|
|
|
> -- * a regular select;
|
|
|
|
> --
|
|
|
|
> -- * a set operator (union, except, intersect);
|
|
|
|
> --
|
|
|
|
> -- * a common table expression (with);
|
|
|
|
> --
|
2013-12-19 11:15:05 +01:00
|
|
|
> -- * a table value constructor (values (1,2),(3,4)); or
|
2013-12-14 13:10:46 +01:00
|
|
|
> --
|
2013-12-19 11:15:05 +01:00
|
|
|
> -- * an explicit table (table t).
|
2013-12-13 11:39:26 +01:00
|
|
|
> data QueryExpr
|
|
|
|
> = Select
|
2013-12-19 09:34:32 +01:00
|
|
|
> {qeSetQuantifier :: SetQuantifier
|
2013-12-31 10:31:00 +01:00
|
|
|
> ,qeSelectList :: [(ValueExpr,Maybe Name)]
|
|
|
|
> -- ^ the expressions and the column aliases
|
2013-12-19 09:34:32 +01:00
|
|
|
|
|
|
|
TODO: consider breaking this up. The SQL grammar has
|
|
|
|
queryexpr = select <select list> [<table expression>]
|
|
|
|
table expression = <from> [where] [groupby] [having] ...
|
|
|
|
|
|
|
|
This would make some things a bit cleaner?
|
|
|
|
|
2013-12-13 11:39:26 +01:00
|
|
|
> ,qeFrom :: [TableRef]
|
2013-12-19 10:46:51 +01:00
|
|
|
> ,qeWhere :: Maybe ValueExpr
|
2013-12-17 18:17:03 +01:00
|
|
|
> ,qeGroupBy :: [GroupingExpr]
|
2013-12-19 10:46:51 +01:00
|
|
|
> ,qeHaving :: Maybe ValueExpr
|
2013-12-18 15:27:06 +01:00
|
|
|
> ,qeOrderBy :: [SortSpec]
|
2013-12-19 10:46:51 +01:00
|
|
|
> ,qeOffset :: Maybe ValueExpr
|
2013-12-19 16:50:25 +01:00
|
|
|
> ,qeFetchFirst :: Maybe ValueExpr
|
2013-12-13 22:41:12 +01:00
|
|
|
> }
|
|
|
|
> | CombineQueryExpr
|
2013-12-17 12:41:06 +01:00
|
|
|
> {qe0 :: QueryExpr
|
2013-12-13 22:41:12 +01:00
|
|
|
> ,qeCombOp :: CombineOp
|
2013-12-19 09:34:32 +01:00
|
|
|
> ,qeSetQuantifier :: SetQuantifier
|
2013-12-13 22:49:22 +01:00
|
|
|
> ,qeCorresponding :: Corresponding
|
2013-12-17 12:41:06 +01:00
|
|
|
> ,qe1 :: QueryExpr
|
2013-12-13 22:41:12 +01:00
|
|
|
> }
|
2013-12-17 12:41:06 +01:00
|
|
|
> | With
|
|
|
|
> {qeWithRecursive :: Bool
|
|
|
|
> ,qeViews :: [(Alias,QueryExpr)]
|
|
|
|
> ,qeQueryExpression :: QueryExpr}
|
2013-12-19 10:46:51 +01:00
|
|
|
> | Values [[ValueExpr]]
|
2013-12-17 12:58:44 +01:00
|
|
|
> | Table Name
|
2014-04-10 17:53:11 +02:00
|
|
|
> deriving (Eq,Show,Read,Data,Typeable)
|
2013-12-13 11:39:26 +01:00
|
|
|
|
2013-12-14 10:41:58 +01:00
|
|
|
TODO: add queryexpr parens to deal with e.g.
|
|
|
|
(select 1 union select 2) union select 3
|
2013-12-14 15:58:35 +01:00
|
|
|
I'm not sure if this is valid syntax or not.
|
2013-12-14 12:33:15 +01:00
|
|
|
|
2013-12-17 21:15:19 +01:00
|
|
|
> -- | Helper/'default' value for query exprs to make creating query
|
2013-12-19 11:15:05 +01:00
|
|
|
> -- 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
|
2013-12-19 16:50:25 +01:00
|
|
|
> -- > ,qeFetchFirst = Nothing}
|
2013-12-19 11:15:05 +01:00
|
|
|
|
2013-12-13 11:39:26 +01:00
|
|
|
> makeSelect :: QueryExpr
|
2013-12-19 09:34:32 +01:00
|
|
|
> makeSelect = Select {qeSetQuantifier = All
|
2013-12-13 16:27:02 +01:00
|
|
|
> ,qeSelectList = []
|
2013-12-13 11:39:26 +01:00
|
|
|
> ,qeFrom = []
|
|
|
|
> ,qeWhere = Nothing
|
|
|
|
> ,qeGroupBy = []
|
|
|
|
> ,qeHaving = Nothing
|
2013-12-13 16:27:02 +01:00
|
|
|
> ,qeOrderBy = []
|
2013-12-17 15:00:17 +01:00
|
|
|
> ,qeOffset = Nothing
|
2013-12-19 16:50:25 +01:00
|
|
|
> ,qeFetchFirst = Nothing}
|
2013-12-13 11:39:26 +01:00
|
|
|
|
2013-12-17 12:58:44 +01:00
|
|
|
|
2013-12-17 21:15:19 +01:00
|
|
|
> -- | Represents the Distinct or All keywords, which can be used
|
2013-12-17 12:58:44 +01:00
|
|
|
> -- before a select list, in an aggregate/window function
|
2013-12-17 21:15:19 +01:00
|
|
|
> -- application, or in a query expression set operator.
|
2014-04-10 17:53:11 +02:00
|
|
|
> data SetQuantifier = Distinct | All deriving (Eq,Show,Read,Data,Typeable)
|
2013-12-17 12:58:44 +01:00
|
|
|
|
|
|
|
> -- | The direction for a column in order by.
|
2014-04-10 17:53:11 +02:00
|
|
|
> data Direction = Asc | Desc deriving (Eq,Show,Read,Data,Typeable)
|
2013-12-17 21:15:19 +01:00
|
|
|
> -- | Query expression set operators.
|
2014-04-10 17:53:11 +02:00
|
|
|
> data CombineOp = Union | Except | Intersect deriving (Eq,Show,Read,Data,Typeable)
|
2013-12-17 21:15:19 +01:00
|
|
|
> -- | Corresponding, an option for the set operators.
|
2014-04-10 17:53:11 +02:00
|
|
|
> data Corresponding = Corresponding | Respectively deriving (Eq,Show,Read,Data,Typeable)
|
2013-12-17 12:58:44 +01:00
|
|
|
|
2013-12-17 21:15:19 +01:00
|
|
|
> -- | Represents an item in a group by clause.
|
2013-12-17 18:17:03 +01:00
|
|
|
> data GroupingExpr
|
|
|
|
> = GroupingParens [GroupingExpr]
|
|
|
|
> | Cube [GroupingExpr]
|
|
|
|
> | Rollup [GroupingExpr]
|
|
|
|
> | GroupingSets [GroupingExpr]
|
2013-12-19 10:46:51 +01:00
|
|
|
> | SimpleGroup ValueExpr
|
2014-04-10 17:53:11 +02:00
|
|
|
> deriving (Eq,Show,Read,Data,Typeable)
|
2013-12-17 18:17:03 +01:00
|
|
|
|
2013-12-14 12:33:15 +01:00
|
|
|
> -- | Represents a entry in the csv of tables in the from clause.
|
2013-12-14 13:10:46 +01:00
|
|
|
> data TableRef = -- | from t
|
2013-12-17 12:21:36 +01:00
|
|
|
> TRSimple Name
|
2014-01-22 08:54:14 +01:00
|
|
|
> -- | from s.t
|
|
|
|
> | TRQualified Name Name
|
2013-12-14 13:10:46 +01:00
|
|
|
> -- | from a join b
|
|
|
|
> | TRJoin TableRef JoinType TableRef (Maybe JoinCondition)
|
|
|
|
> -- | from (a)
|
|
|
|
> | TRParens TableRef
|
|
|
|
> -- | from a as b(c,d)
|
2013-12-17 12:41:06 +01:00
|
|
|
> | TRAlias TableRef Alias
|
2013-12-14 13:10:46 +01:00
|
|
|
> -- | from (query expr)
|
|
|
|
> | TRQueryExpr QueryExpr
|
2013-12-17 11:33:33 +01:00
|
|
|
> -- | from function(args)
|
2013-12-19 10:46:51 +01:00
|
|
|
> | TRFunction Name [ValueExpr]
|
2013-12-17 11:45:32 +01:00
|
|
|
> -- | from lateral t
|
|
|
|
> | TRLateral TableRef
|
2014-04-10 17:53:11 +02:00
|
|
|
> deriving (Eq,Show,Read,Data,Typeable)
|
2013-12-13 11:39:26 +01:00
|
|
|
|
2013-12-17 12:58:44 +01:00
|
|
|
> -- | 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),
|
2013-12-17 21:15:19 +01:00
|
|
|
> -- with a(c) as select 1, select * from a.
|
2013-12-17 12:41:06 +01:00
|
|
|
> data Alias = Alias Name (Maybe [Name])
|
2014-04-10 17:53:11 +02:00
|
|
|
> deriving (Eq,Show,Read,Data,Typeable)
|
2013-12-17 12:41:06 +01:00
|
|
|
|
2013-12-17 21:15:19 +01:00
|
|
|
> -- | The type of a join.
|
2013-12-14 12:33:15 +01:00
|
|
|
> data JoinType = JInner | JLeft | JRight | JFull | JCross
|
2014-04-10 17:53:11 +02:00
|
|
|
> deriving (Eq,Show,Read,Data,Typeable)
|
2013-12-13 11:39:26 +01:00
|
|
|
|
2013-12-14 12:33:15 +01:00
|
|
|
> -- | The join condition.
|
2013-12-19 10:46:51 +01:00
|
|
|
> data JoinCondition = JoinOn ValueExpr -- ^ on expr
|
2013-12-17 12:21:36 +01:00
|
|
|
> | JoinUsing [Name] -- ^ using (column list)
|
2013-12-14 13:10:46 +01:00
|
|
|
> | JoinNatural -- ^ natural join was used
|
2014-04-10 17:53:11 +02:00
|
|
|
> deriving (Eq,Show,Read,Data,Typeable)
|