2013-12-13 11:39:26 +01:00
2015-08-01 17:08:54 +02:00
> -- | The AST for SQL.
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(..)
2014-04-18 16:55:56 +02:00
> ,IntervalTypeField(..)
2014-04-20 22:14:55 +02:00
> ,PrecMultiplier(..)
> ,PrecUnits(..)
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(..)
2014-04-17 21:35:43 +02:00
> ,CompPredQuantifier(..)
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(..)
2015-08-01 19:26:00 +02:00
> -- * Statements
> ,Statement(..)
> ,DropBehaviour(..)
> ,IdentityRestart(..)
> ,InsertSource(..)
> ,SetClause(..)
2015-08-02 17:04:40 +02:00
> ,TableElement(..)
2015-08-02 19:56:39 +02:00
> ,ColumnDef(..)
2015-08-02 17:04:40 +02:00
> ,DefaultClause(..)
> ,IdentityWhen(..)
> ,SequenceGeneratorOption(..)
2015-08-02 19:36:05 +02:00
> ,ColConstraintDef(..)
> ,ColConstraint(..)
> ,TableConstraint(..)
2015-08-02 18:27:39 +02:00
> ,ReferenceMatch(..)
> ,ReferentialAction(..)
2015-08-02 19:56:39 +02:00
> ,AlterTableAction(..)
2015-08-02 22:52:01 +02:00
> ,CheckOption(..)
2015-08-04 21:08:32 +02:00
> ,AlterDomainAction(..)
2015-08-15 20:01:48 +02:00
> ,AdminOption(..)
> ,GrantOption(..)
> ,PrivilegeObject(..)
> ,PrivilegeAction(..)
> ,AdminOptionFor(..)
> ,GrantOptionFor(..)
2016-02-12 11:51:06 +01:00
> -- * Dialects
> ,Dialect
> ,ansi2011
> ,mysql
> ,postgres
> ,oracle
> ,sqlserver
2015-08-01 19:26:00 +02:00
> -- * Comment
2015-03-14 12:40:35 +01:00
> ,Comment(..)
2013-12-13 15:04:48 +01:00
> ) where
2013-12-13 11:39:26 +01:00
2014-04-10 17:53:11 +02:00
> import Data.Data
2016-02-12 11:51:06 +01:00
> import Language.SQL.SimpleSQL.Dialect
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
2016-02-12 12:09:58 +01:00
> -- | string literal, with the start and end quote
> -- e.g. 'test' -> StringLit "'" "'" "test"
> | StringLit String String String
2013-12-14 15:58:35 +01:00
> -- | text of interval literal, units of interval precision,
> -- e.g. interval 3 days (3)
2013-12-17 16:29:49 +01:00
> | IntervalLit
2014-04-18 20:38:24 +02:00
> {ilSign :: Maybe Bool -- ^ true if + used, false if - used
> ,ilLiteral :: String -- ^ literal text
> ,ilFrom :: IntervalTypeField
> ,ilTo :: Maybe IntervalTypeField
2013-12-17 16:29:49 +01:00
> }
2016-02-12 10:57:09 +01:00
> -- | prefix 'typed literal', e.g. int '42'
> | TypedLit TypeName String
2014-04-18 10:43:37 +02:00
> -- | identifier with parts separated by dots
> | 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
2016-02-12 10:57:09 +01:00
> | Parameter -- ^ Represents a ? 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 ValueExpr [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]
2013-12-14 15:58:35 +01:00
> -- | function application (anything that looks like c style
> -- function application syntactically)
2014-04-18 10:43:37 +02:00
> | App [Name] [ValueExpr]
2016-02-12 10:57:09 +01:00
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
2014-04-18 10:43:37 +02:00
> {aggName :: [Name] -- ^ aggregate function name
2014-04-18 10:18:21 +02:00
> ,aggDistinct :: 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
2014-04-19 17:01:49 +02:00
> ,aggFilter :: Maybe ValueExpr -- ^ filter
> }
> -- | aggregates with within group
> | AggregateAppGroup
> {aggName :: [Name] -- ^ aggregate function name
> ,aggArgs :: [ValueExpr] -- ^ args
> ,aggGroup :: [SortSpec] -- ^ within group
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
2014-04-18 10:43:37 +02:00
> {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
> }
2016-02-12 10:57:09 +01:00
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.
2014-04-18 10:43:37 +02:00
> | SpecialOpK [Name] (Maybe ValueExpr) [(String,ValueExpr)]
2016-02-12 10:57:09 +01:00
> -- | cast(a as typename)
> | Cast ValueExpr TypeName
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
> }
2016-02-12 10:57:09 +01:00
2013-12-19 10:46:51 +01:00
> | Parens ValueExpr
2016-02-12 10:57:09 +01:00
2013-12-14 15:58:35 +01:00
> -- | 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
2016-02-12 10:57:09 +01:00
> -- | exists, all, any, some subqueries
> | SubQueryExpr SubQueryExprType QueryExpr
2014-04-18 16:51:57 +02:00
> | QuantifiedComparison
2014-04-17 21:35:43 +02:00
> ValueExpr
2014-04-18 10:43:37 +02:00
> [Name] -- operator
2014-04-17 21:35:43 +02:00
> CompPredQuantifier
> QueryExpr
2016-02-12 10:57:09 +01:00
2014-04-18 16:51:57 +02:00
> | Match ValueExpr Bool -- true if unique
2014-04-17 21:35:43 +02:00
> QueryExpr
2014-04-17 21:57:33 +02:00
> | Array ValueExpr [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
2014-04-18 13:50:54 +02:00
> | ArrayCtor QueryExpr -- ^ this is used for the query expression version of array constructors, e.g. array(select * from t)
2016-02-12 10:57:09 +01:00
todo: special syntax for like, similar with escape - escape cannot go
in other places
2014-04-17 23:16:24 +02:00
> | Escape ValueExpr Char
> | UEscape ValueExpr Char
2014-04-19 11:47:25 +02:00
> | Collate ValueExpr [Name]
2014-04-18 19:50:24 +02:00
> | MultisetBinOp ValueExpr CombineOp SetQuantifier ValueExpr
> | MultisetCtor [ValueExpr]
> | MultisetQueryCtor QueryExpr
2014-04-19 20:17:19 +02:00
> | NextValueFor [Name]
2015-03-14 14:28:05 +01:00
> | VEComment [Comment] ValueExpr
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
2016-02-12 12:09:58 +01:00
> | QuotedName String String String
> -- ^ quoted name, the fields are start quote, end quote and the string itself, these will usually be ", others are possible e.g. `something` is parsed to QuotedName "`" "`" "something, and $a$ test $a$ is parsed to QuotedName "$a$" "$a$" " test "
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.
2014-04-18 16:55:56 +02:00
> data TypeName
> = TypeName [Name]
> | PrecTypeName [Name] Integer
> | PrecScaleTypeName [Name] Integer Integer
2014-04-20 22:14:55 +02:00
> | PrecLengthTypeName [Name] Integer (Maybe PrecMultiplier) (Maybe PrecUnits)
2014-04-18 16:55:56 +02:00
> -- precision, characterset, collate
2014-04-19 11:47:25 +02:00
> | CharTypeName [Name] (Maybe Integer) [Name] [Name]
2014-04-18 16:55:56 +02:00
> | TimeTypeName [Name] (Maybe Integer) Bool -- true == with time zone
> | RowTypeName [(Name,TypeName)]
> | IntervalTypeName IntervalTypeField (Maybe IntervalTypeField)
2014-04-18 18:49:00 +02:00
> | ArrayTypeName TypeName (Maybe Integer)
> | MultisetTypeName TypeName
2014-04-18 16:55:56 +02:00
> deriving (Eq,Show,Read,Data,Typeable)
2014-04-18 18:49:00 +02:00
> data IntervalTypeField = Itf String (Maybe (Integer, Maybe Integer))
2014-04-18 16:55:56 +02:00
> deriving (Eq,Show,Read,Data,Typeable)
2014-04-20 22:14:55 +02:00
> data PrecMultiplier = PrecK | PrecM | PrecG | PrecT | PrecP
> deriving (Eq,Show,Read,Data,Typeable)
> data PrecUnits = PrecCharacters
> | PrecOctets
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
2014-04-17 21:57:33 +02:00
not sure if scalar subquery, exists and unique should be represented like this
2014-04-17 21:35:43 +02: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
2014-04-17 21:35:43 +02:00
> -- | unique (query expr)
> | SqUnique
2013-12-14 13:10:46 +01:00
> -- | a scalar subquery
> | SqSq
2014-04-17 21:35:43 +02:00
> deriving (Eq,Show,Read,Data,Typeable)
> data CompPredQuantifier
> = CPAny
> | CPSome
> | CPAll
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]]
2014-04-18 10:43:37 +02:00
> | Table [Name]
2015-03-14 14:28:05 +01:00
> | QEComment [Comment] QueryExpr
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
2014-04-18 10:18:21 +02:00
> -- > makeSelect = Select {qeSetQuantifier = SQDefault
2013-12-19 11:15:05 +01:00
> -- > ,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
2014-04-18 10:18:21 +02:00
> makeSelect = Select {qeSetQuantifier = SQDefault
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
2015-03-14 14:28:05 +01:00
> ,qeFetchFirst = Nothing}
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-18 10:18:21 +02:00
> data SetQuantifier = SQDefault | 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-18 10:18:21 +02:00
> data Direction = DirDefault | 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.
2014-04-18 10:43:37 +02:00
> data TableRef = -- | from t / from s.t
> TRSimple [Name]
2014-04-19 10:18:29 +02:00
> -- | from a join b, the bool is true if natural was used
> | TRJoin TableRef Bool JoinType TableRef (Maybe JoinCondition)
2013-12-14 13:10:46 +01:00
> -- | 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)
2014-04-18 10:43:37 +02: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)
2014-04-10 17:53:11 +02:00
> deriving (Eq,Show,Read,Data,Typeable)
2014-06-27 11:19:15 +02:00
2015-08-01 19:26:00 +02:00
---------------------------
> data Statement =
> -- ddl
2015-08-02 22:27:09 +02:00
> CreateSchema [Name]
> | DropSchema [Name] DropBehaviour
2015-08-01 22:16:26 +02:00
> | CreateTable [Name] [TableElement]
2015-08-02 19:56:39 +02:00
> | AlterTable [Name] AlterTableAction
2015-08-02 22:27:09 +02:00
> | DropTable [Name] DropBehaviour
2015-08-02 22:52:01 +02:00
> | CreateView Bool [Name] (Maybe [Name])
> QueryExpr (Maybe CheckOption)
> | DropView [Name] DropBehaviour
2015-08-04 21:08:32 +02:00
> | CreateDomain [Name] TypeName (Maybe ValueExpr)
> [(Maybe [Name], ValueExpr)]
> | AlterDomain [Name] AlterDomainAction
> | DropDomain [Name] DropBehaviour
2015-08-04 21:35:51 +02:00
> -- probably won't do character sets, collations
> -- and translations because I think they are too far from
> -- reality
2015-08-09 19:13:11 +02:00
> {- | CreateCharacterSet
2015-08-01 19:26:00 +02:00
> | DropCharacterSet
> | CreateCollation
> | DropCollation
> | CreateTranslation
2015-08-04 21:35:51 +02:00
> | DropTranslation -}
2015-08-16 19:03:02 +02:00
> | CreateAssertion [Name] ValueExpr
> | DropAssertion [Name] DropBehaviour
> {- | CreateTrigger
2015-08-01 19:26:00 +02:00
> | DropTrigger
> | CreateType
> | AlterType
> | DropType
2015-08-04 21:35:51 +02:00
> -- routine stuff? TODO
2015-08-01 19:26:00 +02:00
> | CreateCast
> | DropCast
> | CreateOrdering
2015-08-04 21:35:51 +02:00
> | DropOrdering -}
2015-08-01 19:26:00 +02:00
> -- transforms
2015-08-04 21:35:51 +02:00
> | CreateSequence [Name] [SequenceGeneratorOption]
> | AlterSequence [Name] [SequenceGeneratorOption]
> | DropSequence [Name] DropBehaviour
2015-08-01 19:26:00 +02:00
> -- dml
> | SelectStatement QueryExpr
> {- | DeclareCursor
> | OpenCursor
> | FetchCursor
> | CloseCursor
> | SelectInto -}
> -- | DeletePositioned
> | Delete [Name] (Maybe Name) (Maybe ValueExpr)
> | Truncate [Name] IdentityRestart
> | Insert [Name] (Maybe [Name]) InsertSource
> -- | Merge
> | Update [Name] (Maybe Name) [SetClause] (Maybe ValueExpr)
> {- | TemporaryTable
> | FreeLocator
> | HoldLocator -}
> -- access control
2015-08-15 20:01:48 +02:00
> | GrantPrivilege [PrivilegeAction] PrivilegeObject [Name] GrantOption
> | GrantRole [Name] [Name] AdminOption
> | CreateRole Name
> | DropRole Name
> | RevokePrivilege GrantOptionFor [PrivilegeAction] PrivilegeObject
> [Name] DropBehaviour
> | RevokeRole AdminOptionFor [Name] [Name] DropBehaviour
2015-08-01 19:26:00 +02:00
> -- transaction management
2015-08-04 21:53:08 +02:00
> | StartTransaction
> -- | SetTransaction
> -- | SetContraints
> | Savepoint Name
> | ReleaseSavepoint Name
> | Commit
> | Rollback (Maybe Name)
2015-08-01 19:26:00 +02:00
> -- session
> {- | SetSessionCharacteristics
> | SetSessionAuthorization
> | SetRole
> | SetTimeZone
> | SetCatalog
> | SetSchema
> | SetNames
> | SetTransform
> | SetCollation -}
> deriving (Eq,Show,Read,Data,Typeable)
> data DropBehaviour =
> Restrict
> | Cascade
> | DefaultDropBehaviour
> deriving (Eq,Show,Read,Data,Typeable)
> data IdentityRestart =
> ContinueIdentity
> | RestartIdentity
> | DefaultIdentityRestart
> deriving (Eq,Show,Read,Data,Typeable)
> data InsertSource =
> InsertQuery QueryExpr
> | DefaultInsertValues
> deriving (Eq,Show,Read,Data,Typeable)
> data SetClause =
> Set [Name] ValueExpr
> | SetMultiple [[Name]] [ValueExpr]
> deriving (Eq,Show,Read,Data,Typeable)
2015-08-01 22:16:26 +02:00
> data TableElement =
2015-08-02 19:56:39 +02:00
> TableColumnDef ColumnDef
> | TableConstraintDef (Maybe [Name]) TableConstraint
> deriving (Eq,Show,Read,Data,Typeable)
> data ColumnDef = ColumnDef Name TypeName
2015-08-02 17:04:40 +02:00
> (Maybe DefaultClause)
2015-08-02 19:36:05 +02:00
> [ColConstraintDef]
2015-08-01 22:16:26 +02:00
> -- (Maybe CollateClause)
> deriving (Eq,Show,Read,Data,Typeable)
2015-08-02 19:36:05 +02:00
> data ColConstraintDef =
> ColConstraintDef (Maybe [Name]) ColConstraint
2015-08-02 18:27:39 +02:00
> -- (Maybe [ConstraintCharacteristics])
> deriving (Eq,Show,Read,Data,Typeable)
2015-08-02 19:36:05 +02:00
> data ColConstraint =
> ColNotNullConstraint
> | ColUniqueConstraint
> | ColPrimaryKeyConstraint
> | ColReferencesConstraint [Name] (Maybe Name)
2015-08-02 18:27:39 +02:00
> ReferenceMatch
> ReferentialAction
> ReferentialAction
2015-08-02 19:36:05 +02:00
> | ColCheckConstraint ValueExpr
2015-08-02 18:27:39 +02:00
> deriving (Eq,Show,Read,Data,Typeable)
2015-08-02 19:36:05 +02:00
> data TableConstraint =
> TableUniqueConstraint [Name]
> | TablePrimaryKeyConstraint [Name]
> | TableReferencesConstraint [Name] [Name] (Maybe [Name])
> ReferenceMatch
> ReferentialAction
> ReferentialAction
> | TableCheckConstraint ValueExpr
> deriving (Eq,Show,Read,Data,Typeable)
2015-08-02 18:27:39 +02:00
> data ReferenceMatch =
> DefaultReferenceMatch
> | MatchFull
> | MatchPartial
> | MatchSimple
> deriving (Eq,Show,Read,Data,Typeable)
> data ReferentialAction =
> DefaultReferentialAction
> | RefCascade
> | RefSetNull
> | RefSetDefault
> | RefRestrict
> | RefNoAction
> deriving (Eq,Show,Read,Data,Typeable)
2015-08-02 19:56:39 +02:00
> data AlterTableAction =
> AddColumnDef ColumnDef
2015-08-02 22:22:06 +02:00
> | AlterColumnSetDefault Name ValueExpr
> | AlterColumnDropDefault Name
> | AlterColumnSetNotNull Name
> | AlterColumnDropNotNull Name
> | AlterColumnSetDataType Name TypeName
> {- | AlterColumnAlterIdentity
> | AlterColumnDropIdentity
> | AlterColumnDropColumnGeneration-}
> | DropColumn Name DropBehaviour
> | AddTableConstraintDef (Maybe [Name]) TableConstraint
> -- | AlterTableConstraintDef
> | DropTableConstraintDef [Name] DropBehaviour
2015-08-02 19:56:39 +02:00
> deriving (Eq,Show,Read,Data,Typeable)
2015-08-02 18:27:39 +02:00
> {-data ConstraintCharacteristics =
> ConstraintCharacteristics
> ConstraintCheckTime
> Deferrable
> ConstraintEnforcement
> deriving (Eq,Show,Read,Data,Typeable)
> data ConstraintCheckTime =
> DefaultConstraintCheckTime
> | InitiallyDeferred
> | InitiallyImmeditate
> deriving (Eq,Show,Read,Data,Typeable)
> data Deferrable =
> DefaultDefferable
> | Deferrable
> | NotDeferrable
> deriving (Eq,Show,Read,Data,Typeable)
> data ConstraintEnforcement =
> DefaultConstraintEnforcement
> | Enforced
> | NotEnforced
> deriving (Eq,Show,Read,Data,Typeable) -}
2015-08-01 22:16:26 +02:00
> {-data TableConstraintDef
> deriving (Eq,Show,Read,Data,Typeable) -}
2015-08-02 17:04:40 +02:00
> data DefaultClause =
2015-08-01 22:16:26 +02:00
> DefaultClause ValueExpr
2015-08-02 17:04:40 +02:00
> | IdentityColumnSpec IdentityWhen [SequenceGeneratorOption]
2015-08-02 17:14:45 +02:00
> | GenerationClause ValueExpr
2015-08-02 17:04:40 +02:00
> deriving (Eq,Show,Read,Data,Typeable)
> data IdentityWhen =
2015-08-02 22:22:06 +02:00
> GeneratedAlways
2015-08-02 17:04:40 +02:00
> | GeneratedByDefault
> deriving (Eq,Show,Read,Data,Typeable)
> data SequenceGeneratorOption =
2015-08-04 21:35:51 +02:00
> SGODataType TypeName
> | SGOStartWith Integer
> | SGORestart (Maybe Integer)
2015-08-02 17:04:40 +02:00
> | SGOIncrementBy Integer
> | SGOMaxValue Integer
> | SGONoMaxValue
> | SGOMinValue Integer
> | SGONoMinValue
> | SGOCycle
> | SGONoCycle
> deriving (Eq,Show,Read,Data,Typeable)
2015-08-01 22:16:26 +02:00
2015-08-02 22:52:01 +02:00
> data CheckOption =
> DefaultCheckOption
> | CascadedCheckOption
> | LocalCheckOption
> deriving (Eq,Show,Read,Data,Typeable)
2015-08-04 21:08:32 +02:00
> data AlterDomainAction =
> ADSetDefault ValueExpr
> | ADDropDefault
> | ADAddConstraint (Maybe [Name]) ValueExpr
> | ADDropConstraint [Name]
> deriving (Eq,Show,Read,Data,Typeable)
2015-08-01 22:16:26 +02:00
2015-08-15 20:01:48 +02:00
> data AdminOption = WithAdminOption | WithoutAdminOption
> deriving (Eq,Show,Read,Data,Typeable)
> data GrantOption = WithGrantOption | WithoutGrantOption
> deriving (Eq,Show,Read,Data,Typeable)
> data AdminOptionFor = AdminOptionFor | NoAdminOptionFor
> deriving (Eq,Show,Read,Data,Typeable)
> data GrantOptionFor = GrantOptionFor | NoGrantOptionFor
> deriving (Eq,Show,Read,Data,Typeable)
> data PrivilegeObject =
> PrivTable [Name]
> | PrivDomain [Name]
> | PrivType [Name]
> | PrivSequence [Name]
> | PrivFunction [Name]
> deriving (Eq,Show,Read,Data,Typeable)
> data PrivilegeAction =
> PrivAll
> | PrivSelect [Name]
> | PrivDelete
> | PrivInsert [Name]
> | PrivUpdate [Name]
> | PrivReferences [Name]
> | PrivUsage
> | PrivTrigger
> | PrivExecute
> deriving (Eq,Show,Read,Data,Typeable)
2015-08-01 19:26:00 +02:00
> -- | Comment. Useful when generating SQL code programmatically. The
> -- parser doesn't produce these.
2015-03-14 15:15:37 +01:00
> data Comment = BlockComment String
2015-03-14 12:40:35 +01:00
> deriving (Eq,Show,Read,Data,Typeable)