>
> {-# LANGUAGE DeriveDataTypeable #-}
> module Language.SQL.SimpleSQL.Syntax
> (
> ScalarExpr(..)
> ,Name(..)
> ,TypeName(..)
> ,IntervalTypeField(..)
> ,Sign(..)
> ,PrecMultiplier(..)
> ,PrecUnits(..)
> ,SetQuantifier(..)
> ,SortSpec(..)
> ,Direction(..)
> ,NullsOrder(..)
> ,InPredValue(..)
> ,SubQueryExprType(..)
> ,CompPredQuantifier(..)
> ,Frame(..)
> ,FrameRows(..)
> ,FramePos(..)
> ,OdbcLiteralType(..)
>
> ,QueryExpr(..)
> ,makeSelect
> ,SetOperatorName(..)
> ,Corresponding(..)
> ,Alias(..)
> ,GroupingExpr(..)
>
> ,TableRef(..)
> ,JoinType(..)
> ,JoinCondition(..)
>
> ,Statement(..)
> ,DropBehaviour(..)
> ,IdentityRestart(..)
> ,InsertSource(..)
> ,SetClause(..)
> ,TableElement(..)
> ,ColumnDef(..)
> ,DefaultClause(..)
> ,IdentityWhen(..)
> ,SequenceGeneratorOption(..)
> ,ColConstraintDef(..)
> ,ColConstraint(..)
> ,TableConstraint(..)
> ,ReferenceMatch(..)
> ,ReferentialAction(..)
> ,AlterTableAction(..)
> ,CheckOption(..)
> ,AlterDomainAction(..)
> ,AdminOption(..)
> ,GrantOption(..)
> ,PrivilegeObject(..)
> ,PrivilegeAction(..)
> ,AdminOptionFor(..)
> ,GrantOptionFor(..)
>
> ,Dialect(allowOdbc)
> ,ansi2011
> ,mysql
> ,postgres
> ,oracle
> ,sqlserver
>
> ,Comment(..)
> ) where
> import Data.Data
> import Language.SQL.SimpleSQL.Dialect
>
>
>
> data ScalarExpr
> =
>
>
>
>
>
>
>
>
>
>
>
>
>
> NumLit String
>
>
> | StringLit String String String
>
>
> | IntervalLit
> {ilSign :: Maybe Sign
> ,ilLiteral :: String
> ,ilFrom :: IntervalTypeField
> ,ilTo :: Maybe IntervalTypeField
> }
>
> | TypedLit TypeName String
>
> | Iden [Name]
>
> | Star
> | Parameter
> | PositionalArg Int
> | HostParameter String (Maybe String)
>
>
>
>
>
>
>
> | BinOp ScalarExpr [Name] ScalarExpr
>
>
> | PrefixOp [Name] ScalarExpr
>
>
> | PostfixOp [Name] ScalarExpr
>
>
>
> | SpecialOp [Name] [ScalarExpr]
>
>
> | App [Name] [ScalarExpr]
>
>
> | AggregateApp
> {aggName :: [Name]
> ,aggDistinct :: SetQuantifier
> ,aggArgs :: [ScalarExpr]
> ,aggOrderBy :: [SortSpec]
> ,aggFilter :: Maybe ScalarExpr
> }
>
> | AggregateAppGroup
> {aggName :: [Name]
> ,aggArgs :: [ScalarExpr]
> ,aggGroup :: [SortSpec]
> }
>
>
>
> | WindowApp
> {wnName :: [Name]
> ,wnArgs :: [ScalarExpr]
> ,wnPartition :: [ScalarExpr]
> ,wnOrderBy :: [SortSpec]
> ,wnFrame :: Maybe Frame
> }
>
>
>
>
>
> | SpecialOpK [Name] (Maybe ScalarExpr) [(String,ScalarExpr)]
>
> | Cast ScalarExpr TypeName
>
> | Case
> {caseTest :: Maybe ScalarExpr
> ,caseWhens :: [([ScalarExpr],ScalarExpr)]
> ,caseElse :: Maybe ScalarExpr
> }
> | Parens ScalarExpr
>
>
> | In Bool ScalarExpr InPredValue
>
> | SubQueryExpr SubQueryExprType QueryExpr
> | QuantifiedComparison
> ScalarExpr
> [Name]
> CompPredQuantifier
> QueryExpr
> | Match ScalarExpr Bool
> QueryExpr
> | Array ScalarExpr [ScalarExpr]
>
>
>
>
> | ArrayCtor QueryExpr
todo: special syntax for like, similar with escape - escape cannot go
in other places
>
>
> | Collate ScalarExpr [Name]
> | MultisetBinOp ScalarExpr SetOperatorName SetQuantifier ScalarExpr
> | MultisetCtor [ScalarExpr]
> | MultisetQueryCtor QueryExpr
> | NextValueFor [Name]
> | VEComment [Comment] ScalarExpr
> | OdbcLiteral OdbcLiteralType String
>
> | OdbcFunc ScalarExpr
>
> deriving (Eq,Show,Read,Data,Typeable)
>
>
>
>
>
>
>
> data Name = Name (Maybe (String,String)) String
> deriving (Eq,Show,Read,Data,Typeable)
>
> data TypeName
> = TypeName [Name]
> | PrecTypeName [Name] Integer
> | PrecScaleTypeName [Name] Integer Integer
> | PrecLengthTypeName [Name] Integer (Maybe PrecMultiplier) (Maybe PrecUnits)
>
> | CharTypeName [Name] (Maybe Integer) [Name] [Name]
> | TimeTypeName [Name] (Maybe Integer) Bool
> | 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)
>
>
> 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
>
> data SubQueryExprType
> =
> SqExists
>
> | SqUnique
>
> | SqSq
> deriving (Eq,Show,Read,Data,Typeable)
> data CompPredQuantifier
> = CPAny
> | CPSome
> | CPAll
> deriving (Eq,Show,Read,Data,Typeable)
>
> data SortSpec = SortSpec ScalarExpr Direction NullsOrder
> deriving (Eq,Show,Read,Data,Typeable)
>
> data NullsOrder = NullsOrderDefault
> | NullsFirst
> | NullsLast
> deriving (Eq,Show,Read,Data,Typeable)
>
>
>
> data Frame = FrameFrom FrameRows FramePos
> | FrameBetween FrameRows FramePos FramePos
> deriving (Eq,Show,Read,Data,Typeable)
>
> data FrameRows = FrameRows | FrameRange
> deriving (Eq,Show,Read,Data,Typeable)
>
> data FramePos = UnboundedPreceding
> | Preceding ScalarExpr
> | Current
> | Following ScalarExpr
> | UnboundedFollowing
> deriving (Eq,Show,Read,Data,Typeable)
>
>
> data OdbcLiteralType = OLDate
> | OLTime
> | OLTimestamp
> deriving (Eq,Show,Read,Data,Typeable)
>
>
>
>
>
>
>
>
>
>
>
> data QueryExpr
> = Select
> {qeSetQuantifier :: SetQuantifier
> ,qeSelectList :: [(ScalarExpr,Maybe Name)]
>
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?
> ,qeFrom :: [TableRef]
> ,qeWhere :: Maybe ScalarExpr
> ,qeGroupBy :: [GroupingExpr]
> ,qeHaving :: Maybe ScalarExpr
> ,qeOrderBy :: [SortSpec]
> ,qeOffset :: Maybe ScalarExpr
> ,qeFetchFirst :: Maybe ScalarExpr
> }
> | QueryExprSetOp
> {qe0 :: QueryExpr
> ,qeCombOp :: SetOperatorName
> ,qeSetQuantifier :: SetQuantifier
> ,qeCorresponding :: Corresponding
> ,qe1 :: QueryExpr
> }
> | With
> {qeWithRecursive :: Bool
> ,qeViews :: [(Alias,QueryExpr)]
> ,qeQueryExpression :: QueryExpr}
> | Values [[ScalarExpr]]
> | Table [Name]
> | QEComment [Comment] QueryExpr
> deriving (Eq,Show,Read,Data,Typeable)
TODO: add queryexpr parens to deal with e.g.
(select 1 union select 2) union select 3
I'm not sure if this is valid syntax or not.
>
>
>
>
>
>
>
>
>
>
>
>
>
> makeSelect :: QueryExpr
> makeSelect = Select {qeSetQuantifier = SQDefault
> ,qeSelectList = []
> ,qeFrom = []
> ,qeWhere = Nothing
> ,qeGroupBy = []
> ,qeHaving = Nothing
> ,qeOrderBy = []
> ,qeOffset = Nothing
> ,qeFetchFirst = Nothing}
>
>
>
> data SetQuantifier = SQDefault | Distinct | All deriving (Eq,Show,Read,Data,Typeable)
>
> data Direction = DirDefault | Asc | Desc deriving (Eq,Show,Read,Data,Typeable)
>
> data SetOperatorName = Union | Except | Intersect deriving (Eq,Show,Read,Data,Typeable)
>
> data Corresponding = Corresponding | Respectively deriving (Eq,Show,Read,Data,Typeable)
>
> data GroupingExpr
> = GroupingParens [GroupingExpr]
> | Cube [GroupingExpr]
> | Rollup [GroupingExpr]
> | GroupingSets [GroupingExpr]
> | SimpleGroup ScalarExpr
> deriving (Eq,Show,Read,Data,Typeable)
>
> data TableRef =
> TRSimple [Name]
>
> | TRJoin TableRef Bool JoinType TableRef (Maybe JoinCondition)
>
> | TRParens TableRef
>
> | TRAlias TableRef Alias
>
> | TRQueryExpr QueryExpr
>
> | TRFunction [Name] [ScalarExpr]
>
> | TRLateral TableRef
>
> | TROdbc TableRef
> deriving (Eq,Show,Read,Data,Typeable)
>
>
>
> data Alias = Alias Name (Maybe [Name])
> deriving (Eq,Show,Read,Data,Typeable)
>
> data JoinType = JInner | JLeft | JRight | JFull | JCross
> deriving (Eq,Show,Read,Data,Typeable)
>
> data JoinCondition = JoinOn ScalarExpr
> | JoinUsing [Name]
> deriving (Eq,Show,Read,Data,Typeable)
> data Statement =
>
> CreateSchema [Name]
> | DropSchema [Name] DropBehaviour
> | CreateTable [Name] [TableElement]
> | AlterTable [Name] AlterTableAction
> | DropTable [Name] DropBehaviour
> | CreateView Bool [Name] (Maybe [Name])
> QueryExpr (Maybe CheckOption)
> | DropView [Name] DropBehaviour
> | CreateDomain [Name] TypeName (Maybe ScalarExpr)
> [(Maybe [Name], ScalarExpr)]
> | AlterDomain [Name] AlterDomainAction
> | DropDomain [Name] DropBehaviour
>
>
>
>
> | CreateAssertion [Name] ScalarExpr
> | DropAssertion [Name] DropBehaviour
>
>
> | CreateSequence [Name] [SequenceGeneratorOption]
> | AlterSequence [Name] [SequenceGeneratorOption]
> | DropSequence [Name] DropBehaviour
>
> | SelectStatement QueryExpr
>
>
> | Delete [Name] (Maybe Name) (Maybe ScalarExpr)
> | Truncate [Name] IdentityRestart
> | Insert [Name] (Maybe [Name]) InsertSource
>
> | Update [Name] (Maybe Name) [SetClause] (Maybe ScalarExpr)
>
>
> | GrantPrivilege [PrivilegeAction] PrivilegeObject [Name] GrantOption
> | GrantRole [Name] [Name] AdminOption
> | CreateRole Name
> | DropRole Name
> | RevokePrivilege GrantOptionFor [PrivilegeAction] PrivilegeObject
> [Name] DropBehaviour
> | RevokeRole AdminOptionFor [Name] [Name] DropBehaviour
>
> | StartTransaction
>
>
> | Savepoint Name
> | ReleaseSavepoint Name
> | Commit
> | Rollback (Maybe Name)
>
>
> | StatementComment [Comment]
> 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] ScalarExpr
> | SetMultiple [[Name]] [ScalarExpr]
> deriving (Eq,Show,Read,Data,Typeable)
> data TableElement =
> TableColumnDef ColumnDef
> | TableConstraintDef (Maybe [Name]) TableConstraint
> deriving (Eq,Show,Read,Data,Typeable)
> data ColumnDef = ColumnDef Name TypeName
> (Maybe DefaultClause)
> [ColConstraintDef]
>
> deriving (Eq,Show,Read,Data,Typeable)
> data ColConstraintDef =
> ColConstraintDef (Maybe [Name]) ColConstraint
>
> deriving (Eq,Show,Read,Data,Typeable)
> data ColConstraint =
> ColNotNullConstraint
> | ColUniqueConstraint
> | ColPrimaryKeyConstraint
> | ColReferencesConstraint [Name] (Maybe Name)
> ReferenceMatch
> ReferentialAction
> ReferentialAction
> | ColCheckConstraint ScalarExpr
> deriving (Eq,Show,Read,Data,Typeable)
> data TableConstraint =
> TableUniqueConstraint [Name]
> | TablePrimaryKeyConstraint [Name]
> | TableReferencesConstraint [Name] [Name] (Maybe [Name])
> ReferenceMatch
> ReferentialAction
> ReferentialAction
> | TableCheckConstraint ScalarExpr
> deriving (Eq,Show,Read,Data,Typeable)
> 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)
> data AlterTableAction =
> AddColumnDef ColumnDef
> | AlterColumnSetDefault Name ScalarExpr
> | AlterColumnDropDefault Name
> | AlterColumnSetNotNull Name
> | AlterColumnDropNotNull Name
> | AlterColumnSetDataType Name TypeName
>
> | DropColumn Name DropBehaviour
> | AddTableConstraintDef (Maybe [Name]) TableConstraint
>
> | DropTableConstraintDef [Name] DropBehaviour
> deriving (Eq,Show,Read,Data,Typeable)
>
>
> data DefaultClause =
> DefaultClause ScalarExpr
> | IdentityColumnSpec IdentityWhen [SequenceGeneratorOption]
> | GenerationClause ScalarExpr
> deriving (Eq,Show,Read,Data,Typeable)
> data IdentityWhen =
> GeneratedAlways
> | GeneratedByDefault
> deriving (Eq,Show,Read,Data,Typeable)
> data SequenceGeneratorOption =
> SGODataType TypeName
> | SGOStartWith Integer
> | SGORestart (Maybe Integer)
> | SGOIncrementBy Integer
> | SGOMaxValue Integer
> | SGONoMaxValue
> | SGOMinValue Integer
> | SGONoMinValue
> | SGOCycle
> | SGONoCycle
> deriving (Eq,Show,Read,Data,Typeable)
> data CheckOption =
> DefaultCheckOption
> | CascadedCheckOption
> | LocalCheckOption
> deriving (Eq,Show,Read,Data,Typeable)
> data AlterDomainAction =
> ADSetDefault ScalarExpr
> | ADDropDefault
> | ADAddConstraint (Maybe [Name]) ScalarExpr
> | ADDropConstraint [Name]
> deriving (Eq,Show,Read,Data,Typeable)
> 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)
>
>
> data Comment = BlockComment String
> deriving (Eq,Show,Read,Data,Typeable)