{-# LANGUAGE CPP #-}
{-# LANGUAGE UndecidableInstances #-}
module Database.Beam.Backend.SQL.AST where
import Prelude hiding (Ordering)
import Database.Beam.Backend.Internal.Compat
import Database.Beam.Backend.SQL.SQL92
import Database.Beam.Backend.SQL.SQL99
import Database.Beam.Backend.SQL.SQL2003
import Database.Beam.Backend.SQL.Types
import Data.Text (Text)
import Data.ByteString (ByteString)
import Data.Time
import Data.Word (Word16, Word32, Word64)
import Data.Typeable
import Data.Int
import GHC.TypeLits
data Command
= SelectCommand Select
| InsertCommand Insert
| UpdateCommand Update
| DeleteCommand Delete
deriving (Int -> Command -> ShowS
[Command] -> ShowS
Command -> String
(Int -> Command -> ShowS)
-> (Command -> String) -> ([Command] -> ShowS) -> Show Command
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Command] -> ShowS
$cshowList :: [Command] -> ShowS
show :: Command -> String
$cshow :: Command -> String
showsPrec :: Int -> Command -> ShowS
$cshowsPrec :: Int -> Command -> ShowS
Show, Command -> Command -> Bool
(Command -> Command -> Bool)
-> (Command -> Command -> Bool) -> Eq Command
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Command -> Command -> Bool
$c/= :: Command -> Command -> Bool
== :: Command -> Command -> Bool
$c== :: Command -> Command -> Bool
Eq)
instance IsSql92Syntax Command where
type Sql92SelectSyntax Command = Select
type Sql92UpdateSyntax Command = Update
type Sql92InsertSyntax Command = Insert
type Sql92DeleteSyntax Command = Delete
selectCmd :: Sql92SelectSyntax Command -> Command
selectCmd = Sql92SelectSyntax Command -> Command
Select -> Command
SelectCommand
insertCmd :: Sql92InsertSyntax Command -> Command
insertCmd = Sql92InsertSyntax Command -> Command
Insert -> Command
InsertCommand
updateCmd :: Sql92UpdateSyntax Command -> Command
updateCmd = Sql92UpdateSyntax Command -> Command
Update -> Command
UpdateCommand
deleteCmd :: Sql92DeleteSyntax Command -> Command
deleteCmd = Sql92DeleteSyntax Command -> Command
Delete -> Command
DeleteCommand
data Select
= Select
{ Select -> SelectTable
selectTable :: SelectTable
, Select -> [Ordering]
selectOrdering :: [ Ordering ]
, Select -> Maybe Integer
selectLimit, Select -> Maybe Integer
selectOffset :: Maybe Integer }
deriving (Int -> Select -> ShowS
[Select] -> ShowS
Select -> String
(Int -> Select -> ShowS)
-> (Select -> String) -> ([Select] -> ShowS) -> Show Select
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Select] -> ShowS
$cshowList :: [Select] -> ShowS
show :: Select -> String
$cshow :: Select -> String
showsPrec :: Int -> Select -> ShowS
$cshowsPrec :: Int -> Select -> ShowS
Show, Select -> Select -> Bool
(Select -> Select -> Bool)
-> (Select -> Select -> Bool) -> Eq Select
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Select -> Select -> Bool
$c/= :: Select -> Select -> Bool
== :: Select -> Select -> Bool
$c== :: Select -> Select -> Bool
Eq)
instance IsSql92SelectSyntax Select where
type Sql92SelectSelectTableSyntax Select = SelectTable
type Sql92SelectOrderingSyntax Select = Ordering
selectStmt :: Sql92SelectSelectTableSyntax Select
-> [Sql92SelectOrderingSyntax Select]
-> Maybe Integer
-> Maybe Integer
-> Select
selectStmt = Sql92SelectSelectTableSyntax Select
-> [Sql92SelectOrderingSyntax Select]
-> Maybe Integer
-> Maybe Integer
-> Select
SelectTable
-> [Ordering] -> Maybe Integer -> Maybe Integer -> Select
Select
data SelectTable
= SelectTable
{ SelectTable -> Maybe SetQuantifier
selectQuantifier :: Maybe SetQuantifier
, SelectTable -> Projection
selectProjection :: Projection
, SelectTable -> Maybe From
selectFrom :: Maybe From
, SelectTable -> Maybe Expression
selectWhere :: Maybe Expression
, SelectTable -> Maybe Grouping
selectGrouping :: Maybe Grouping
, SelectTable -> Maybe Expression
selectHaving :: Maybe Expression }
| UnionTables Bool SelectTable SelectTable
| IntersectTables Bool SelectTable SelectTable
| ExceptTable Bool SelectTable SelectTable
deriving (Int -> SelectTable -> ShowS
[SelectTable] -> ShowS
SelectTable -> String
(Int -> SelectTable -> ShowS)
-> (SelectTable -> String)
-> ([SelectTable] -> ShowS)
-> Show SelectTable
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SelectTable] -> ShowS
$cshowList :: [SelectTable] -> ShowS
show :: SelectTable -> String
$cshow :: SelectTable -> String
showsPrec :: Int -> SelectTable -> ShowS
$cshowsPrec :: Int -> SelectTable -> ShowS
Show, SelectTable -> SelectTable -> Bool
(SelectTable -> SelectTable -> Bool)
-> (SelectTable -> SelectTable -> Bool) -> Eq SelectTable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SelectTable -> SelectTable -> Bool
$c/= :: SelectTable -> SelectTable -> Bool
== :: SelectTable -> SelectTable -> Bool
$c== :: SelectTable -> SelectTable -> Bool
Eq)
instance IsSql92SelectTableSyntax SelectTable where
type Sql92SelectTableSelectSyntax SelectTable = Select
type Sql92SelectTableExpressionSyntax SelectTable = Expression
type Sql92SelectTableProjectionSyntax SelectTable = Projection
type Sql92SelectTableFromSyntax SelectTable = From
type Sql92SelectTableGroupingSyntax SelectTable = Grouping
type Sql92SelectTableSetQuantifierSyntax SelectTable = SetQuantifier
selectTableStmt :: Maybe (Sql92SelectTableSetQuantifierSyntax SelectTable)
-> Sql92SelectTableProjectionSyntax SelectTable
-> Maybe (Sql92SelectTableFromSyntax SelectTable)
-> Maybe (Sql92SelectTableExpressionSyntax SelectTable)
-> Maybe (Sql92SelectTableGroupingSyntax SelectTable)
-> Maybe (Sql92SelectTableExpressionSyntax SelectTable)
-> SelectTable
selectTableStmt = Maybe (Sql92SelectTableSetQuantifierSyntax SelectTable)
-> Sql92SelectTableProjectionSyntax SelectTable
-> Maybe (Sql92SelectTableFromSyntax SelectTable)
-> Maybe (Sql92SelectTableExpressionSyntax SelectTable)
-> Maybe (Sql92SelectTableGroupingSyntax SelectTable)
-> Maybe (Sql92SelectTableExpressionSyntax SelectTable)
-> SelectTable
Maybe SetQuantifier
-> Projection
-> Maybe From
-> Maybe Expression
-> Maybe Grouping
-> Maybe Expression
-> SelectTable
SelectTable
unionTables :: Bool -> SelectTable -> SelectTable -> SelectTable
unionTables = Bool -> SelectTable -> SelectTable -> SelectTable
UnionTables
intersectTables :: Bool -> SelectTable -> SelectTable -> SelectTable
intersectTables = Bool -> SelectTable -> SelectTable -> SelectTable
IntersectTables
exceptTable :: Bool -> SelectTable -> SelectTable -> SelectTable
exceptTable = Bool -> SelectTable -> SelectTable -> SelectTable
ExceptTable
data Insert
= Insert
{ Insert -> TableName
insertTable :: TableName
, Insert -> [Text]
insertFields :: [ Text ]
, Insert -> InsertValues
insertValues :: InsertValues }
deriving (Int -> Insert -> ShowS
[Insert] -> ShowS
Insert -> String
(Int -> Insert -> ShowS)
-> (Insert -> String) -> ([Insert] -> ShowS) -> Show Insert
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Insert] -> ShowS
$cshowList :: [Insert] -> ShowS
show :: Insert -> String
$cshow :: Insert -> String
showsPrec :: Int -> Insert -> ShowS
$cshowsPrec :: Int -> Insert -> ShowS
Show, Insert -> Insert -> Bool
(Insert -> Insert -> Bool)
-> (Insert -> Insert -> Bool) -> Eq Insert
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Insert -> Insert -> Bool
$c/= :: Insert -> Insert -> Bool
== :: Insert -> Insert -> Bool
$c== :: Insert -> Insert -> Bool
Eq)
instance IsSql92InsertSyntax Insert where
type Sql92InsertValuesSyntax Insert = InsertValues
type Sql92InsertTableNameSyntax Insert = TableName
insertStmt :: Sql92InsertTableNameSyntax Insert
-> [Text] -> Sql92InsertValuesSyntax Insert -> Insert
insertStmt = Sql92InsertTableNameSyntax Insert
-> [Text] -> Sql92InsertValuesSyntax Insert -> Insert
TableName -> [Text] -> InsertValues -> Insert
Insert
data InsertValues
= InsertValues
{ InsertValues -> [[Expression]]
insertValuesExpressions :: [ [ Expression ] ] }
| InsertSelect
{ InsertValues -> Select
insertSelectStmt :: Select }
deriving (Int -> InsertValues -> ShowS
[InsertValues] -> ShowS
InsertValues -> String
(Int -> InsertValues -> ShowS)
-> (InsertValues -> String)
-> ([InsertValues] -> ShowS)
-> Show InsertValues
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InsertValues] -> ShowS
$cshowList :: [InsertValues] -> ShowS
show :: InsertValues -> String
$cshow :: InsertValues -> String
showsPrec :: Int -> InsertValues -> ShowS
$cshowsPrec :: Int -> InsertValues -> ShowS
Show, InsertValues -> InsertValues -> Bool
(InsertValues -> InsertValues -> Bool)
-> (InsertValues -> InsertValues -> Bool) -> Eq InsertValues
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InsertValues -> InsertValues -> Bool
$c/= :: InsertValues -> InsertValues -> Bool
== :: InsertValues -> InsertValues -> Bool
$c== :: InsertValues -> InsertValues -> Bool
Eq)
instance IsSql92InsertValuesSyntax InsertValues where
type Sql92InsertValuesExpressionSyntax InsertValues = Expression
type Sql92InsertValuesSelectSyntax InsertValues = Select
insertSqlExpressions :: [[Sql92InsertValuesExpressionSyntax InsertValues]] -> InsertValues
insertSqlExpressions = [[Sql92InsertValuesExpressionSyntax InsertValues]] -> InsertValues
[[Expression]] -> InsertValues
InsertValues
insertFromSql :: Sql92InsertValuesSelectSyntax InsertValues -> InsertValues
insertFromSql = Sql92InsertValuesSelectSyntax InsertValues -> InsertValues
Select -> InsertValues
InsertSelect
data Update
= Update
{ Update -> TableName
updateTable :: TableName
, Update -> [(FieldName, Expression)]
updateFields :: [ (FieldName, Expression) ]
, Update -> Maybe Expression
updateWhere :: Maybe Expression }
deriving (Int -> Update -> ShowS
[Update] -> ShowS
Update -> String
(Int -> Update -> ShowS)
-> (Update -> String) -> ([Update] -> ShowS) -> Show Update
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Update] -> ShowS
$cshowList :: [Update] -> ShowS
show :: Update -> String
$cshow :: Update -> String
showsPrec :: Int -> Update -> ShowS
$cshowsPrec :: Int -> Update -> ShowS
Show, Update -> Update -> Bool
(Update -> Update -> Bool)
-> (Update -> Update -> Bool) -> Eq Update
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Update -> Update -> Bool
$c/= :: Update -> Update -> Bool
== :: Update -> Update -> Bool
$c== :: Update -> Update -> Bool
Eq)
instance IsSql92UpdateSyntax Update where
type Sql92UpdateTableNameSyntax Update = TableName
type Sql92UpdateFieldNameSyntax Update = FieldName
type Sql92UpdateExpressionSyntax Update = Expression
updateStmt :: Sql92UpdateTableNameSyntax Update
-> [(Sql92UpdateFieldNameSyntax Update,
Sql92UpdateExpressionSyntax Update)]
-> Maybe (Sql92UpdateExpressionSyntax Update)
-> Update
updateStmt = Sql92UpdateTableNameSyntax Update
-> [(Sql92UpdateFieldNameSyntax Update,
Sql92UpdateExpressionSyntax Update)]
-> Maybe (Sql92UpdateExpressionSyntax Update)
-> Update
TableName
-> [(FieldName, Expression)] -> Maybe Expression -> Update
Update
data Delete
= Delete
{ Delete -> TableName
deleteTable :: TableName
, Delete -> Maybe Text
deleteAlias :: Maybe Text
, Delete -> Maybe Expression
deleteWhere :: Maybe Expression }
deriving (Int -> Delete -> ShowS
[Delete] -> ShowS
Delete -> String
(Int -> Delete -> ShowS)
-> (Delete -> String) -> ([Delete] -> ShowS) -> Show Delete
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Delete] -> ShowS
$cshowList :: [Delete] -> ShowS
show :: Delete -> String
$cshow :: Delete -> String
showsPrec :: Int -> Delete -> ShowS
$cshowsPrec :: Int -> Delete -> ShowS
Show, Delete -> Delete -> Bool
(Delete -> Delete -> Bool)
-> (Delete -> Delete -> Bool) -> Eq Delete
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Delete -> Delete -> Bool
$c/= :: Delete -> Delete -> Bool
== :: Delete -> Delete -> Bool
$c== :: Delete -> Delete -> Bool
Eq)
instance IsSql92DeleteSyntax Delete where
type Sql92DeleteTableNameSyntax Delete = TableName
type Sql92DeleteExpressionSyntax Delete = Expression
deleteStmt :: Sql92DeleteTableNameSyntax Delete
-> Maybe Text
-> Maybe (Sql92DeleteExpressionSyntax Delete)
-> Delete
deleteStmt = Sql92DeleteTableNameSyntax Delete
-> Maybe Text
-> Maybe (Sql92DeleteExpressionSyntax Delete)
-> Delete
TableName -> Maybe Text -> Maybe Expression -> Delete
Delete
deleteSupportsAlias :: Proxy Delete -> Bool
deleteSupportsAlias Proxy Delete
_ = Bool
True
data FieldName
= QualifiedField Text Text
| UnqualifiedField Text
deriving (Int -> FieldName -> ShowS
[FieldName] -> ShowS
FieldName -> String
(Int -> FieldName -> ShowS)
-> (FieldName -> String)
-> ([FieldName] -> ShowS)
-> Show FieldName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FieldName] -> ShowS
$cshowList :: [FieldName] -> ShowS
show :: FieldName -> String
$cshow :: FieldName -> String
showsPrec :: Int -> FieldName -> ShowS
$cshowsPrec :: Int -> FieldName -> ShowS
Show, FieldName -> FieldName -> Bool
(FieldName -> FieldName -> Bool)
-> (FieldName -> FieldName -> Bool) -> Eq FieldName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FieldName -> FieldName -> Bool
$c/= :: FieldName -> FieldName -> Bool
== :: FieldName -> FieldName -> Bool
$c== :: FieldName -> FieldName -> Bool
Eq)
instance IsSql92FieldNameSyntax FieldName where
qualifiedField :: Text -> Text -> FieldName
qualifiedField = Text -> Text -> FieldName
QualifiedField
unqualifiedField :: Text -> FieldName
unqualifiedField = Text -> FieldName
UnqualifiedField
data ComparatorQuantifier
= ComparatorQuantifierAny
| ComparatorQuantifierAll
deriving (Int -> ComparatorQuantifier -> ShowS
[ComparatorQuantifier] -> ShowS
ComparatorQuantifier -> String
(Int -> ComparatorQuantifier -> ShowS)
-> (ComparatorQuantifier -> String)
-> ([ComparatorQuantifier] -> ShowS)
-> Show ComparatorQuantifier
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ComparatorQuantifier] -> ShowS
$cshowList :: [ComparatorQuantifier] -> ShowS
show :: ComparatorQuantifier -> String
$cshow :: ComparatorQuantifier -> String
showsPrec :: Int -> ComparatorQuantifier -> ShowS
$cshowsPrec :: Int -> ComparatorQuantifier -> ShowS
Show, ComparatorQuantifier -> ComparatorQuantifier -> Bool
(ComparatorQuantifier -> ComparatorQuantifier -> Bool)
-> (ComparatorQuantifier -> ComparatorQuantifier -> Bool)
-> Eq ComparatorQuantifier
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ComparatorQuantifier -> ComparatorQuantifier -> Bool
$c/= :: ComparatorQuantifier -> ComparatorQuantifier -> Bool
== :: ComparatorQuantifier -> ComparatorQuantifier -> Bool
$c== :: ComparatorQuantifier -> ComparatorQuantifier -> Bool
Eq)
instance IsSql92QuantifierSyntax ComparatorQuantifier where
quantifyOverAll :: ComparatorQuantifier
quantifyOverAll = ComparatorQuantifier
ComparatorQuantifierAll
quantifyOverAny :: ComparatorQuantifier
quantifyOverAny = ComparatorQuantifier
ComparatorQuantifierAny
data
=
|
|
|
|
|
|
|
deriving (Int -> ExtractField -> ShowS
[ExtractField] -> ShowS
ExtractField -> String
(Int -> ExtractField -> ShowS)
-> (ExtractField -> String)
-> ([ExtractField] -> ShowS)
-> Show ExtractField
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExtractField] -> ShowS
$cshowList :: [ExtractField] -> ShowS
show :: ExtractField -> String
$cshow :: ExtractField -> String
showsPrec :: Int -> ExtractField -> ShowS
$cshowsPrec :: Int -> ExtractField -> ShowS
Show, ExtractField -> ExtractField -> Bool
(ExtractField -> ExtractField -> Bool)
-> (ExtractField -> ExtractField -> Bool) -> Eq ExtractField
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExtractField -> ExtractField -> Bool
$c/= :: ExtractField -> ExtractField -> Bool
== :: ExtractField -> ExtractField -> Bool
$c== :: ExtractField -> ExtractField -> Bool
Eq)
data DataType
= DataTypeChar Bool (Maybe Word) (Maybe Text)
| DataTypeNationalChar Bool (Maybe Word)
| DataTypeBit Bool (Maybe Word)
| DataTypeNumeric (Maybe (Word, Maybe Word))
| DataTypeDecimal (Maybe (Word, Maybe Word))
| DataTypeInteger
| DataTypeSmallInt
| DataTypeBigInt
| DataTypeFloat (Maybe Word)
| DataTypeReal
| DataTypeDoublePrecision
| DataTypeDate
| DataTypeTime (Maybe Word) Bool
| DataTypeTimeStamp (Maybe Word) Bool
| DataTypeInterval ExtractField
| DataTypeIntervalFromTo ExtractField ExtractField
| DataTypeBoolean
| DataTypeBinaryLargeObject
| DataTypeCharacterLargeObject
| DataTypeArray DataType Int
| DataTypeRow [ (Text, DataType) ]
| DataTypeDomain Text
deriving (Int -> DataType -> ShowS
[DataType] -> ShowS
DataType -> String
(Int -> DataType -> ShowS)
-> (DataType -> String) -> ([DataType] -> ShowS) -> Show DataType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DataType] -> ShowS
$cshowList :: [DataType] -> ShowS
show :: DataType -> String
$cshow :: DataType -> String
showsPrec :: Int -> DataType -> ShowS
$cshowsPrec :: Int -> DataType -> ShowS
Show, DataType -> DataType -> Bool
(DataType -> DataType -> Bool)
-> (DataType -> DataType -> Bool) -> Eq DataType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DataType -> DataType -> Bool
$c/= :: DataType -> DataType -> Bool
== :: DataType -> DataType -> Bool
$c== :: DataType -> DataType -> Bool
Eq)
instance IsSql92DataTypeSyntax DataType where
domainType :: Text -> DataType
domainType = Text -> DataType
DataTypeDomain
charType :: Maybe Word -> Maybe Text -> DataType
charType = Bool -> Maybe Word -> Maybe Text -> DataType
DataTypeChar Bool
False
varCharType :: Maybe Word -> Maybe Text -> DataType
varCharType = Bool -> Maybe Word -> Maybe Text -> DataType
DataTypeChar Bool
True
nationalCharType :: Maybe Word -> DataType
nationalCharType = Bool -> Maybe Word -> DataType
DataTypeNationalChar Bool
False
nationalVarCharType :: Maybe Word -> DataType
nationalVarCharType = Bool -> Maybe Word -> DataType
DataTypeNationalChar Bool
True
bitType :: Maybe Word -> DataType
bitType = Bool -> Maybe Word -> DataType
DataTypeBit Bool
False
varBitType :: Maybe Word -> DataType
varBitType = Bool -> Maybe Word -> DataType
DataTypeBit Bool
True
numericType :: Maybe (Word, Maybe Word) -> DataType
numericType = Maybe (Word, Maybe Word) -> DataType
DataTypeNumeric
decimalType :: Maybe (Word, Maybe Word) -> DataType
decimalType = Maybe (Word, Maybe Word) -> DataType
DataTypeDecimal
intType :: DataType
intType = DataType
DataTypeInteger
smallIntType :: DataType
smallIntType = DataType
DataTypeSmallInt
floatType :: Maybe Word -> DataType
floatType = Maybe Word -> DataType
DataTypeFloat
doubleType :: DataType
doubleType = DataType
DataTypeDoublePrecision
realType :: DataType
realType = DataType
DataTypeReal
dateType :: DataType
dateType = DataType
DataTypeDate
timeType :: Maybe Word -> Bool -> DataType
timeType = Maybe Word -> Bool -> DataType
DataTypeTime
timestampType :: Maybe Word -> Bool -> DataType
timestampType = Maybe Word -> Bool -> DataType
DataTypeTimeStamp
instance IsSql99DataTypeSyntax DataType where
characterLargeObjectType :: DataType
characterLargeObjectType = DataType
DataTypeCharacterLargeObject
binaryLargeObjectType :: DataType
binaryLargeObjectType = DataType
DataTypeCharacterLargeObject
booleanType :: DataType
booleanType = DataType
DataTypeBoolean
arrayType :: DataType -> Int -> DataType
arrayType = DataType -> Int -> DataType
DataTypeArray
rowType :: [(Text, DataType)] -> DataType
rowType = [(Text, DataType)] -> DataType
DataTypeRow
instance IsSql2008BigIntDataTypeSyntax DataType where
bigIntType :: DataType
bigIntType = DataType
DataTypeBigInt
data SetQuantifier
= SetQuantifierAll | SetQuantifierDistinct
deriving (Int -> SetQuantifier -> ShowS
[SetQuantifier] -> ShowS
SetQuantifier -> String
(Int -> SetQuantifier -> ShowS)
-> (SetQuantifier -> String)
-> ([SetQuantifier] -> ShowS)
-> Show SetQuantifier
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetQuantifier] -> ShowS
$cshowList :: [SetQuantifier] -> ShowS
show :: SetQuantifier -> String
$cshow :: SetQuantifier -> String
showsPrec :: Int -> SetQuantifier -> ShowS
$cshowsPrec :: Int -> SetQuantifier -> ShowS
Show, SetQuantifier -> SetQuantifier -> Bool
(SetQuantifier -> SetQuantifier -> Bool)
-> (SetQuantifier -> SetQuantifier -> Bool) -> Eq SetQuantifier
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetQuantifier -> SetQuantifier -> Bool
$c/= :: SetQuantifier -> SetQuantifier -> Bool
== :: SetQuantifier -> SetQuantifier -> Bool
$c== :: SetQuantifier -> SetQuantifier -> Bool
Eq)
instance IsSql92AggregationSetQuantifierSyntax SetQuantifier where
setQuantifierDistinct :: SetQuantifier
setQuantifierDistinct = SetQuantifier
SetQuantifierDistinct
setQuantifierAll :: SetQuantifier
setQuantifierAll = SetQuantifier
SetQuantifierAll
data Expression
= ExpressionValue Value
| ExpressionDefault
| ExpressionRow [ Expression ]
| ExpressionIn Expression [ Expression ]
| ExpressionIsNull Expression
| ExpressionIsNotNull Expression
| ExpressionIsTrue Expression
| ExpressionIsNotTrue Expression
| ExpressionIsFalse Expression
| ExpressionIsNotFalse Expression
| ExpressionIsUnknown Expression
| ExpressionIsNotUnknown Expression
| ExpressionCase [(Expression, Expression)] Expression
| ExpressionCoalesce [Expression]
| ExpressionNullIf Expression Expression
| ExpressionFieldName FieldName
| ExpressionBetween Expression Expression Expression
| ExpressionBinOp Text Expression Expression
| ExpressionCompOp Text (Maybe ComparatorQuantifier) Expression Expression
| ExpressionUnOp Text Expression
| ExpressionPosition Expression Expression
| ExpressionCast Expression DataType
| ExtractField Expression
| ExpressionCharLength Expression
| ExpressionOctetLength Expression
| ExpressionBitLength Expression
| ExpressionAbs Expression
| ExpressionLower Expression
| ExpressionUpper Expression
| ExpressionTrim Expression
| ExpressionNamedFunction Text
| ExpressionFunctionCall Expression [ Expression ]
| ExpressionInstanceField Expression Text
| ExpressionRefField Expression Text
| ExpressionCountAll
| ExpressionAgg Text (Maybe SetQuantifier) [ Expression ]
| ExpressionBuiltinFunction Text [ Expression ]
| ExpressionSubquery Select
| ExpressionUnique Select
| ExpressionDistinct Select
| ExpressionExists Select
| ExpressionOver Expression WindowFrame
| ExpressionCurrentTimestamp
deriving (Int -> Expression -> ShowS
[Expression] -> ShowS
Expression -> String
(Int -> Expression -> ShowS)
-> (Expression -> String)
-> ([Expression] -> ShowS)
-> Show Expression
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Expression] -> ShowS
$cshowList :: [Expression] -> ShowS
show :: Expression -> String
$cshow :: Expression -> String
showsPrec :: Int -> Expression -> ShowS
$cshowsPrec :: Int -> Expression -> ShowS
Show, Expression -> Expression -> Bool
(Expression -> Expression -> Bool)
-> (Expression -> Expression -> Bool) -> Eq Expression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Expression -> Expression -> Bool
$c/= :: Expression -> Expression -> Bool
== :: Expression -> Expression -> Bool
$c== :: Expression -> Expression -> Bool
Eq)
instance IsSql92ExtractFieldSyntax ExtractField where
secondsField :: ExtractField
secondsField = ExtractField
ExtractFieldDateTimeSecond
minutesField :: ExtractField
minutesField = ExtractField
ExtractFieldDateTimeMinute
hourField :: ExtractField
hourField = ExtractField
ExtractFieldDateTimeHour
dayField :: ExtractField
dayField = ExtractField
ExtractFieldDateTimeDay
monthField :: ExtractField
monthField = ExtractField
ExtractFieldDateTimeMonth
yearField :: ExtractField
yearField = ExtractField
ExtractFieldDateTimeYear
instance IsSql92ExpressionSyntax Expression where
type Sql92ExpressionQuantifierSyntax Expression = ComparatorQuantifier
type Sql92ExpressionValueSyntax Expression = Value
type Sql92ExpressionSelectSyntax Expression = Select
type Sql92ExpressionFieldNameSyntax Expression = FieldName
type Sql92ExpressionCastTargetSyntax Expression = DataType
type Expression = ExtractField
valueE :: Sql92ExpressionValueSyntax Expression -> Expression
valueE = Sql92ExpressionValueSyntax Expression -> Expression
Value -> Expression
ExpressionValue
rowE :: [Expression] -> Expression
rowE = [Expression] -> Expression
ExpressionRow
isNullE :: Expression -> Expression
isNullE = Expression -> Expression
ExpressionIsNull
isNotNullE :: Expression -> Expression
isNotNullE = Expression -> Expression
ExpressionIsNotNull
isTrueE :: Expression -> Expression
isTrueE = Expression -> Expression
ExpressionIsTrue
isNotTrueE :: Expression -> Expression
isNotTrueE = Expression -> Expression
ExpressionIsNotTrue
isFalseE :: Expression -> Expression
isFalseE = Expression -> Expression
ExpressionIsFalse
isNotFalseE :: Expression -> Expression
isNotFalseE = Expression -> Expression
ExpressionIsNotFalse
isUnknownE :: Expression -> Expression
isUnknownE = Expression -> Expression
ExpressionIsUnknown
isNotUnknownE :: Expression -> Expression
isNotUnknownE = Expression -> Expression
ExpressionIsNotUnknown
caseE :: [(Expression, Expression)] -> Expression -> Expression
caseE = [(Expression, Expression)] -> Expression -> Expression
ExpressionCase
coalesceE :: [Expression] -> Expression
coalesceE = [Expression] -> Expression
ExpressionCoalesce
nullIfE :: Expression -> Expression -> Expression
nullIfE = Expression -> Expression -> Expression
ExpressionNullIf
positionE :: Expression -> Expression -> Expression
positionE = Expression -> Expression -> Expression
ExpressionPosition
extractE :: Sql92ExpressionExtractFieldSyntax Expression
-> Expression -> Expression
extractE = Sql92ExpressionExtractFieldSyntax Expression
-> Expression -> Expression
ExtractField -> Expression -> Expression
ExpressionExtract
castE :: Expression
-> Sql92ExpressionCastTargetSyntax Expression -> Expression
castE = Expression
-> Sql92ExpressionCastTargetSyntax Expression -> Expression
Expression -> DataType -> Expression
ExpressionCast
fieldE :: Sql92ExpressionFieldNameSyntax Expression -> Expression
fieldE = Sql92ExpressionFieldNameSyntax Expression -> Expression
FieldName -> Expression
ExpressionFieldName
betweenE :: Expression -> Expression -> Expression -> Expression
betweenE = Expression -> Expression -> Expression -> Expression
ExpressionBetween
andE :: Expression -> Expression -> Expression
andE = Text -> Expression -> Expression -> Expression
ExpressionBinOp Text
"AND"
orE :: Expression -> Expression -> Expression
orE = Text -> Expression -> Expression -> Expression
ExpressionBinOp Text
"OR"
eqE :: Maybe (Sql92ExpressionQuantifierSyntax Expression)
-> Expression -> Expression -> Expression
eqE = Text
-> Maybe ComparatorQuantifier
-> Expression
-> Expression
-> Expression
ExpressionCompOp Text
"=="
neqE :: Maybe (Sql92ExpressionQuantifierSyntax Expression)
-> Expression -> Expression -> Expression
neqE = Text
-> Maybe ComparatorQuantifier
-> Expression
-> Expression
-> Expression
ExpressionCompOp Text
"<>"
ltE :: Maybe (Sql92ExpressionQuantifierSyntax Expression)
-> Expression -> Expression -> Expression
ltE = Text
-> Maybe ComparatorQuantifier
-> Expression
-> Expression
-> Expression
ExpressionCompOp Text
"<"
gtE :: Maybe (Sql92ExpressionQuantifierSyntax Expression)
-> Expression -> Expression -> Expression
gtE = Text
-> Maybe ComparatorQuantifier
-> Expression
-> Expression
-> Expression
ExpressionCompOp Text
">"
leE :: Maybe (Sql92ExpressionQuantifierSyntax Expression)
-> Expression -> Expression -> Expression
leE = Text
-> Maybe ComparatorQuantifier
-> Expression
-> Expression
-> Expression
ExpressionCompOp Text
"<="
geE :: Maybe (Sql92ExpressionQuantifierSyntax Expression)
-> Expression -> Expression -> Expression
geE = Text
-> Maybe ComparatorQuantifier
-> Expression
-> Expression
-> Expression
ExpressionCompOp Text
">="
addE :: Expression -> Expression -> Expression
addE = Text -> Expression -> Expression -> Expression
ExpressionBinOp Text
"+"
subE :: Expression -> Expression -> Expression
subE = Text -> Expression -> Expression -> Expression
ExpressionBinOp Text
"-"
mulE :: Expression -> Expression -> Expression
mulE = Text -> Expression -> Expression -> Expression
ExpressionBinOp Text
"*"
divE :: Expression -> Expression -> Expression
divE = Text -> Expression -> Expression -> Expression
ExpressionBinOp Text
"/"
modE :: Expression -> Expression -> Expression
modE = Text -> Expression -> Expression -> Expression
ExpressionBinOp Text
"%"
likeE :: Expression -> Expression -> Expression
likeE = Text -> Expression -> Expression -> Expression
ExpressionBinOp Text
"LIKE"
overlapsE :: Expression -> Expression -> Expression
overlapsE = Text -> Expression -> Expression -> Expression
ExpressionBinOp Text
"OVERLAPS"
notE :: Expression -> Expression
notE = Text -> Expression -> Expression
ExpressionUnOp Text
"NOT"
negateE :: Expression -> Expression
negateE = Text -> Expression -> Expression
ExpressionUnOp Text
"-"
charLengthE :: Expression -> Expression
charLengthE = Expression -> Expression
ExpressionCharLength
octetLengthE :: Expression -> Expression
octetLengthE = Expression -> Expression
ExpressionOctetLength
bitLengthE :: Expression -> Expression
bitLengthE = Expression -> Expression
ExpressionBitLength
absE :: Expression -> Expression
absE = Expression -> Expression
ExpressionAbs
lowerE :: Expression -> Expression
lowerE = Expression -> Expression
ExpressionLower
upperE :: Expression -> Expression
upperE = Expression -> Expression
ExpressionUpper
trimE :: Expression -> Expression
trimE = Expression -> Expression
ExpressionTrim
subqueryE :: Sql92ExpressionSelectSyntax Expression -> Expression
subqueryE = Sql92ExpressionSelectSyntax Expression -> Expression
Select -> Expression
ExpressionSubquery
uniqueE :: Sql92ExpressionSelectSyntax Expression -> Expression
uniqueE = Sql92ExpressionSelectSyntax Expression -> Expression
Select -> Expression
ExpressionUnique
existsE :: Sql92ExpressionSelectSyntax Expression -> Expression
existsE = Sql92ExpressionSelectSyntax Expression -> Expression
Select -> Expression
ExpressionExists
currentTimestampE :: Expression
currentTimestampE = Expression
ExpressionCurrentTimestamp
defaultE :: Expression
defaultE = Expression
ExpressionDefault
inE :: Expression -> [Expression] -> Expression
inE = Expression -> [Expression] -> Expression
ExpressionIn
instance IsSql99FunctionExpressionSyntax Expression where
functionNameE :: Text -> Expression
functionNameE = Text -> Expression
ExpressionNamedFunction
functionCallE :: Expression -> [Expression] -> Expression
functionCallE = Expression -> [Expression] -> Expression
ExpressionFunctionCall
instance IsSql99ExpressionSyntax Expression where
distinctE :: Sql92ExpressionSelectSyntax Expression -> Expression
distinctE = Sql92ExpressionSelectSyntax Expression -> Expression
Select -> Expression
ExpressionDistinct
similarToE :: Expression -> Expression -> Expression
similarToE = Text -> Expression -> Expression -> Expression
ExpressionBinOp Text
"SIMILAR TO"
instanceFieldE :: Expression -> Text -> Expression
instanceFieldE = Expression -> Text -> Expression
ExpressionInstanceField
refFieldE :: Expression -> Text -> Expression
refFieldE = Expression -> Text -> Expression
ExpressionRefField
instance IsSql92AggregationExpressionSyntax Expression where
type Sql92AggregationSetQuantifierSyntax Expression = SetQuantifier
countAllE :: Expression
countAllE = Expression
ExpressionCountAll
countE :: Maybe (Sql92AggregationSetQuantifierSyntax Expression)
-> Expression -> Expression
countE Maybe (Sql92AggregationSetQuantifierSyntax Expression)
q = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"COUNT" Maybe (Sql92AggregationSetQuantifierSyntax Expression)
Maybe SetQuantifier
q ([Expression] -> Expression)
-> (Expression -> [Expression]) -> Expression -> Expression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expression -> [Expression]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
sumE :: Maybe (Sql92AggregationSetQuantifierSyntax Expression)
-> Expression -> Expression
sumE Maybe (Sql92AggregationSetQuantifierSyntax Expression)
q = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"SUM" Maybe (Sql92AggregationSetQuantifierSyntax Expression)
Maybe SetQuantifier
q ([Expression] -> Expression)
-> (Expression -> [Expression]) -> Expression -> Expression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expression -> [Expression]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
minE :: Maybe (Sql92AggregationSetQuantifierSyntax Expression)
-> Expression -> Expression
minE Maybe (Sql92AggregationSetQuantifierSyntax Expression)
q = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"MIN" Maybe (Sql92AggregationSetQuantifierSyntax Expression)
Maybe SetQuantifier
q ([Expression] -> Expression)
-> (Expression -> [Expression]) -> Expression -> Expression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expression -> [Expression]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
maxE :: Maybe (Sql92AggregationSetQuantifierSyntax Expression)
-> Expression -> Expression
maxE Maybe (Sql92AggregationSetQuantifierSyntax Expression)
q = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"MAX" Maybe (Sql92AggregationSetQuantifierSyntax Expression)
Maybe SetQuantifier
q ([Expression] -> Expression)
-> (Expression -> [Expression]) -> Expression -> Expression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expression -> [Expression]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
avgE :: Maybe (Sql92AggregationSetQuantifierSyntax Expression)
-> Expression -> Expression
avgE Maybe (Sql92AggregationSetQuantifierSyntax Expression)
q = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"AVG" Maybe (Sql92AggregationSetQuantifierSyntax Expression)
Maybe SetQuantifier
q ([Expression] -> Expression)
-> (Expression -> [Expression]) -> Expression -> Expression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expression -> [Expression]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
instance IsSql99AggregationExpressionSyntax Expression where
everyE :: Maybe (Sql92AggregationSetQuantifierSyntax Expression)
-> Expression -> Expression
everyE Maybe (Sql92AggregationSetQuantifierSyntax Expression)
q = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"EVERY" Maybe (Sql92AggregationSetQuantifierSyntax Expression)
Maybe SetQuantifier
q ([Expression] -> Expression)
-> (Expression -> [Expression]) -> Expression -> Expression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expression -> [Expression]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
someE :: Maybe (Sql92AggregationSetQuantifierSyntax Expression)
-> Expression -> Expression
someE Maybe (Sql92AggregationSetQuantifierSyntax Expression)
q = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"SOME" Maybe (Sql92AggregationSetQuantifierSyntax Expression)
Maybe SetQuantifier
q ([Expression] -> Expression)
-> (Expression -> [Expression]) -> Expression -> Expression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expression -> [Expression]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
anyE :: Maybe (Sql92AggregationSetQuantifierSyntax Expression)
-> Expression -> Expression
anyE Maybe (Sql92AggregationSetQuantifierSyntax Expression)
q = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"ANY" Maybe (Sql92AggregationSetQuantifierSyntax Expression)
Maybe SetQuantifier
q ([Expression] -> Expression)
-> (Expression -> [Expression]) -> Expression -> Expression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expression -> [Expression]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
instance IsSql2003EnhancedNumericFunctionsExpressionSyntax Expression where
lnE :: Expression -> Expression
lnE = Text -> [Expression] -> Expression
ExpressionBuiltinFunction Text
"LN" ([Expression] -> Expression)
-> (Expression -> [Expression]) -> Expression -> Expression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expression -> [Expression]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
expE :: Expression -> Expression
expE = Text -> [Expression] -> Expression
ExpressionBuiltinFunction Text
"EXP" ([Expression] -> Expression)
-> (Expression -> [Expression]) -> Expression -> Expression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expression -> [Expression]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
sqrtE :: Expression -> Expression
sqrtE = Text -> [Expression] -> Expression
ExpressionBuiltinFunction Text
"SQRT" ([Expression] -> Expression)
-> (Expression -> [Expression]) -> Expression -> Expression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expression -> [Expression]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
ceilE :: Expression -> Expression
ceilE = Text -> [Expression] -> Expression
ExpressionBuiltinFunction Text
"CEIL" ([Expression] -> Expression)
-> (Expression -> [Expression]) -> Expression -> Expression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expression -> [Expression]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
floorE :: Expression -> Expression
floorE = Text -> [Expression] -> Expression
ExpressionBuiltinFunction Text
"FLOOR" ([Expression] -> Expression)
-> (Expression -> [Expression]) -> Expression -> Expression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expression -> [Expression]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
powerE :: Expression -> Expression -> Expression
powerE Expression
a Expression
b = Text -> [Expression] -> Expression
ExpressionBuiltinFunction Text
"POWER" [Expression
a, Expression
b]
instance IsSql2003EnhancedNumericFunctionsAggregationExpressionSyntax Expression where
stddevPopE :: Maybe (Sql92AggregationSetQuantifierSyntax Expression)
-> Expression -> Expression
stddevPopE Maybe (Sql92AggregationSetQuantifierSyntax Expression)
q = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"STDDEV_POP" Maybe (Sql92AggregationSetQuantifierSyntax Expression)
Maybe SetQuantifier
q ([Expression] -> Expression)
-> (Expression -> [Expression]) -> Expression -> Expression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expression -> [Expression]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
stddevSampE :: Maybe (Sql92AggregationSetQuantifierSyntax Expression)
-> Expression -> Expression
stddevSampE Maybe (Sql92AggregationSetQuantifierSyntax Expression)
q = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"STDDEV_SAMP" Maybe (Sql92AggregationSetQuantifierSyntax Expression)
Maybe SetQuantifier
q ([Expression] -> Expression)
-> (Expression -> [Expression]) -> Expression -> Expression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expression -> [Expression]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
varPopE :: Maybe (Sql92AggregationSetQuantifierSyntax Expression)
-> Expression -> Expression
varPopE Maybe (Sql92AggregationSetQuantifierSyntax Expression)
q = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"VAR_POP" Maybe (Sql92AggregationSetQuantifierSyntax Expression)
Maybe SetQuantifier
q ([Expression] -> Expression)
-> (Expression -> [Expression]) -> Expression -> Expression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expression -> [Expression]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
varSampE :: Maybe (Sql92AggregationSetQuantifierSyntax Expression)
-> Expression -> Expression
varSampE Maybe (Sql92AggregationSetQuantifierSyntax Expression)
q = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"VAR_SAMP" Maybe (Sql92AggregationSetQuantifierSyntax Expression)
Maybe SetQuantifier
q ([Expression] -> Expression)
-> (Expression -> [Expression]) -> Expression -> Expression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expression -> [Expression]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
covarPopE :: Maybe (Sql92AggregationSetQuantifierSyntax Expression)
-> Expression -> Expression -> Expression
covarPopE Maybe (Sql92AggregationSetQuantifierSyntax Expression)
q Expression
a Expression
b = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"COVAR_POP" Maybe (Sql92AggregationSetQuantifierSyntax Expression)
Maybe SetQuantifier
q [Expression
a, Expression
b]
covarSampE :: Maybe (Sql92AggregationSetQuantifierSyntax Expression)
-> Expression -> Expression -> Expression
covarSampE Maybe (Sql92AggregationSetQuantifierSyntax Expression)
q Expression
a Expression
b = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"COVAR_SAMP" Maybe (Sql92AggregationSetQuantifierSyntax Expression)
Maybe SetQuantifier
q [Expression
a, Expression
b]
corrE :: Maybe (Sql92AggregationSetQuantifierSyntax Expression)
-> Expression -> Expression -> Expression
corrE Maybe (Sql92AggregationSetQuantifierSyntax Expression)
q Expression
a Expression
b = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"CORR" Maybe (Sql92AggregationSetQuantifierSyntax Expression)
Maybe SetQuantifier
q [Expression
a, Expression
b]
regrSlopeE :: Maybe (Sql92AggregationSetQuantifierSyntax Expression)
-> Expression -> Expression -> Expression
regrSlopeE Maybe (Sql92AggregationSetQuantifierSyntax Expression)
q Expression
a Expression
b = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"REGR_SLOPE" Maybe (Sql92AggregationSetQuantifierSyntax Expression)
Maybe SetQuantifier
q [Expression
a, Expression
b]
regrInterceptE :: Maybe (Sql92AggregationSetQuantifierSyntax Expression)
-> Expression -> Expression -> Expression
regrInterceptE Maybe (Sql92AggregationSetQuantifierSyntax Expression)
q Expression
a Expression
b = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"REGR_INTERCEPT" Maybe (Sql92AggregationSetQuantifierSyntax Expression)
Maybe SetQuantifier
q [Expression
a, Expression
b]
regrCountE :: Maybe (Sql92AggregationSetQuantifierSyntax Expression)
-> Expression -> Expression -> Expression
regrCountE Maybe (Sql92AggregationSetQuantifierSyntax Expression)
q Expression
a Expression
b = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"REGR_COUNT" Maybe (Sql92AggregationSetQuantifierSyntax Expression)
Maybe SetQuantifier
q [Expression
a, Expression
b]
regrRSquaredE :: Maybe (Sql92AggregationSetQuantifierSyntax Expression)
-> Expression -> Expression -> Expression
regrRSquaredE Maybe (Sql92AggregationSetQuantifierSyntax Expression)
q Expression
a Expression
b = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"REGR_R2" Maybe (Sql92AggregationSetQuantifierSyntax Expression)
Maybe SetQuantifier
q [Expression
a, Expression
b]
regrAvgXE :: Maybe (Sql92AggregationSetQuantifierSyntax Expression)
-> Expression -> Expression -> Expression
regrAvgXE Maybe (Sql92AggregationSetQuantifierSyntax Expression)
q Expression
a Expression
b = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"REGR_AVGX" Maybe (Sql92AggregationSetQuantifierSyntax Expression)
Maybe SetQuantifier
q [Expression
a, Expression
b]
regrAvgYE :: Maybe (Sql92AggregationSetQuantifierSyntax Expression)
-> Expression -> Expression -> Expression
regrAvgYE Maybe (Sql92AggregationSetQuantifierSyntax Expression)
q Expression
a Expression
b = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"REGR_AVGY" Maybe (Sql92AggregationSetQuantifierSyntax Expression)
Maybe SetQuantifier
q [Expression
a, Expression
b]
regrSXXE :: Maybe (Sql92AggregationSetQuantifierSyntax Expression)
-> Expression -> Expression -> Expression
regrSXXE Maybe (Sql92AggregationSetQuantifierSyntax Expression)
q Expression
a Expression
b = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"REGR_SXX" Maybe (Sql92AggregationSetQuantifierSyntax Expression)
Maybe SetQuantifier
q [Expression
a, Expression
b]
regrSXYE :: Maybe (Sql92AggregationSetQuantifierSyntax Expression)
-> Expression -> Expression -> Expression
regrSXYE Maybe (Sql92AggregationSetQuantifierSyntax Expression)
q Expression
a Expression
b = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"REGR_SXY" Maybe (Sql92AggregationSetQuantifierSyntax Expression)
Maybe SetQuantifier
q [Expression
a, Expression
b]
regrSYYE :: Maybe (Sql92AggregationSetQuantifierSyntax Expression)
-> Expression -> Expression -> Expression
regrSYYE Maybe (Sql92AggregationSetQuantifierSyntax Expression)
q Expression
a Expression
b = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"REGR_SYY" Maybe (Sql92AggregationSetQuantifierSyntax Expression)
Maybe SetQuantifier
q [Expression
a, Expression
b]
instance IsSql2003NtileExpressionSyntax Expression where
ntileE :: Expression -> Expression
ntileE = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"NTILE" Maybe SetQuantifier
forall a. Maybe a
Nothing ([Expression] -> Expression)
-> (Expression -> [Expression]) -> Expression -> Expression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expression -> [Expression]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
instance IsSql2003LeadAndLagExpressionSyntax Expression where
leadE :: Expression -> Maybe Expression -> Maybe Expression -> Expression
leadE Expression
x Maybe Expression
Nothing Maybe Expression
Nothing = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"LEAD" Maybe SetQuantifier
forall a. Maybe a
Nothing [Expression
x]
leadE Expression
x (Just Expression
y) Maybe Expression
Nothing = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"LEAD" Maybe SetQuantifier
forall a. Maybe a
Nothing [Expression
x, Expression
y]
leadE Expression
x (Just Expression
y) (Just Expression
z) = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"LEAD" Maybe SetQuantifier
forall a. Maybe a
Nothing [Expression
x, Expression
y, Expression
z]
leadE Expression
x Maybe Expression
Nothing (Just Expression
z) = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"LEAD" Maybe SetQuantifier
forall a. Maybe a
Nothing [Expression
x, Value -> Expression
ExpressionValue (Int -> Value
forall a. (Show a, Eq a, Typeable a) => a -> Value
Value (Int
1 :: Int)), Expression
z]
lagE :: Expression -> Maybe Expression -> Maybe Expression -> Expression
lagE Expression
x Maybe Expression
Nothing Maybe Expression
Nothing = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"LAG" Maybe SetQuantifier
forall a. Maybe a
Nothing [Expression
x]
lagE Expression
x (Just Expression
y) Maybe Expression
Nothing = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"LAG" Maybe SetQuantifier
forall a. Maybe a
Nothing [Expression
x, Expression
y]
lagE Expression
x (Just Expression
y) (Just Expression
z) = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"LAG" Maybe SetQuantifier
forall a. Maybe a
Nothing [Expression
x, Expression
y, Expression
z]
lagE Expression
x Maybe Expression
Nothing (Just Expression
z) = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"LAG" Maybe SetQuantifier
forall a. Maybe a
Nothing [Expression
x, Value -> Expression
ExpressionValue (Int -> Value
forall a. (Show a, Eq a, Typeable a) => a -> Value
Value (Int
1 :: Int)), Expression
z]
instance IsSql2003NthValueExpressionSyntax Expression where
nthValueE :: Expression -> Expression -> Expression
nthValueE Expression
a Expression
b = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"NTH_VALUE" Maybe SetQuantifier
forall a. Maybe a
Nothing [Expression
a, Expression
b]
instance IsSql2003ExpressionSyntax Expression where
type Sql2003ExpressionWindowFrameSyntax Expression = WindowFrame
overE :: Expression
-> Sql2003ExpressionWindowFrameSyntax Expression -> Expression
overE = Expression
-> Sql2003ExpressionWindowFrameSyntax Expression -> Expression
Expression -> WindowFrame -> Expression
ExpressionOver
rowNumberE :: Expression
rowNumberE = Text -> Maybe SetQuantifier -> [Expression] -> Expression
ExpressionAgg Text
"ROW_NUMBER" Maybe SetQuantifier
forall a. Maybe a
Nothing []
newtype Projection
= ProjExprs [ (Expression, Maybe Text ) ]
deriving (Int -> Projection -> ShowS
[Projection] -> ShowS
Projection -> String
(Int -> Projection -> ShowS)
-> (Projection -> String)
-> ([Projection] -> ShowS)
-> Show Projection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Projection] -> ShowS
$cshowList :: [Projection] -> ShowS
show :: Projection -> String
$cshow :: Projection -> String
showsPrec :: Int -> Projection -> ShowS
$cshowsPrec :: Int -> Projection -> ShowS
Show, Projection -> Projection -> Bool
(Projection -> Projection -> Bool)
-> (Projection -> Projection -> Bool) -> Eq Projection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Projection -> Projection -> Bool
$c/= :: Projection -> Projection -> Bool
== :: Projection -> Projection -> Bool
$c== :: Projection -> Projection -> Bool
Eq)
instance IsSql92ProjectionSyntax Projection where
type Sql92ProjectionExpressionSyntax Projection = Expression
projExprs :: [(Sql92ProjectionExpressionSyntax Projection, Maybe Text)]
-> Projection
projExprs = [(Sql92ProjectionExpressionSyntax Projection, Maybe Text)]
-> Projection
[(Expression, Maybe Text)] -> Projection
ProjExprs
data Ordering
= OrderingAsc Expression
| OrderingDesc Expression
deriving (Int -> Ordering -> ShowS
[Ordering] -> ShowS
Ordering -> String
(Int -> Ordering -> ShowS)
-> (Ordering -> String) -> ([Ordering] -> ShowS) -> Show Ordering
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Ordering] -> ShowS
$cshowList :: [Ordering] -> ShowS
show :: Ordering -> String
$cshow :: Ordering -> String
showsPrec :: Int -> Ordering -> ShowS
$cshowsPrec :: Int -> Ordering -> ShowS
Show, Ordering -> Ordering -> Bool
(Ordering -> Ordering -> Bool)
-> (Ordering -> Ordering -> Bool) -> Eq Ordering
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Ordering -> Ordering -> Bool
$c/= :: Ordering -> Ordering -> Bool
== :: Ordering -> Ordering -> Bool
$c== :: Ordering -> Ordering -> Bool
Eq)
instance IsSql92OrderingSyntax Ordering where
type Sql92OrderingExpressionSyntax Ordering = Expression
ascOrdering :: Sql92OrderingExpressionSyntax Ordering -> Ordering
ascOrdering = Sql92OrderingExpressionSyntax Ordering -> Ordering
Expression -> Ordering
OrderingAsc
descOrdering :: Sql92OrderingExpressionSyntax Ordering -> Ordering
descOrdering = Sql92OrderingExpressionSyntax Ordering -> Ordering
Expression -> Ordering
OrderingDesc
newtype Grouping = Grouping [ Expression ] deriving (Int -> Grouping -> ShowS
[Grouping] -> ShowS
Grouping -> String
(Int -> Grouping -> ShowS)
-> (Grouping -> String) -> ([Grouping] -> ShowS) -> Show Grouping
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Grouping] -> ShowS
$cshowList :: [Grouping] -> ShowS
show :: Grouping -> String
$cshow :: Grouping -> String
showsPrec :: Int -> Grouping -> ShowS
$cshowsPrec :: Int -> Grouping -> ShowS
Show, Grouping -> Grouping -> Bool
(Grouping -> Grouping -> Bool)
-> (Grouping -> Grouping -> Bool) -> Eq Grouping
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Grouping -> Grouping -> Bool
$c/= :: Grouping -> Grouping -> Bool
== :: Grouping -> Grouping -> Bool
$c== :: Grouping -> Grouping -> Bool
Eq)
instance IsSql92GroupingSyntax Grouping where
type Sql92GroupingExpressionSyntax Grouping = Expression
groupByExpressions :: [Sql92GroupingExpressionSyntax Grouping] -> Grouping
groupByExpressions = [Sql92GroupingExpressionSyntax Grouping] -> Grouping
[Expression] -> Grouping
Grouping
data TableName = TableName (Maybe Text) Text
deriving (Int -> TableName -> ShowS
[TableName] -> ShowS
TableName -> String
(Int -> TableName -> ShowS)
-> (TableName -> String)
-> ([TableName] -> ShowS)
-> Show TableName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TableName] -> ShowS
$cshowList :: [TableName] -> ShowS
show :: TableName -> String
$cshow :: TableName -> String
showsPrec :: Int -> TableName -> ShowS
$cshowsPrec :: Int -> TableName -> ShowS
Show, TableName -> TableName -> Bool
(TableName -> TableName -> Bool)
-> (TableName -> TableName -> Bool) -> Eq TableName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TableName -> TableName -> Bool
$c/= :: TableName -> TableName -> Bool
== :: TableName -> TableName -> Bool
$c== :: TableName -> TableName -> Bool
Eq, Eq TableName
Eq TableName
-> (TableName -> TableName -> Ordering)
-> (TableName -> TableName -> Bool)
-> (TableName -> TableName -> Bool)
-> (TableName -> TableName -> Bool)
-> (TableName -> TableName -> Bool)
-> (TableName -> TableName -> TableName)
-> (TableName -> TableName -> TableName)
-> Ord TableName
TableName -> TableName -> Bool
TableName -> TableName -> Ordering
TableName -> TableName -> TableName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TableName -> TableName -> TableName
$cmin :: TableName -> TableName -> TableName
max :: TableName -> TableName -> TableName
$cmax :: TableName -> TableName -> TableName
>= :: TableName -> TableName -> Bool
$c>= :: TableName -> TableName -> Bool
> :: TableName -> TableName -> Bool
$c> :: TableName -> TableName -> Bool
<= :: TableName -> TableName -> Bool
$c<= :: TableName -> TableName -> Bool
< :: TableName -> TableName -> Bool
$c< :: TableName -> TableName -> Bool
compare :: TableName -> TableName -> Ordering
$ccompare :: TableName -> TableName -> Ordering
$cp1Ord :: Eq TableName
Ord)
instance IsSql92TableNameSyntax TableName where
tableName :: Maybe Text -> Text -> TableName
tableName = Maybe Text -> Text -> TableName
TableName
data TableSource
= TableNamed TableName
| TableFromSubSelect Select
| TableFromValues [ [ Expression ] ]
deriving (Int -> TableSource -> ShowS
[TableSource] -> ShowS
TableSource -> String
(Int -> TableSource -> ShowS)
-> (TableSource -> String)
-> ([TableSource] -> ShowS)
-> Show TableSource
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TableSource] -> ShowS
$cshowList :: [TableSource] -> ShowS
show :: TableSource -> String
$cshow :: TableSource -> String
showsPrec :: Int -> TableSource -> ShowS
$cshowsPrec :: Int -> TableSource -> ShowS
Show, TableSource -> TableSource -> Bool
(TableSource -> TableSource -> Bool)
-> (TableSource -> TableSource -> Bool) -> Eq TableSource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TableSource -> TableSource -> Bool
$c/= :: TableSource -> TableSource -> Bool
== :: TableSource -> TableSource -> Bool
$c== :: TableSource -> TableSource -> Bool
Eq)
instance IsSql92TableSourceSyntax TableSource where
type Sql92TableSourceSelectSyntax TableSource = Select
type Sql92TableSourceExpressionSyntax TableSource = Expression
type Sql92TableSourceTableNameSyntax TableSource = TableName
tableNamed :: Sql92TableSourceTableNameSyntax TableSource -> TableSource
tableNamed = Sql92TableSourceTableNameSyntax TableSource -> TableSource
TableName -> TableSource
TableNamed
tableFromSubSelect :: Sql92TableSourceSelectSyntax TableSource -> TableSource
tableFromSubSelect = Sql92TableSourceSelectSyntax TableSource -> TableSource
Select -> TableSource
TableFromSubSelect
tableFromValues :: [[Sql92TableSourceExpressionSyntax TableSource]] -> TableSource
tableFromValues = [[Sql92TableSourceExpressionSyntax TableSource]] -> TableSource
[[Expression]] -> TableSource
TableFromValues
data From
= FromTable TableSource (Maybe (Text, Maybe [Text]))
| InnerJoin From From (Maybe Expression)
| LeftJoin From From (Maybe Expression)
| RightJoin From From (Maybe Expression)
| OuterJoin From From (Maybe Expression)
deriving (Int -> From -> ShowS
[From] -> ShowS
From -> String
(Int -> From -> ShowS)
-> (From -> String) -> ([From] -> ShowS) -> Show From
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [From] -> ShowS
$cshowList :: [From] -> ShowS
show :: From -> String
$cshow :: From -> String
showsPrec :: Int -> From -> ShowS
$cshowsPrec :: Int -> From -> ShowS
Show, From -> From -> Bool
(From -> From -> Bool) -> (From -> From -> Bool) -> Eq From
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: From -> From -> Bool
$c/= :: From -> From -> Bool
== :: From -> From -> Bool
$c== :: From -> From -> Bool
Eq)
instance IsSql92FromSyntax From where
type Sql92FromTableSourceSyntax From = TableSource
type Sql92FromExpressionSyntax From = Expression
fromTable :: Sql92FromTableSourceSyntax From
-> Maybe (Text, Maybe [Text]) -> From
fromTable = Sql92FromTableSourceSyntax From
-> Maybe (Text, Maybe [Text]) -> From
TableSource -> Maybe (Text, Maybe [Text]) -> From
FromTable
innerJoin :: From -> From -> Maybe (Sql92FromExpressionSyntax From) -> From
innerJoin = From -> From -> Maybe (Sql92FromExpressionSyntax From) -> From
From -> From -> Maybe Expression -> From
InnerJoin
leftJoin :: From -> From -> Maybe (Sql92FromExpressionSyntax From) -> From
leftJoin = From -> From -> Maybe (Sql92FromExpressionSyntax From) -> From
From -> From -> Maybe Expression -> From
LeftJoin
rightJoin :: From -> From -> Maybe (Sql92FromExpressionSyntax From) -> From
rightJoin = From -> From -> Maybe (Sql92FromExpressionSyntax From) -> From
From -> From -> Maybe Expression -> From
RightJoin
data Value where
Value :: (Show a, Eq a, Typeable a) => a -> Value
#define VALUE_SYNTAX_INSTANCE(ty) instance HasSqlValueSyntax Value ty where { sqlValueSyntax = Value }
VALUE_SYNTAX_INSTANCE(Int16)
VALUE_SYNTAX_INSTANCE(Int32)
VALUE_SYNTAX_INSTANCE(Int64)
VALUE_SYNTAX_INSTANCE(Word16)
VALUE_SYNTAX_INSTANCE(Word32)
VALUE_SYNTAX_INSTANCE(Word64)
VALUE_SYNTAX_INSTANCE(Integer)
VALUE_SYNTAX_INSTANCE(String)
VALUE_SYNTAX_INSTANCE(Text)
VALUE_SYNTAX_INSTANCE(ByteString)
VALUE_SYNTAX_INSTANCE(LocalTime)
VALUE_SYNTAX_INSTANCE(UTCTime)
VALUE_SYNTAX_INSTANCE(Day)
VALUE_SYNTAX_INSTANCE(TimeOfDay)
VALUE_SYNTAX_INSTANCE(SqlNull)
VALUE_SYNTAX_INSTANCE(Double)
VALUE_SYNTAX_INSTANCE(Bool)
instance TypeError (PreferExplicitSize Int Int32) => HasSqlValueSyntax Value Int where
sqlValueSyntax :: Int -> Value
sqlValueSyntax = Int -> Value
forall a. (Show a, Eq a, Typeable a) => a -> Value
Value
instance TypeError (PreferExplicitSize Word Word32) => HasSqlValueSyntax Value Word where
sqlValueSyntax :: Word -> Value
sqlValueSyntax = Word -> Value
forall a. (Show a, Eq a, Typeable a) => a -> Value
Value
instance HasSqlValueSyntax Value x => HasSqlValueSyntax Value (Maybe x) where
sqlValueSyntax :: Maybe x -> Value
sqlValueSyntax (Just x
x) = x -> Value
forall expr ty. HasSqlValueSyntax expr ty => ty -> expr
sqlValueSyntax x
x
sqlValueSyntax Maybe x
Nothing = SqlNull -> Value
forall expr ty. HasSqlValueSyntax expr ty => ty -> expr
sqlValueSyntax SqlNull
SqlNull
instance Eq Value where
Value a
a == :: Value -> Value -> Bool
== Value a
b =
case a -> Maybe a
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a
a of
Just a
a' -> a
a' a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
b
Maybe a
Nothing -> Bool
False
instance Show Value where
showsPrec :: Int -> Value -> ShowS
showsPrec Int
prec (Value a
a) =
Bool -> ShowS -> ShowS
showParen (Int
prec Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
app_prec) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$
(String
"Value " String -> ShowS
forall a. [a] -> [a] -> [a]
++ )ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> a -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec (Int
app_prec Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) a
a
where app_prec :: Int
app_prec = Int
10
data WindowFrame
= WindowFrame
{ WindowFrame -> Maybe [Expression]
windowFramePartitions :: Maybe [Expression]
, WindowFrame -> Maybe [Ordering]
windowFrameOrdering :: Maybe [Ordering]
, WindowFrame -> Maybe WindowFrameBounds
windowFrameBounds :: Maybe WindowFrameBounds
} deriving (Int -> WindowFrame -> ShowS
[WindowFrame] -> ShowS
WindowFrame -> String
(Int -> WindowFrame -> ShowS)
-> (WindowFrame -> String)
-> ([WindowFrame] -> ShowS)
-> Show WindowFrame
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WindowFrame] -> ShowS
$cshowList :: [WindowFrame] -> ShowS
show :: WindowFrame -> String
$cshow :: WindowFrame -> String
showsPrec :: Int -> WindowFrame -> ShowS
$cshowsPrec :: Int -> WindowFrame -> ShowS
Show, WindowFrame -> WindowFrame -> Bool
(WindowFrame -> WindowFrame -> Bool)
-> (WindowFrame -> WindowFrame -> Bool) -> Eq WindowFrame
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WindowFrame -> WindowFrame -> Bool
$c/= :: WindowFrame -> WindowFrame -> Bool
== :: WindowFrame -> WindowFrame -> Bool
$c== :: WindowFrame -> WindowFrame -> Bool
Eq)
instance IsSql2003WindowFrameSyntax WindowFrame where
type Sql2003WindowFrameExpressionSyntax WindowFrame = Expression
type Sql2003WindowFrameOrderingSyntax WindowFrame = Ordering
type Sql2003WindowFrameBoundsSyntax WindowFrame = WindowFrameBounds
frameSyntax :: Maybe [Sql2003WindowFrameExpressionSyntax WindowFrame]
-> Maybe [Sql2003WindowFrameOrderingSyntax WindowFrame]
-> Maybe (Sql2003WindowFrameBoundsSyntax WindowFrame)
-> WindowFrame
frameSyntax = Maybe [Sql2003WindowFrameExpressionSyntax WindowFrame]
-> Maybe [Sql2003WindowFrameOrderingSyntax WindowFrame]
-> Maybe (Sql2003WindowFrameBoundsSyntax WindowFrame)
-> WindowFrame
Maybe [Expression]
-> Maybe [Ordering] -> Maybe WindowFrameBounds -> WindowFrame
WindowFrame
data WindowFrameBounds
= WindowFrameBounds
{ WindowFrameBounds -> WindowFrameBound
boundsFrom :: WindowFrameBound
, WindowFrameBounds -> Maybe WindowFrameBound
boundsTo :: Maybe WindowFrameBound
} deriving (Int -> WindowFrameBounds -> ShowS
[WindowFrameBounds] -> ShowS
WindowFrameBounds -> String
(Int -> WindowFrameBounds -> ShowS)
-> (WindowFrameBounds -> String)
-> ([WindowFrameBounds] -> ShowS)
-> Show WindowFrameBounds
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WindowFrameBounds] -> ShowS
$cshowList :: [WindowFrameBounds] -> ShowS
show :: WindowFrameBounds -> String
$cshow :: WindowFrameBounds -> String
showsPrec :: Int -> WindowFrameBounds -> ShowS
$cshowsPrec :: Int -> WindowFrameBounds -> ShowS
Show, WindowFrameBounds -> WindowFrameBounds -> Bool
(WindowFrameBounds -> WindowFrameBounds -> Bool)
-> (WindowFrameBounds -> WindowFrameBounds -> Bool)
-> Eq WindowFrameBounds
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WindowFrameBounds -> WindowFrameBounds -> Bool
$c/= :: WindowFrameBounds -> WindowFrameBounds -> Bool
== :: WindowFrameBounds -> WindowFrameBounds -> Bool
$c== :: WindowFrameBounds -> WindowFrameBounds -> Bool
Eq)
instance IsSql2003WindowFrameBoundsSyntax WindowFrameBounds where
type Sql2003WindowFrameBoundsBoundSyntax WindowFrameBounds = WindowFrameBound
fromToBoundSyntax :: Sql2003WindowFrameBoundsBoundSyntax WindowFrameBounds
-> Maybe (Sql2003WindowFrameBoundsBoundSyntax WindowFrameBounds)
-> WindowFrameBounds
fromToBoundSyntax = Sql2003WindowFrameBoundsBoundSyntax WindowFrameBounds
-> Maybe (Sql2003WindowFrameBoundsBoundSyntax WindowFrameBounds)
-> WindowFrameBounds
WindowFrameBound -> Maybe WindowFrameBound -> WindowFrameBounds
WindowFrameBounds
data WindowFrameBound
= WindowFrameUnbounded
| WindowFrameBoundNRows Int
deriving (Int -> WindowFrameBound -> ShowS
[WindowFrameBound] -> ShowS
WindowFrameBound -> String
(Int -> WindowFrameBound -> ShowS)
-> (WindowFrameBound -> String)
-> ([WindowFrameBound] -> ShowS)
-> Show WindowFrameBound
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WindowFrameBound] -> ShowS
$cshowList :: [WindowFrameBound] -> ShowS
show :: WindowFrameBound -> String
$cshow :: WindowFrameBound -> String
showsPrec :: Int -> WindowFrameBound -> ShowS
$cshowsPrec :: Int -> WindowFrameBound -> ShowS
Show, WindowFrameBound -> WindowFrameBound -> Bool
(WindowFrameBound -> WindowFrameBound -> Bool)
-> (WindowFrameBound -> WindowFrameBound -> Bool)
-> Eq WindowFrameBound
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WindowFrameBound -> WindowFrameBound -> Bool
$c/= :: WindowFrameBound -> WindowFrameBound -> Bool
== :: WindowFrameBound -> WindowFrameBound -> Bool
$c== :: WindowFrameBound -> WindowFrameBound -> Bool
Eq)
instance IsSql2003WindowFrameBoundSyntax WindowFrameBound where
unboundedSyntax :: WindowFrameBound
unboundedSyntax = WindowFrameBound
WindowFrameUnbounded
nrowsBoundSyntax :: Int -> WindowFrameBound
nrowsBoundSyntax = Int -> WindowFrameBound
WindowFrameBoundNRows