| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Hydra.Langs.Sql.Ansi
Description
A subset of ANSI SQL:2003, capturing selected productions of the BNF grammar provided at https://ronsavage.github.io/SQL/sql-2003-2.bnf.html, which is based on the Final Committee Draft (FCD) of ISO/IEC 9075-2:2003
Documentation
newtype ApproximateNumericLiteral Source #
Constructors
| ApproximateNumericLiteral | |
Fields | |
Instances
data BinaryStringLiteral Source #
Constructors
| BinaryStringLiteral | |
Instances
newtype CharacterStringLiteral Source #
Constructors
| CharacterStringLiteral | |
Fields | |
Instances
newtype ColumnName Source #
Constructors
| ColumnName | |
Fields | |
Instances
| Read ColumnName Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS ColumnName # readList :: ReadS [ColumnName] # readPrec :: ReadPrec ColumnName # readListPrec :: ReadPrec [ColumnName] # | |
| Show ColumnName Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> ColumnName -> ShowS # show :: ColumnName -> String # showList :: [ColumnName] -> ShowS # | |
| Eq ColumnName Source # | |
Defined in Hydra.Langs.Sql.Ansi | |
| Ord ColumnName Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: ColumnName -> ColumnName -> Ordering # (<) :: ColumnName -> ColumnName -> Bool # (<=) :: ColumnName -> ColumnName -> Bool # (>) :: ColumnName -> ColumnName -> Bool # (>=) :: ColumnName -> ColumnName -> Bool # max :: ColumnName -> ColumnName -> ColumnName # min :: ColumnName -> ColumnName -> ColumnName # | |
_ColumnName :: Name Source #
data DateString Source #
Constructors
| DateString | |
Instances
| Read DateString Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS DateString # readList :: ReadS [DateString] # readPrec :: ReadPrec DateString # readListPrec :: ReadPrec [DateString] # | |
| Show DateString Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> DateString -> ShowS # show :: DateString -> String # showList :: [DateString] -> ShowS # | |
| Eq DateString Source # | |
Defined in Hydra.Langs.Sql.Ansi | |
| Ord DateString Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: DateString -> DateString -> Ordering # (<) :: DateString -> DateString -> Bool # (<=) :: DateString -> DateString -> Bool # (>) :: DateString -> DateString -> Bool # (>=) :: DateString -> DateString -> Bool # max :: DateString -> DateString -> DateString # min :: DateString -> DateString -> DateString # | |
_DateString :: Name Source #
newtype DomainName Source #
Constructors
| DomainName | |
Fields | |
Instances
| Read DomainName Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS DomainName # readList :: ReadS [DomainName] # readPrec :: ReadPrec DomainName # readListPrec :: ReadPrec [DomainName] # | |
| Show DomainName Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> DomainName -> ShowS # show :: DomainName -> String # showList :: [DomainName] -> ShowS # | |
| Eq DomainName Source # | |
Defined in Hydra.Langs.Sql.Ansi | |
| Ord DomainName Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: DomainName -> DomainName -> Ordering # (<) :: DomainName -> DomainName -> Bool # (<=) :: DomainName -> DomainName -> Bool # (>) :: DomainName -> DomainName -> Bool # (>=) :: DomainName -> DomainName -> Bool # max :: DomainName -> DomainName -> DomainName # min :: DomainName -> DomainName -> DomainName # | |
_DomainName :: Name Source #
newtype ExactNumericLiteral Source #
Constructors
| ExactNumericLiteral | |
Fields | |
Instances
newtype LeftBracketOrTrigraph Source #
Constructors
| LeftBracketOrTrigraph | |
Fields | |
Instances
newtype RightBracketOrTrigraph Source #
Constructors
| RightBracketOrTrigraph | |
Fields | |
Instances
data NationalCharacterStringLiteral Source #
Constructors
| NationalCharacterStringLiteral | |
Instances
newtype PathResolvedUserDefinedTypeName Source #
Constructors
| PathResolvedUserDefinedTypeName | |
Fields | |
Instances
Constructors
| TableName | |
Fields | |
Instances
| Read TableName Source # | |
| Show TableName Source # | |
| Eq TableName Source # | |
| Ord TableName Source # | |
_TableName :: Name Source #
data TimeString Source #
Constructors
| TimeString | |
Instances
| Read TimeString Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS TimeString # readList :: ReadS [TimeString] # readPrec :: ReadPrec TimeString # readListPrec :: ReadPrec [TimeString] # | |
| Show TimeString Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> TimeString -> ShowS # show :: TimeString -> String # showList :: [TimeString] -> ShowS # | |
| Eq TimeString Source # | |
Defined in Hydra.Langs.Sql.Ansi | |
| Ord TimeString Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: TimeString -> TimeString -> Ordering # (<) :: TimeString -> TimeString -> Bool # (<=) :: TimeString -> TimeString -> Bool # (>) :: TimeString -> TimeString -> Bool # (>=) :: TimeString -> TimeString -> Bool # max :: TimeString -> TimeString -> TimeString # min :: TimeString -> TimeString -> TimeString # | |
_TimeString :: Name Source #
data TimestampLiteral Source #
Constructors
| TimestampLiteral | |
Instances
| Read TimestampLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS TimestampLiteral # readList :: ReadS [TimestampLiteral] # | |
| Show TimestampLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> TimestampLiteral -> ShowS # show :: TimestampLiteral -> String # showList :: [TimestampLiteral] -> ShowS # | |
| Eq TimestampLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: TimestampLiteral -> TimestampLiteral -> Bool # (/=) :: TimestampLiteral -> TimestampLiteral -> Bool # | |
| Ord TimestampLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: TimestampLiteral -> TimestampLiteral -> Ordering # (<) :: TimestampLiteral -> TimestampLiteral -> Bool # (<=) :: TimestampLiteral -> TimestampLiteral -> Bool # (>) :: TimestampLiteral -> TimestampLiteral -> Bool # (>=) :: TimestampLiteral -> TimestampLiteral -> Bool # max :: TimestampLiteral -> TimestampLiteral -> TimestampLiteral # min :: TimestampLiteral -> TimestampLiteral -> TimestampLiteral # | |
data UnicodeCharacterStringLiteral Source #
Constructors
| UnicodeCharacterStringLiteral | |
Instances
newtype UnsignedInteger Source #
Constructors
| UnsignedInteger | |
Fields | |
Instances
| Read UnsignedInteger Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS UnsignedInteger # readList :: ReadS [UnsignedInteger] # | |
| Show UnsignedInteger Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> UnsignedInteger -> ShowS # show :: UnsignedInteger -> String # showList :: [UnsignedInteger] -> ShowS # | |
| Eq UnsignedInteger Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: UnsignedInteger -> UnsignedInteger -> Bool # (/=) :: UnsignedInteger -> UnsignedInteger -> Bool # | |
| Ord UnsignedInteger Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: UnsignedInteger -> UnsignedInteger -> Ordering # (<) :: UnsignedInteger -> UnsignedInteger -> Bool # (<=) :: UnsignedInteger -> UnsignedInteger -> Bool # (>) :: UnsignedInteger -> UnsignedInteger -> Bool # (>=) :: UnsignedInteger -> UnsignedInteger -> Bool # max :: UnsignedInteger -> UnsignedInteger -> UnsignedInteger # min :: UnsignedInteger -> UnsignedInteger -> UnsignedInteger # | |
data ApproximateNumericType Source #
Constructors
| ApproximateNumericTypeFloat (Maybe Precision) | |
| ApproximateNumericTypeReal | |
| ApproximateNumericTypeDouble |
Instances
newtype ArrayElement Source #
Constructors
| ArrayElement | |
Fields | |
Instances
| Read ArrayElement Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS ArrayElement # readList :: ReadS [ArrayElement] # | |
| Show ArrayElement Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> ArrayElement -> ShowS # show :: ArrayElement -> String # showList :: [ArrayElement] -> ShowS # | |
| Eq ArrayElement Source # | |
Defined in Hydra.Langs.Sql.Ansi | |
| Ord ArrayElement Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: ArrayElement -> ArrayElement -> Ordering # (<) :: ArrayElement -> ArrayElement -> Bool # (<=) :: ArrayElement -> ArrayElement -> Bool # (>) :: ArrayElement -> ArrayElement -> Bool # (>=) :: ArrayElement -> ArrayElement -> Bool # max :: ArrayElement -> ArrayElement -> ArrayElement # min :: ArrayElement -> ArrayElement -> ArrayElement # | |
_ArrayElement :: Name Source #
data ArrayElementList Source #
Constructors
| ArrayElementList | |
Fields | |
Instances
| Read ArrayElementList Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS ArrayElementList # readList :: ReadS [ArrayElementList] # | |
| Show ArrayElementList Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> ArrayElementList -> ShowS # show :: ArrayElementList -> String # showList :: [ArrayElementList] -> ShowS # | |
| Eq ArrayElementList Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: ArrayElementList -> ArrayElementList -> Bool # (/=) :: ArrayElementList -> ArrayElementList -> Bool # | |
| Ord ArrayElementList Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: ArrayElementList -> ArrayElementList -> Ordering # (<) :: ArrayElementList -> ArrayElementList -> Bool # (<=) :: ArrayElementList -> ArrayElementList -> Bool # (>) :: ArrayElementList -> ArrayElementList -> Bool # (>=) :: ArrayElementList -> ArrayElementList -> Bool # max :: ArrayElementList -> ArrayElementList -> ArrayElementList # min :: ArrayElementList -> ArrayElementList -> ArrayElementList # | |
data ArrayElementReference Source #
Constructors
| ArrayElementReference | |
Instances
Constructors
| ArrayType | |
Instances
| Read ArrayType Source # | |
| Show ArrayType Source # | |
| Eq ArrayType Source # | |
| Ord ArrayType Source # | |
_ArrayType :: Name Source #
data ArrayValueConstructor Source #
Constructors
| ArrayValueConstructorEnumeration ArrayValueConstructorByEnumeration | |
| ArrayValueConstructorQuery ArrayValueConstructorByQuery |
Instances
data ArrayValueConstructorByQuery Source #
Constructors
| ArrayValueConstructorByQuery | |
Instances
data ArrayValueConstructorByEnumeration Source #
Constructors
| ArrayValueConstructorByEnumeration | |
Instances
data ArrayValueExpression Source #
Constructors
| ArrayValueExpression | |
Instances
data AsSubqueryClause Source #
Constructors
| AsSubqueryClause | |
Instances
| Read AsSubqueryClause Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS AsSubqueryClause # readList :: ReadS [AsSubqueryClause] # | |
| Show AsSubqueryClause Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> AsSubqueryClause -> ShowS # show :: AsSubqueryClause -> String # showList :: [AsSubqueryClause] -> ShowS # | |
| Eq AsSubqueryClause Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: AsSubqueryClause -> AsSubqueryClause -> Bool # (/=) :: AsSubqueryClause -> AsSubqueryClause -> Bool # | |
| Ord AsSubqueryClause Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: AsSubqueryClause -> AsSubqueryClause -> Ordering # (<) :: AsSubqueryClause -> AsSubqueryClause -> Bool # (<=) :: AsSubqueryClause -> AsSubqueryClause -> Bool # (>) :: AsSubqueryClause -> AsSubqueryClause -> Bool # (>=) :: AsSubqueryClause -> AsSubqueryClause -> Bool # max :: AsSubqueryClause -> AsSubqueryClause -> AsSubqueryClause # min :: AsSubqueryClause -> AsSubqueryClause -> AsSubqueryClause # | |
data AttributeOrMethodReference Source #
Constructors
| AttributeOrMethodReference | |
Instances
data BinaryLargeObjectStringType Source #
Constructors
| BinaryLargeObjectStringTypeBinary (Maybe LargeObjectLength) | |
| BinaryLargeObjectStringTypeBlob (Maybe LargeObjectLength) |
Instances
data BooleanFactor Source #
Constructors
| BooleanFactor | |
Fields | |
Instances
| Read BooleanFactor Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS BooleanFactor # readList :: ReadS [BooleanFactor] # | |
| Show BooleanFactor Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> BooleanFactor -> ShowS # show :: BooleanFactor -> String # showList :: [BooleanFactor] -> ShowS # | |
| Eq BooleanFactor Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: BooleanFactor -> BooleanFactor -> Bool # (/=) :: BooleanFactor -> BooleanFactor -> Bool # | |
| Ord BooleanFactor Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: BooleanFactor -> BooleanFactor -> Ordering # (<) :: BooleanFactor -> BooleanFactor -> Bool # (<=) :: BooleanFactor -> BooleanFactor -> Bool # (>) :: BooleanFactor -> BooleanFactor -> Bool # (>=) :: BooleanFactor -> BooleanFactor -> Bool # max :: BooleanFactor -> BooleanFactor -> BooleanFactor # min :: BooleanFactor -> BooleanFactor -> BooleanFactor # | |
data BooleanLiteral Source #
Instances
| Read BooleanLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS BooleanLiteral # readList :: ReadS [BooleanLiteral] # | |
| Show BooleanLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> BooleanLiteral -> ShowS # show :: BooleanLiteral -> String # showList :: [BooleanLiteral] -> ShowS # | |
| Eq BooleanLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: BooleanLiteral -> BooleanLiteral -> Bool # (/=) :: BooleanLiteral -> BooleanLiteral -> Bool # | |
| Ord BooleanLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: BooleanLiteral -> BooleanLiteral -> Ordering # (<) :: BooleanLiteral -> BooleanLiteral -> Bool # (<=) :: BooleanLiteral -> BooleanLiteral -> Bool # (>) :: BooleanLiteral -> BooleanLiteral -> Bool # (>=) :: BooleanLiteral -> BooleanLiteral -> Bool # max :: BooleanLiteral -> BooleanLiteral -> BooleanLiteral # min :: BooleanLiteral -> BooleanLiteral -> BooleanLiteral # | |
data BooleanPredicand Source #
Constructors
| BooleanPredicand | |
Instances
| Read BooleanPredicand Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS BooleanPredicand # readList :: ReadS [BooleanPredicand] # | |
| Show BooleanPredicand Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> BooleanPredicand -> ShowS # show :: BooleanPredicand -> String # showList :: [BooleanPredicand] -> ShowS # | |
| Eq BooleanPredicand Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: BooleanPredicand -> BooleanPredicand -> Bool # (/=) :: BooleanPredicand -> BooleanPredicand -> Bool # | |
| Ord BooleanPredicand Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: BooleanPredicand -> BooleanPredicand -> Ordering # (<) :: BooleanPredicand -> BooleanPredicand -> Bool # (<=) :: BooleanPredicand -> BooleanPredicand -> Bool # (>) :: BooleanPredicand -> BooleanPredicand -> Bool # (>=) :: BooleanPredicand -> BooleanPredicand -> Bool # max :: BooleanPredicand -> BooleanPredicand -> BooleanPredicand # min :: BooleanPredicand -> BooleanPredicand -> BooleanPredicand # | |
data BooleanPrimary Source #
Instances
| Read BooleanPrimary Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS BooleanPrimary # readList :: ReadS [BooleanPrimary] # | |
| Show BooleanPrimary Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> BooleanPrimary -> ShowS # show :: BooleanPrimary -> String # showList :: [BooleanPrimary] -> ShowS # | |
| Eq BooleanPrimary Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: BooleanPrimary -> BooleanPrimary -> Bool # (/=) :: BooleanPrimary -> BooleanPrimary -> Bool # | |
| Ord BooleanPrimary Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: BooleanPrimary -> BooleanPrimary -> Ordering # (<) :: BooleanPrimary -> BooleanPrimary -> Bool # (<=) :: BooleanPrimary -> BooleanPrimary -> Bool # (>) :: BooleanPrimary -> BooleanPrimary -> Bool # (>=) :: BooleanPrimary -> BooleanPrimary -> Bool # max :: BooleanPrimary -> BooleanPrimary -> BooleanPrimary # min :: BooleanPrimary -> BooleanPrimary -> BooleanPrimary # | |
data BooleanTerm Source #
Constructors
| BooleanTermFactor BooleanFactor | |
| BooleanTermAnd BooleanTerm_And |
Instances
| Read BooleanTerm Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS BooleanTerm # readList :: ReadS [BooleanTerm] # readPrec :: ReadPrec BooleanTerm # readListPrec :: ReadPrec [BooleanTerm] # | |
| Show BooleanTerm Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> BooleanTerm -> ShowS # show :: BooleanTerm -> String # showList :: [BooleanTerm] -> ShowS # | |
| Eq BooleanTerm Source # | |
Defined in Hydra.Langs.Sql.Ansi | |
| Ord BooleanTerm Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: BooleanTerm -> BooleanTerm -> Ordering # (<) :: BooleanTerm -> BooleanTerm -> Bool # (<=) :: BooleanTerm -> BooleanTerm -> Bool # (>) :: BooleanTerm -> BooleanTerm -> Bool # (>=) :: BooleanTerm -> BooleanTerm -> Bool # max :: BooleanTerm -> BooleanTerm -> BooleanTerm # min :: BooleanTerm -> BooleanTerm -> BooleanTerm # | |
_BooleanTerm :: Name Source #
data BooleanTerm_And Source #
Constructors
| BooleanTerm_And | |
Fields | |
Instances
| Read BooleanTerm_And Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS BooleanTerm_And # readList :: ReadS [BooleanTerm_And] # | |
| Show BooleanTerm_And Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> BooleanTerm_And -> ShowS # show :: BooleanTerm_And -> String # showList :: [BooleanTerm_And] -> ShowS # | |
| Eq BooleanTerm_And Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: BooleanTerm_And -> BooleanTerm_And -> Bool # (/=) :: BooleanTerm_And -> BooleanTerm_And -> Bool # | |
| Ord BooleanTerm_And Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: BooleanTerm_And -> BooleanTerm_And -> Ordering # (<) :: BooleanTerm_And -> BooleanTerm_And -> Bool # (<=) :: BooleanTerm_And -> BooleanTerm_And -> Bool # (>) :: BooleanTerm_And -> BooleanTerm_And -> Bool # (>=) :: BooleanTerm_And -> BooleanTerm_And -> Bool # max :: BooleanTerm_And -> BooleanTerm_And -> BooleanTerm_And # min :: BooleanTerm_And -> BooleanTerm_And -> BooleanTerm_And # | |
data BooleanTest Source #
Constructors
| BooleanTest | |
Instances
| Read BooleanTest Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS BooleanTest # readList :: ReadS [BooleanTest] # readPrec :: ReadPrec BooleanTest # readListPrec :: ReadPrec [BooleanTest] # | |
| Show BooleanTest Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> BooleanTest -> ShowS # show :: BooleanTest -> String # showList :: [BooleanTest] -> ShowS # | |
| Eq BooleanTest Source # | |
Defined in Hydra.Langs.Sql.Ansi | |
| Ord BooleanTest Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: BooleanTest -> BooleanTest -> Ordering # (<) :: BooleanTest -> BooleanTest -> Bool # (<=) :: BooleanTest -> BooleanTest -> Bool # (>) :: BooleanTest -> BooleanTest -> Bool # (>=) :: BooleanTest -> BooleanTest -> Bool # max :: BooleanTest -> BooleanTest -> BooleanTest # min :: BooleanTest -> BooleanTest -> BooleanTest # | |
_BooleanTest :: Name Source #
data BooleanTest_Sequence_Option Source #
Constructors
| BooleanTest_Sequence_Option | |
Instances
data BooleanType Source #
Constructors
| BooleanType | |
Instances
| Read BooleanType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS BooleanType # readList :: ReadS [BooleanType] # readPrec :: ReadPrec BooleanType # readListPrec :: ReadPrec [BooleanType] # | |
| Show BooleanType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> BooleanType -> ShowS # show :: BooleanType -> String # showList :: [BooleanType] -> ShowS # | |
| Eq BooleanType Source # | |
Defined in Hydra.Langs.Sql.Ansi | |
| Ord BooleanType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: BooleanType -> BooleanType -> Ordering # (<) :: BooleanType -> BooleanType -> Bool # (<=) :: BooleanType -> BooleanType -> Bool # (>) :: BooleanType -> BooleanType -> Bool # (>=) :: BooleanType -> BooleanType -> Bool # max :: BooleanType -> BooleanType -> BooleanType # min :: BooleanType -> BooleanType -> BooleanType # | |
_BooleanType :: Name Source #
data BooleanValueExpression Source #
Constructors
| BooleanValueExpressionTerm BooleanTerm | |
| BooleanValueExpressionOr BooleanValueExpression_Or |
Instances
data BooleanValueExpression_Or Source #
Constructors
| BooleanValueExpression_Or | |
Instances
data CaseExpression Source #
Constructors
| CaseExpression | |
Instances
| Read CaseExpression Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS CaseExpression # readList :: ReadS [CaseExpression] # | |
| Show CaseExpression Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> CaseExpression -> ShowS # show :: CaseExpression -> String # showList :: [CaseExpression] -> ShowS # | |
| Eq CaseExpression Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: CaseExpression -> CaseExpression -> Bool # (/=) :: CaseExpression -> CaseExpression -> Bool # | |
| Ord CaseExpression Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: CaseExpression -> CaseExpression -> Ordering # (<) :: CaseExpression -> CaseExpression -> Bool # (<=) :: CaseExpression -> CaseExpression -> Bool # (>) :: CaseExpression -> CaseExpression -> Bool # (>=) :: CaseExpression -> CaseExpression -> Bool # max :: CaseExpression -> CaseExpression -> CaseExpression # min :: CaseExpression -> CaseExpression -> CaseExpression # | |
data CastSpecification Source #
Constructors
| CastSpecification | |
Instances
data CharacterSetSpecification Source #
Constructors
| CharacterSetSpecification | |
Instances
data CharacterStringType Source #
Constructors
Instances
data CollateClause Source #
Constructors
| CollateClause | |
Instances
| Read CollateClause Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS CollateClause # readList :: ReadS [CollateClause] # | |
| Show CollateClause Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> CollateClause -> ShowS # show :: CollateClause -> String # showList :: [CollateClause] -> ShowS # | |
| Eq CollateClause Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: CollateClause -> CollateClause -> Bool # (/=) :: CollateClause -> CollateClause -> Bool # | |
| Ord CollateClause Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: CollateClause -> CollateClause -> Ordering # (<) :: CollateClause -> CollateClause -> Bool # (<=) :: CollateClause -> CollateClause -> Bool # (>) :: CollateClause -> CollateClause -> Bool # (>=) :: CollateClause -> CollateClause -> Bool # max :: CollateClause -> CollateClause -> CollateClause # min :: CollateClause -> CollateClause -> CollateClause # | |
data CollectionType Source #
Instances
| Read CollectionType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS CollectionType # readList :: ReadS [CollectionType] # | |
| Show CollectionType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> CollectionType -> ShowS # show :: CollectionType -> String # showList :: [CollectionType] -> ShowS # | |
| Eq CollectionType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: CollectionType -> CollectionType -> Bool # (/=) :: CollectionType -> CollectionType -> Bool # | |
| Ord CollectionType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: CollectionType -> CollectionType -> Ordering # (<) :: CollectionType -> CollectionType -> Bool # (<=) :: CollectionType -> CollectionType -> Bool # (>) :: CollectionType -> CollectionType -> Bool # (>=) :: CollectionType -> CollectionType -> Bool # max :: CollectionType -> CollectionType -> CollectionType # min :: CollectionType -> CollectionType -> CollectionType # | |
data CollectionValueConstructor Source #
Constructors
| CollectionValueConstructorArray ArrayValueConstructor | |
| CollectionValueConstructorMultiset MultisetValueConstructor |
Instances
data CollectionValueExpression Source #
Constructors
| CollectionValueExpressionArray ArrayValueExpression | |
| CollectionValueExpressionMultiset MultisetValueExpression |
Instances
data ColumnConstraintDefinition Source #
Constructors
| ColumnConstraintDefinition | |
Instances
data ColumnDefinition Source #
Constructors
Instances
| Read ColumnDefinition Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS ColumnDefinition # readList :: ReadS [ColumnDefinition] # | |
| Show ColumnDefinition Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> ColumnDefinition -> ShowS # show :: ColumnDefinition -> String # showList :: [ColumnDefinition] -> ShowS # | |
| Eq ColumnDefinition Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: ColumnDefinition -> ColumnDefinition -> Bool # (/=) :: ColumnDefinition -> ColumnDefinition -> Bool # | |
| Ord ColumnDefinition Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: ColumnDefinition -> ColumnDefinition -> Ordering # (<) :: ColumnDefinition -> ColumnDefinition -> Bool # (<=) :: ColumnDefinition -> ColumnDefinition -> Bool # (>) :: ColumnDefinition -> ColumnDefinition -> Bool # (>=) :: ColumnDefinition -> ColumnDefinition -> Bool # max :: ColumnDefinition -> ColumnDefinition -> ColumnDefinition # min :: ColumnDefinition -> ColumnDefinition -> ColumnDefinition # | |
data ColumnDefinition_TypeOrDomain_Option Source #
Constructors
| ColumnDefinition_TypeOrDomain_OptionDataType DataType | |
| ColumnDefinition_TypeOrDomain_OptionDomainName DomainName |
Instances
data ColumnDefinition_DefaultOrIdentityOrGeneration_Option Source #
Constructors
Instances
data ColumnNameList Source #
Constructors
| ColumnNameList | |
Fields | |
Instances
| Read ColumnNameList Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS ColumnNameList # readList :: ReadS [ColumnNameList] # | |
| Show ColumnNameList Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> ColumnNameList -> ShowS # show :: ColumnNameList -> String # showList :: [ColumnNameList] -> ShowS # | |
| Eq ColumnNameList Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: ColumnNameList -> ColumnNameList -> Bool # (/=) :: ColumnNameList -> ColumnNameList -> Bool # | |
| Ord ColumnNameList Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: ColumnNameList -> ColumnNameList -> Ordering # (<) :: ColumnNameList -> ColumnNameList -> Bool # (<=) :: ColumnNameList -> ColumnNameList -> Bool # (>) :: ColumnNameList -> ColumnNameList -> Bool # (>=) :: ColumnNameList -> ColumnNameList -> Bool # max :: ColumnNameList -> ColumnNameList -> ColumnNameList # min :: ColumnNameList -> ColumnNameList -> ColumnNameList # | |
data ColumnOptions Source #
Constructors
| ColumnOptions | |
Instances
| Read ColumnOptions Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS ColumnOptions # readList :: ReadS [ColumnOptions] # | |
| Show ColumnOptions Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> ColumnOptions -> ShowS # show :: ColumnOptions -> String # showList :: [ColumnOptions] -> ShowS # | |
| Eq ColumnOptions Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: ColumnOptions -> ColumnOptions -> Bool # (/=) :: ColumnOptions -> ColumnOptions -> Bool # | |
| Ord ColumnOptions Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: ColumnOptions -> ColumnOptions -> Ordering # (<) :: ColumnOptions -> ColumnOptions -> Bool # (<=) :: ColumnOptions -> ColumnOptions -> Bool # (>) :: ColumnOptions -> ColumnOptions -> Bool # (>=) :: ColumnOptions -> ColumnOptions -> Bool # max :: ColumnOptions -> ColumnOptions -> ColumnOptions # min :: ColumnOptions -> ColumnOptions -> ColumnOptions # | |
data ColumnReference Source #
Constructors
| ColumnReference | |
Instances
| Read ColumnReference Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS ColumnReference # readList :: ReadS [ColumnReference] # | |
| Show ColumnReference Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> ColumnReference -> ShowS # show :: ColumnReference -> String # showList :: [ColumnReference] -> ShowS # | |
| Eq ColumnReference Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: ColumnReference -> ColumnReference -> Bool # (/=) :: ColumnReference -> ColumnReference -> Bool # | |
| Ord ColumnReference Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: ColumnReference -> ColumnReference -> Ordering # (<) :: ColumnReference -> ColumnReference -> Bool # (<=) :: ColumnReference -> ColumnReference -> Bool # (>) :: ColumnReference -> ColumnReference -> Bool # (>=) :: ColumnReference -> ColumnReference -> Bool # max :: ColumnReference -> ColumnReference -> ColumnReference # min :: ColumnReference -> ColumnReference -> ColumnReference # | |
data CommonValueExpression Source #
Constructors
Instances
data ContextuallyTypedRowValueExpression Source #
Constructors
| ContextuallyTypedRowValueExpressionSpecialCase RowValueSpecialCase | |
| ContextuallyTypedRowValueExpressionConstructor ContextuallyTypedRowValueConstructor |
Instances
data ContextuallyTypedRowValueConstructor Source #
Constructors
| ContextuallyTypedRowValueConstructor | |
Instances
data ContextuallyTypedRowValueExpressionList Source #
Constructors
| ContextuallyTypedRowValueExpressionList | |
Instances
newtype ContextuallyTypedTableValueConstructor Source #
Constructors
| ContextuallyTypedTableValueConstructor | |
Instances
Constructors
| DataTypePredefined PredefinedType | |
| DataTypeRow RowType | |
| DataTypeNamed PathResolvedUserDefinedTypeName | |
| DataTypeReference ReferenceType | |
| DataTypeCollection CollectionType |
_DataType_row :: Name Source #
newtype DateLiteral Source #
Constructors
| DateLiteral | |
Fields | |
Instances
| Read DateLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS DateLiteral # readList :: ReadS [DateLiteral] # readPrec :: ReadPrec DateLiteral # readListPrec :: ReadPrec [DateLiteral] # | |
| Show DateLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> DateLiteral -> ShowS # show :: DateLiteral -> String # showList :: [DateLiteral] -> ShowS # | |
| Eq DateLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi | |
| Ord DateLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: DateLiteral -> DateLiteral -> Ordering # (<) :: DateLiteral -> DateLiteral -> Bool # (<=) :: DateLiteral -> DateLiteral -> Bool # (>) :: DateLiteral -> DateLiteral -> Bool # (>=) :: DateLiteral -> DateLiteral -> Bool # max :: DateLiteral -> DateLiteral -> DateLiteral # min :: DateLiteral -> DateLiteral -> DateLiteral # | |
_DateLiteral :: Name Source #
data DatetimeLiteral Source #
Constructors
| DatetimeLiteralDate DateLiteral | |
| DatetimeLiteralTime TimeLiteral | |
| DatetimeLiteralTimestamp TimestampLiteral |
Instances
| Read DatetimeLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS DatetimeLiteral # readList :: ReadS [DatetimeLiteral] # | |
| Show DatetimeLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> DatetimeLiteral -> ShowS # show :: DatetimeLiteral -> String # showList :: [DatetimeLiteral] -> ShowS # | |
| Eq DatetimeLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: DatetimeLiteral -> DatetimeLiteral -> Bool # (/=) :: DatetimeLiteral -> DatetimeLiteral -> Bool # | |
| Ord DatetimeLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: DatetimeLiteral -> DatetimeLiteral -> Ordering # (<) :: DatetimeLiteral -> DatetimeLiteral -> Bool # (<=) :: DatetimeLiteral -> DatetimeLiteral -> Bool # (>) :: DatetimeLiteral -> DatetimeLiteral -> Bool # (>=) :: DatetimeLiteral -> DatetimeLiteral -> Bool # max :: DatetimeLiteral -> DatetimeLiteral -> DatetimeLiteral # min :: DatetimeLiteral -> DatetimeLiteral -> DatetimeLiteral # | |
data DatetimeType Source #
Constructors
| DatetimeType | |
Instances
| Read DatetimeType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS DatetimeType # readList :: ReadS [DatetimeType] # | |
| Show DatetimeType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> DatetimeType -> ShowS # show :: DatetimeType -> String # showList :: [DatetimeType] -> ShowS # | |
| Eq DatetimeType Source # | |
Defined in Hydra.Langs.Sql.Ansi | |
| Ord DatetimeType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: DatetimeType -> DatetimeType -> Ordering # (<) :: DatetimeType -> DatetimeType -> Bool # (<=) :: DatetimeType -> DatetimeType -> Bool # (>) :: DatetimeType -> DatetimeType -> Bool # (>=) :: DatetimeType -> DatetimeType -> Bool # max :: DatetimeType -> DatetimeType -> DatetimeType # min :: DatetimeType -> DatetimeType -> DatetimeType # | |
_DatetimeType :: Name Source #
data DatetimeValueExpression Source #
Constructors
| DatetimeValueExpression | |
Instances
data DefaultClause Source #
Constructors
| DefaultClause | |
Instances
| Read DefaultClause Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS DefaultClause # readList :: ReadS [DefaultClause] # | |
| Show DefaultClause Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> DefaultClause -> ShowS # show :: DefaultClause -> String # showList :: [DefaultClause] -> ShowS # | |
| Eq DefaultClause Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: DefaultClause -> DefaultClause -> Bool # (/=) :: DefaultClause -> DefaultClause -> Bool # | |
| Ord DefaultClause Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: DefaultClause -> DefaultClause -> Ordering # (<) :: DefaultClause -> DefaultClause -> Bool # (<=) :: DefaultClause -> DefaultClause -> Bool # (>) :: DefaultClause -> DefaultClause -> Bool # (>=) :: DefaultClause -> DefaultClause -> Bool # max :: DefaultClause -> DefaultClause -> DefaultClause # min :: DefaultClause -> DefaultClause -> DefaultClause # | |
data ExactNumericType Source #
Constructors
Instances
| Read ExactNumericType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS ExactNumericType # readList :: ReadS [ExactNumericType] # | |
| Show ExactNumericType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> ExactNumericType -> ShowS # show :: ExactNumericType -> String # showList :: [ExactNumericType] -> ShowS # | |
| Eq ExactNumericType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: ExactNumericType -> ExactNumericType -> Bool # (/=) :: ExactNumericType -> ExactNumericType -> Bool # | |
| Ord ExactNumericType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: ExactNumericType -> ExactNumericType -> Ordering # (<) :: ExactNumericType -> ExactNumericType -> Bool # (<=) :: ExactNumericType -> ExactNumericType -> Bool # (>) :: ExactNumericType -> ExactNumericType -> Bool # (>=) :: ExactNumericType -> ExactNumericType -> Bool # max :: ExactNumericType -> ExactNumericType -> ExactNumericType # min :: ExactNumericType -> ExactNumericType -> ExactNumericType # | |
data ExactNumericType_Numeric_Option Source #
Constructors
| ExactNumericType_Numeric_Option | |
Instances
data ExactNumericType_Decimal_Option Source #
Constructors
| ExactNumericType_Decimal_Option | |
Instances
data ExactNumericType_Dec_Option Source #
Constructors
| ExactNumericType_Dec_Option | |
Instances
data FieldReference Source #
Constructors
| FieldReference | |
Instances
| Read FieldReference Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS FieldReference # readList :: ReadS [FieldReference] # | |
| Show FieldReference Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> FieldReference -> ShowS # show :: FieldReference -> String # showList :: [FieldReference] -> ShowS # | |
| Eq FieldReference Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: FieldReference -> FieldReference -> Bool # (/=) :: FieldReference -> FieldReference -> Bool # | |
| Ord FieldReference Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: FieldReference -> FieldReference -> Ordering # (<) :: FieldReference -> FieldReference -> Bool # (<=) :: FieldReference -> FieldReference -> Bool # (>) :: FieldReference -> FieldReference -> Bool # (>=) :: FieldReference -> FieldReference -> Bool # max :: FieldReference -> FieldReference -> FieldReference # min :: FieldReference -> FieldReference -> FieldReference # | |
data FromConstructor Source #
Constructors
| FromConstructor | |
Instances
| Read FromConstructor Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS FromConstructor # readList :: ReadS [FromConstructor] # | |
| Show FromConstructor Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> FromConstructor -> ShowS # show :: FromConstructor -> String # showList :: [FromConstructor] -> ShowS # | |
| Eq FromConstructor Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: FromConstructor -> FromConstructor -> Bool # (/=) :: FromConstructor -> FromConstructor -> Bool # | |
| Ord FromConstructor Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: FromConstructor -> FromConstructor -> Ordering # (<) :: FromConstructor -> FromConstructor -> Bool # (<=) :: FromConstructor -> FromConstructor -> Bool # (>) :: FromConstructor -> FromConstructor -> Bool # (>=) :: FromConstructor -> FromConstructor -> Bool # max :: FromConstructor -> FromConstructor -> FromConstructor # min :: FromConstructor -> FromConstructor -> FromConstructor # | |
data FromDefault Source #
Constructors
| FromDefault | |
Instances
| Read FromDefault Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS FromDefault # readList :: ReadS [FromDefault] # readPrec :: ReadPrec FromDefault # readListPrec :: ReadPrec [FromDefault] # | |
| Show FromDefault Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> FromDefault -> ShowS # show :: FromDefault -> String # showList :: [FromDefault] -> ShowS # | |
| Eq FromDefault Source # | |
Defined in Hydra.Langs.Sql.Ansi | |
| Ord FromDefault Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: FromDefault -> FromDefault -> Ordering # (<) :: FromDefault -> FromDefault -> Bool # (<=) :: FromDefault -> FromDefault -> Bool # (>) :: FromDefault -> FromDefault -> Bool # (>=) :: FromDefault -> FromDefault -> Bool # max :: FromDefault -> FromDefault -> FromDefault # min :: FromDefault -> FromDefault -> FromDefault # | |
_FromDefault :: Name Source #
data FromSubquery Source #
Constructors
| FromSubquery | |
Instances
| Read FromSubquery Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS FromSubquery # readList :: ReadS [FromSubquery] # | |
| Show FromSubquery Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> FromSubquery -> ShowS # show :: FromSubquery -> String # showList :: [FromSubquery] -> ShowS # | |
| Eq FromSubquery Source # | |
Defined in Hydra.Langs.Sql.Ansi | |
| Ord FromSubquery Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: FromSubquery -> FromSubquery -> Ordering # (<) :: FromSubquery -> FromSubquery -> Bool # (<=) :: FromSubquery -> FromSubquery -> Bool # (>) :: FromSubquery -> FromSubquery -> Bool # (>=) :: FromSubquery -> FromSubquery -> Bool # max :: FromSubquery -> FromSubquery -> FromSubquery # min :: FromSubquery -> FromSubquery -> FromSubquery # | |
_FromSubquery :: Name Source #
data GeneralLiteral Source #
Constructors
Instances
| Read GeneralLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS GeneralLiteral # readList :: ReadS [GeneralLiteral] # | |
| Show GeneralLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> GeneralLiteral -> ShowS # show :: GeneralLiteral -> String # showList :: [GeneralLiteral] -> ShowS # | |
| Eq GeneralLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: GeneralLiteral -> GeneralLiteral -> Bool # (/=) :: GeneralLiteral -> GeneralLiteral -> Bool # | |
| Ord GeneralLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: GeneralLiteral -> GeneralLiteral -> Ordering # (<) :: GeneralLiteral -> GeneralLiteral -> Bool # (<=) :: GeneralLiteral -> GeneralLiteral -> Bool # (>) :: GeneralLiteral -> GeneralLiteral -> Bool # (>=) :: GeneralLiteral -> GeneralLiteral -> Bool # max :: GeneralLiteral -> GeneralLiteral -> GeneralLiteral # min :: GeneralLiteral -> GeneralLiteral -> GeneralLiteral # | |
data GeneralValueSpecification Source #
Constructors
| GeneralValueSpecification | |
Instances
data GenerationClause Source #
Constructors
| GenerationClause | |
Instances
| Read GenerationClause Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS GenerationClause # readList :: ReadS [GenerationClause] # | |
| Show GenerationClause Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> GenerationClause -> ShowS # show :: GenerationClause -> String # showList :: [GenerationClause] -> ShowS # | |
| Eq GenerationClause Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: GenerationClause -> GenerationClause -> Bool # (/=) :: GenerationClause -> GenerationClause -> Bool # | |
| Ord GenerationClause Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: GenerationClause -> GenerationClause -> Ordering # (<) :: GenerationClause -> GenerationClause -> Bool # (<=) :: GenerationClause -> GenerationClause -> Bool # (>) :: GenerationClause -> GenerationClause -> Bool # (>=) :: GenerationClause -> GenerationClause -> Bool # max :: GenerationClause -> GenerationClause -> GenerationClause # min :: GenerationClause -> GenerationClause -> GenerationClause # | |
data GlobalOrLocal Source #
Constructors
| GlobalOrLocalGlobal | |
| GlobalOrLocalLocal |
Instances
| Read GlobalOrLocal Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS GlobalOrLocal # readList :: ReadS [GlobalOrLocal] # | |
| Show GlobalOrLocal Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> GlobalOrLocal -> ShowS # show :: GlobalOrLocal -> String # showList :: [GlobalOrLocal] -> ShowS # | |
| Eq GlobalOrLocal Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: GlobalOrLocal -> GlobalOrLocal -> Bool # (/=) :: GlobalOrLocal -> GlobalOrLocal -> Bool # | |
| Ord GlobalOrLocal Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: GlobalOrLocal -> GlobalOrLocal -> Ordering # (<) :: GlobalOrLocal -> GlobalOrLocal -> Bool # (<=) :: GlobalOrLocal -> GlobalOrLocal -> Bool # (>) :: GlobalOrLocal -> GlobalOrLocal -> Bool # (>=) :: GlobalOrLocal -> GlobalOrLocal -> Bool # max :: GlobalOrLocal -> GlobalOrLocal -> GlobalOrLocal # min :: GlobalOrLocal -> GlobalOrLocal -> GlobalOrLocal # | |
data IdentityColumnSpecification Source #
Constructors
| IdentityColumnSpecification | |
Instances
newtype InsertColumnList Source #
Constructors
| InsertColumnList | |
Fields | |
Instances
| Read InsertColumnList Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS InsertColumnList # readList :: ReadS [InsertColumnList] # | |
| Show InsertColumnList Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> InsertColumnList -> ShowS # show :: InsertColumnList -> String # showList :: [InsertColumnList] -> ShowS # | |
| Eq InsertColumnList Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: InsertColumnList -> InsertColumnList -> Bool # (/=) :: InsertColumnList -> InsertColumnList -> Bool # | |
| Ord InsertColumnList Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: InsertColumnList -> InsertColumnList -> Ordering # (<) :: InsertColumnList -> InsertColumnList -> Bool # (<=) :: InsertColumnList -> InsertColumnList -> Bool # (>) :: InsertColumnList -> InsertColumnList -> Bool # (>=) :: InsertColumnList -> InsertColumnList -> Bool # max :: InsertColumnList -> InsertColumnList -> InsertColumnList # min :: InsertColumnList -> InsertColumnList -> InsertColumnList # | |
data InsertColumnsAndSource Source #
Constructors
| InsertColumnsAndSourceSubquery FromSubquery | |
| InsertColumnsAndSourceConstructor FromConstructor | |
| InsertColumnsAndSourceDefault FromDefault |
Instances
data InsertStatement Source #
Constructors
| InsertStatement | |
Instances
| Read InsertStatement Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS InsertStatement # readList :: ReadS [InsertStatement] # | |
| Show InsertStatement Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> InsertStatement -> ShowS # show :: InsertStatement -> String # showList :: [InsertStatement] -> ShowS # | |
| Eq InsertStatement Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: InsertStatement -> InsertStatement -> Bool # (/=) :: InsertStatement -> InsertStatement -> Bool # | |
| Ord InsertStatement Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: InsertStatement -> InsertStatement -> Ordering # (<) :: InsertStatement -> InsertStatement -> Bool # (<=) :: InsertStatement -> InsertStatement -> Bool # (>) :: InsertStatement -> InsertStatement -> Bool # (>=) :: InsertStatement -> InsertStatement -> Bool # max :: InsertStatement -> InsertStatement -> InsertStatement # min :: InsertStatement -> InsertStatement -> InsertStatement # | |
newtype InsertionTarget Source #
Constructors
| InsertionTarget | |
Fields | |
Instances
| Read InsertionTarget Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS InsertionTarget # readList :: ReadS [InsertionTarget] # | |
| Show InsertionTarget Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> InsertionTarget -> ShowS # show :: InsertionTarget -> String # showList :: [InsertionTarget] -> ShowS # | |
| Eq InsertionTarget Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: InsertionTarget -> InsertionTarget -> Bool # (/=) :: InsertionTarget -> InsertionTarget -> Bool # | |
| Ord InsertionTarget Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: InsertionTarget -> InsertionTarget -> Ordering # (<) :: InsertionTarget -> InsertionTarget -> Bool # (<=) :: InsertionTarget -> InsertionTarget -> Bool # (>) :: InsertionTarget -> InsertionTarget -> Bool # (>=) :: InsertionTarget -> InsertionTarget -> Bool # max :: InsertionTarget -> InsertionTarget -> InsertionTarget # min :: InsertionTarget -> InsertionTarget -> InsertionTarget # | |
data IntervalLiteral Source #
Constructors
| IntervalLiteral | |
Instances
| Read IntervalLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS IntervalLiteral # readList :: ReadS [IntervalLiteral] # | |
| Show IntervalLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> IntervalLiteral -> ShowS # show :: IntervalLiteral -> String # showList :: [IntervalLiteral] -> ShowS # | |
| Eq IntervalLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: IntervalLiteral -> IntervalLiteral -> Bool # (/=) :: IntervalLiteral -> IntervalLiteral -> Bool # | |
| Ord IntervalLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: IntervalLiteral -> IntervalLiteral -> Ordering # (<) :: IntervalLiteral -> IntervalLiteral -> Bool # (<=) :: IntervalLiteral -> IntervalLiteral -> Bool # (>) :: IntervalLiteral -> IntervalLiteral -> Bool # (>=) :: IntervalLiteral -> IntervalLiteral -> Bool # max :: IntervalLiteral -> IntervalLiteral -> IntervalLiteral # min :: IntervalLiteral -> IntervalLiteral -> IntervalLiteral # | |
data IntervalType Source #
Constructors
| IntervalType | |
Instances
| Read IntervalType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS IntervalType # readList :: ReadS [IntervalType] # | |
| Show IntervalType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> IntervalType -> ShowS # show :: IntervalType -> String # showList :: [IntervalType] -> ShowS # | |
| Eq IntervalType Source # | |
Defined in Hydra.Langs.Sql.Ansi | |
| Ord IntervalType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: IntervalType -> IntervalType -> Ordering # (<) :: IntervalType -> IntervalType -> Bool # (<=) :: IntervalType -> IntervalType -> Bool # (>) :: IntervalType -> IntervalType -> Bool # (>=) :: IntervalType -> IntervalType -> Bool # max :: IntervalType -> IntervalType -> IntervalType # min :: IntervalType -> IntervalType -> IntervalType # | |
_IntervalType :: Name Source #
data IntervalValueExpression Source #
Constructors
| IntervalValueExpression | |
Instances
data LargeObjectLength Source #
Constructors
| LargeObjectLength | |
Instances
Constructors
| Length | |
Fields | |
data LikeClause Source #
Constructors
| LikeClause | |
Instances
| Read LikeClause Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS LikeClause # readList :: ReadS [LikeClause] # readPrec :: ReadPrec LikeClause # readListPrec :: ReadPrec [LikeClause] # | |
| Show LikeClause Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> LikeClause -> ShowS # show :: LikeClause -> String # showList :: [LikeClause] -> ShowS # | |
| Eq LikeClause Source # | |
Defined in Hydra.Langs.Sql.Ansi | |
| Ord LikeClause Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: LikeClause -> LikeClause -> Ordering # (<) :: LikeClause -> LikeClause -> Bool # (<=) :: LikeClause -> LikeClause -> Bool # (>) :: LikeClause -> LikeClause -> Bool # (>=) :: LikeClause -> LikeClause -> Bool # max :: LikeClause -> LikeClause -> LikeClause # min :: LikeClause -> LikeClause -> LikeClause # | |
_LikeClause :: Name Source #
data MethodInvocation Source #
Constructors
| MethodInvocation | |
Instances
| Read MethodInvocation Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS MethodInvocation # readList :: ReadS [MethodInvocation] # | |
| Show MethodInvocation Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> MethodInvocation -> ShowS # show :: MethodInvocation -> String # showList :: [MethodInvocation] -> ShowS # | |
| Eq MethodInvocation Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: MethodInvocation -> MethodInvocation -> Bool # (/=) :: MethodInvocation -> MethodInvocation -> Bool # | |
| Ord MethodInvocation Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: MethodInvocation -> MethodInvocation -> Ordering # (<) :: MethodInvocation -> MethodInvocation -> Bool # (<=) :: MethodInvocation -> MethodInvocation -> Bool # (>) :: MethodInvocation -> MethodInvocation -> Bool # (>=) :: MethodInvocation -> MethodInvocation -> Bool # max :: MethodInvocation -> MethodInvocation -> MethodInvocation # min :: MethodInvocation -> MethodInvocation -> MethodInvocation # | |
data MultisetElementReference Source #
Constructors
| MultisetElementReference | |
Instances
newtype MultisetType Source #
Constructors
| MultisetType | |
Fields | |
Instances
| Read MultisetType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS MultisetType # readList :: ReadS [MultisetType] # | |
| Show MultisetType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> MultisetType -> ShowS # show :: MultisetType -> String # showList :: [MultisetType] -> ShowS # | |
| Eq MultisetType Source # | |
Defined in Hydra.Langs.Sql.Ansi | |
| Ord MultisetType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: MultisetType -> MultisetType -> Ordering # (<) :: MultisetType -> MultisetType -> Bool # (<=) :: MultisetType -> MultisetType -> Bool # (>) :: MultisetType -> MultisetType -> Bool # (>=) :: MultisetType -> MultisetType -> Bool # max :: MultisetType -> MultisetType -> MultisetType # min :: MultisetType -> MultisetType -> MultisetType # | |
_MultisetType :: Name Source #
data MultisetValueConstructor Source #
Constructors
| MultisetValueConstructor | |
Instances
data MultisetValueExpression Source #
Constructors
| MultisetValueExpression | |
Instances
data NationalCharacterStringType Source #
Constructors
| NationalCharacterStringType | |
Instances
data NewSpecification Source #
Constructors
| NewSpecification | |
Instances
| Read NewSpecification Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS NewSpecification # readList :: ReadS [NewSpecification] # | |
| Show NewSpecification Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> NewSpecification -> ShowS # show :: NewSpecification -> String # showList :: [NewSpecification] -> ShowS # | |
| Eq NewSpecification Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: NewSpecification -> NewSpecification -> Bool # (/=) :: NewSpecification -> NewSpecification -> Bool # | |
| Ord NewSpecification Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: NewSpecification -> NewSpecification -> Ordering # (<) :: NewSpecification -> NewSpecification -> Bool # (<=) :: NewSpecification -> NewSpecification -> Bool # (>) :: NewSpecification -> NewSpecification -> Bool # (>=) :: NewSpecification -> NewSpecification -> Bool # max :: NewSpecification -> NewSpecification -> NewSpecification # min :: NewSpecification -> NewSpecification -> NewSpecification # | |
data NextValueExpression Source #
Constructors
| NextValueExpression | |
Instances
data NumericType Source #
Instances
| Read NumericType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS NumericType # readList :: ReadS [NumericType] # readPrec :: ReadPrec NumericType # readListPrec :: ReadPrec [NumericType] # | |
| Show NumericType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> NumericType -> ShowS # show :: NumericType -> String # showList :: [NumericType] -> ShowS # | |
| Eq NumericType Source # | |
Defined in Hydra.Langs.Sql.Ansi | |
| Ord NumericType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: NumericType -> NumericType -> Ordering # (<) :: NumericType -> NumericType -> Bool # (<=) :: NumericType -> NumericType -> Bool # (>) :: NumericType -> NumericType -> Bool # (>=) :: NumericType -> NumericType -> Bool # max :: NumericType -> NumericType -> NumericType # min :: NumericType -> NumericType -> NumericType # | |
_NumericType :: Name Source #
data NumericValueExpression Source #
Constructors
| NumericValueExpression | |
Instances
data OverrideClause Source #
Instances
| Read OverrideClause Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS OverrideClause # readList :: ReadS [OverrideClause] # | |
| Show OverrideClause Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> OverrideClause -> ShowS # show :: OverrideClause -> String # showList :: [OverrideClause] -> ShowS # | |
| Eq OverrideClause Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: OverrideClause -> OverrideClause -> Bool # (/=) :: OverrideClause -> OverrideClause -> Bool # | |
| Ord OverrideClause Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: OverrideClause -> OverrideClause -> Ordering # (<) :: OverrideClause -> OverrideClause -> Bool # (<=) :: OverrideClause -> OverrideClause -> Bool # (>) :: OverrideClause -> OverrideClause -> Bool # (>=) :: OverrideClause -> OverrideClause -> Bool # max :: OverrideClause -> OverrideClause -> OverrideClause # min :: OverrideClause -> OverrideClause -> OverrideClause # | |
newtype ParenthesizedValueExpression Source #
Constructors
| ParenthesizedValueExpression | |
Instances
Constructors
| Precision | |
Fields | |
Instances
| Read Precision Source # | |
| Show Precision Source # | |
| Eq Precision Source # | |
| Ord Precision Source # | |
_Precision :: Name Source #
data PredefinedType Source #
Constructors
Instances
| Read PredefinedType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS PredefinedType # readList :: ReadS [PredefinedType] # | |
| Show PredefinedType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> PredefinedType -> ShowS # show :: PredefinedType -> String # showList :: [PredefinedType] -> ShowS # | |
| Eq PredefinedType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: PredefinedType -> PredefinedType -> Bool # (/=) :: PredefinedType -> PredefinedType -> Bool # | |
| Ord PredefinedType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: PredefinedType -> PredefinedType -> Ordering # (<) :: PredefinedType -> PredefinedType -> Bool # (<=) :: PredefinedType -> PredefinedType -> Bool # (>) :: PredefinedType -> PredefinedType -> Bool # (>=) :: PredefinedType -> PredefinedType -> Bool # max :: PredefinedType -> PredefinedType -> PredefinedType # min :: PredefinedType -> PredefinedType -> PredefinedType # | |
data PredefinedType_String Source #
Constructors
| PredefinedType_String | |
Instances
data PredefinedType_NationalString Source #
Constructors
| PredefinedType_NationalString | |
Instances
Constructors
| Predicate | |
Instances
| Read Predicate Source # | |
| Show Predicate Source # | |
| Eq Predicate Source # | |
| Ord Predicate Source # | |
_Predicate :: Name Source #
data QueryExpression Source #
Constructors
| QueryExpression | |
Instances
| Read QueryExpression Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS QueryExpression # readList :: ReadS [QueryExpression] # | |
| Show QueryExpression Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> QueryExpression -> ShowS # show :: QueryExpression -> String # showList :: [QueryExpression] -> ShowS # | |
| Eq QueryExpression Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: QueryExpression -> QueryExpression -> Bool # (/=) :: QueryExpression -> QueryExpression -> Bool # | |
| Ord QueryExpression Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: QueryExpression -> QueryExpression -> Ordering # (<) :: QueryExpression -> QueryExpression -> Bool # (<=) :: QueryExpression -> QueryExpression -> Bool # (>) :: QueryExpression -> QueryExpression -> Bool # (>=) :: QueryExpression -> QueryExpression -> Bool # max :: QueryExpression -> QueryExpression -> QueryExpression # min :: QueryExpression -> QueryExpression -> QueryExpression # | |
data ReferenceScopeCheck Source #
Constructors
| ReferenceScopeCheck | |
Instances
data ReferenceType Source #
Constructors
| ReferenceType | |
Instances
| Read ReferenceType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS ReferenceType # readList :: ReadS [ReferenceType] # | |
| Show ReferenceType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> ReferenceType -> ShowS # show :: ReferenceType -> String # showList :: [ReferenceType] -> ShowS # | |
| Eq ReferenceType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: ReferenceType -> ReferenceType -> Bool # (/=) :: ReferenceType -> ReferenceType -> Bool # | |
| Ord ReferenceType Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: ReferenceType -> ReferenceType -> Ordering # (<) :: ReferenceType -> ReferenceType -> Bool # (<=) :: ReferenceType -> ReferenceType -> Bool # (>) :: ReferenceType -> ReferenceType -> Bool # (>=) :: ReferenceType -> ReferenceType -> Bool # max :: ReferenceType -> ReferenceType -> ReferenceType # min :: ReferenceType -> ReferenceType -> ReferenceType # | |
Constructors
| RowType | |
newtype RowValueSpecialCase Source #
Constructors
| RowValueSpecialCase | |
Instances
data NonparenthesizedValueExpressionPrimary Source #
Constructors
Instances
data ReferenceResolution Source #
Constructors
| ReferenceResolution | |
Instances
newtype ReferenceValueExpression Source #
Constructors
| ReferenceValueExpression | |
Instances
data RowValueExpression Source #
Constructors
| RowValueExpression | |
Instances
data RoutineInvocation Source #
Constructors
| RoutineInvocation | |
Instances
newtype ScalarSubquery Source #
Constructors
| ScalarSubquery | |
Fields | |
Instances
| Read ScalarSubquery Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS ScalarSubquery # readList :: ReadS [ScalarSubquery] # | |
| Show ScalarSubquery Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> ScalarSubquery -> ShowS # show :: ScalarSubquery -> String # showList :: [ScalarSubquery] -> ShowS # | |
| Eq ScalarSubquery Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: ScalarSubquery -> ScalarSubquery -> Bool # (/=) :: ScalarSubquery -> ScalarSubquery -> Bool # | |
| Ord ScalarSubquery Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: ScalarSubquery -> ScalarSubquery -> Ordering # (<) :: ScalarSubquery -> ScalarSubquery -> Bool # (<=) :: ScalarSubquery -> ScalarSubquery -> Bool # (>) :: ScalarSubquery -> ScalarSubquery -> Bool # (>=) :: ScalarSubquery -> ScalarSubquery -> Bool # max :: ScalarSubquery -> ScalarSubquery -> ScalarSubquery # min :: ScalarSubquery -> ScalarSubquery -> ScalarSubquery # | |
Constructors
| Scale | |
Fields | |
data SelfReferencingColumnSpecification Source #
Constructors
| SelfReferencingColumnSpecification | |
Instances
data SetFunctionSpecification Source #
Constructors
| SetFunctionSpecification | |
Instances
data StaticMethodInvocation Source #
Constructors
| StaticMethodInvocation | |
Instances
data StringValueExpression Source #
Constructors
| StringValueExpression | |
Instances
Constructors
| Subquery | |
Fields | |
data SubtableClause Source #
Constructors
| SubtableClause | |
Instances
| Read SubtableClause Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS SubtableClause # readList :: ReadS [SubtableClause] # | |
| Show SubtableClause Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> SubtableClause -> ShowS # show :: SubtableClause -> String # showList :: [SubtableClause] -> ShowS # | |
| Eq SubtableClause Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: SubtableClause -> SubtableClause -> Bool # (/=) :: SubtableClause -> SubtableClause -> Bool # | |
| Ord SubtableClause Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: SubtableClause -> SubtableClause -> Ordering # (<) :: SubtableClause -> SubtableClause -> Bool # (<=) :: SubtableClause -> SubtableClause -> Bool # (>) :: SubtableClause -> SubtableClause -> Bool # (>=) :: SubtableClause -> SubtableClause -> Bool # max :: SubtableClause -> SubtableClause -> SubtableClause # min :: SubtableClause -> SubtableClause -> SubtableClause # | |
data SubtypeTreatment Source #
Constructors
| SubtypeTreatment | |
Instances
| Read SubtypeTreatment Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS SubtypeTreatment # readList :: ReadS [SubtypeTreatment] # | |
| Show SubtypeTreatment Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> SubtypeTreatment -> ShowS # show :: SubtypeTreatment -> String # showList :: [SubtypeTreatment] -> ShowS # | |
| Eq SubtypeTreatment Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: SubtypeTreatment -> SubtypeTreatment -> Bool # (/=) :: SubtypeTreatment -> SubtypeTreatment -> Bool # | |
| Ord SubtypeTreatment Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: SubtypeTreatment -> SubtypeTreatment -> Ordering # (<) :: SubtypeTreatment -> SubtypeTreatment -> Bool # (<=) :: SubtypeTreatment -> SubtypeTreatment -> Bool # (>) :: SubtypeTreatment -> SubtypeTreatment -> Bool # (>=) :: SubtypeTreatment -> SubtypeTreatment -> Bool # max :: SubtypeTreatment -> SubtypeTreatment -> SubtypeTreatment # min :: SubtypeTreatment -> SubtypeTreatment -> SubtypeTreatment # | |
data TableCommitAction Source #
Constructors
| TableCommitActionPreserve | |
| TableCommitActionDelete |
Instances
data TableConstraintDefinition Source #
Constructors
| TableConstraintDefinition | |
Instances
data TableContentsSource Source #
Constructors
| TableContentsSourceList TableElementList | |
| TableContentsSourceSubtable TableContentsSource_Subtable | |
| TableContentsSourceSubquery AsSubqueryClause |
Instances
data TableContentsSource_Subtable Source #
Constructors
| TableContentsSource_Subtable | |
Instances
data TableDefinition Source #
Constructors
| TableDefinition | |
Instances
| Read TableDefinition Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS TableDefinition # readList :: ReadS [TableDefinition] # | |
| Show TableDefinition Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> TableDefinition -> ShowS # show :: TableDefinition -> String # showList :: [TableDefinition] -> ShowS # | |
| Eq TableDefinition Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: TableDefinition -> TableDefinition -> Bool # (/=) :: TableDefinition -> TableDefinition -> Bool # | |
| Ord TableDefinition Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: TableDefinition -> TableDefinition -> Ordering # (<) :: TableDefinition -> TableDefinition -> Bool # (<=) :: TableDefinition -> TableDefinition -> Bool # (>) :: TableDefinition -> TableDefinition -> Bool # (>=) :: TableDefinition -> TableDefinition -> Bool # max :: TableDefinition -> TableDefinition -> TableDefinition # min :: TableDefinition -> TableDefinition -> TableDefinition # | |
data TableElement Source #
Constructors
Instances
| Read TableElement Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS TableElement # readList :: ReadS [TableElement] # | |
| Show TableElement Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> TableElement -> ShowS # show :: TableElement -> String # showList :: [TableElement] -> ShowS # | |
| Eq TableElement Source # | |
Defined in Hydra.Langs.Sql.Ansi | |
| Ord TableElement Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: TableElement -> TableElement -> Ordering # (<) :: TableElement -> TableElement -> Bool # (<=) :: TableElement -> TableElement -> Bool # (>) :: TableElement -> TableElement -> Bool # (>=) :: TableElement -> TableElement -> Bool # max :: TableElement -> TableElement -> TableElement # min :: TableElement -> TableElement -> TableElement # | |
_TableElement :: Name Source #
data TableElementList Source #
Constructors
| TableElementList | |
Fields | |
Instances
| Read TableElementList Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS TableElementList # readList :: ReadS [TableElementList] # | |
| Show TableElementList Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> TableElementList -> ShowS # show :: TableElementList -> String # showList :: [TableElementList] -> ShowS # | |
| Eq TableElementList Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: TableElementList -> TableElementList -> Bool # (/=) :: TableElementList -> TableElementList -> Bool # | |
| Ord TableElementList Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: TableElementList -> TableElementList -> Ordering # (<) :: TableElementList -> TableElementList -> Bool # (<=) :: TableElementList -> TableElementList -> Bool # (>) :: TableElementList -> TableElementList -> Bool # (>=) :: TableElementList -> TableElementList -> Bool # max :: TableElementList -> TableElementList -> TableElementList # min :: TableElementList -> TableElementList -> TableElementList # | |
newtype TableScope Source #
Constructors
| TableScope | |
Fields | |
Instances
| Read TableScope Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS TableScope # readList :: ReadS [TableScope] # readPrec :: ReadPrec TableScope # readListPrec :: ReadPrec [TableScope] # | |
| Show TableScope Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> TableScope -> ShowS # show :: TableScope -> String # showList :: [TableScope] -> ShowS # | |
| Eq TableScope Source # | |
Defined in Hydra.Langs.Sql.Ansi | |
| Ord TableScope Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: TableScope -> TableScope -> Ordering # (<) :: TableScope -> TableScope -> Bool # (<=) :: TableScope -> TableScope -> Bool # (>) :: TableScope -> TableScope -> Bool # (>=) :: TableScope -> TableScope -> Bool # max :: TableScope -> TableScope -> TableScope # min :: TableScope -> TableScope -> TableScope # | |
_TableScope :: Name Source #
newtype TimeLiteral Source #
Constructors
| TimeLiteral | |
Fields | |
Instances
| Read TimeLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS TimeLiteral # readList :: ReadS [TimeLiteral] # readPrec :: ReadPrec TimeLiteral # readListPrec :: ReadPrec [TimeLiteral] # | |
| Show TimeLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> TimeLiteral -> ShowS # show :: TimeLiteral -> String # showList :: [TimeLiteral] -> ShowS # | |
| Eq TimeLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi | |
| Ord TimeLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: TimeLiteral -> TimeLiteral -> Ordering # (<) :: TimeLiteral -> TimeLiteral -> Bool # (<=) :: TimeLiteral -> TimeLiteral -> Bool # (>) :: TimeLiteral -> TimeLiteral -> Bool # (>=) :: TimeLiteral -> TimeLiteral -> Bool # max :: TimeLiteral -> TimeLiteral -> TimeLiteral # min :: TimeLiteral -> TimeLiteral -> TimeLiteral # | |
_TimeLiteral :: Name Source #
data TruthValue Source #
Constructors
| TruthValueTRUE | |
| TruthValueFALSE | |
| TruthValueUNKNOWN |
Instances
| Read TruthValue Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS TruthValue # readList :: ReadS [TruthValue] # readPrec :: ReadPrec TruthValue # readListPrec :: ReadPrec [TruthValue] # | |
| Show TruthValue Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> TruthValue -> ShowS # show :: TruthValue -> String # showList :: [TruthValue] -> ShowS # | |
| Eq TruthValue Source # | |
Defined in Hydra.Langs.Sql.Ansi | |
| Ord TruthValue Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: TruthValue -> TruthValue -> Ordering # (<) :: TruthValue -> TruthValue -> Bool # (<=) :: TruthValue -> TruthValue -> Bool # (>) :: TruthValue -> TruthValue -> Bool # (>=) :: TruthValue -> TruthValue -> Bool # max :: TruthValue -> TruthValue -> TruthValue # min :: TruthValue -> TruthValue -> TruthValue # | |
_TruthValue :: Name Source #
data UnsignedLiteral Source #
Instances
| Read UnsignedLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS UnsignedLiteral # readList :: ReadS [UnsignedLiteral] # | |
| Show UnsignedLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> UnsignedLiteral -> ShowS # show :: UnsignedLiteral -> String # showList :: [UnsignedLiteral] -> ShowS # | |
| Eq UnsignedLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: UnsignedLiteral -> UnsignedLiteral -> Bool # (/=) :: UnsignedLiteral -> UnsignedLiteral -> Bool # | |
| Ord UnsignedLiteral Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: UnsignedLiteral -> UnsignedLiteral -> Ordering # (<) :: UnsignedLiteral -> UnsignedLiteral -> Bool # (<=) :: UnsignedLiteral -> UnsignedLiteral -> Bool # (>) :: UnsignedLiteral -> UnsignedLiteral -> Bool # (>=) :: UnsignedLiteral -> UnsignedLiteral -> Bool # max :: UnsignedLiteral -> UnsignedLiteral -> UnsignedLiteral # min :: UnsignedLiteral -> UnsignedLiteral -> UnsignedLiteral # | |
data UnsignedNumericLiteral Source #
Constructors
| UnsignedNumericLiteralExact ExactNumericLiteral | |
| UnsignedNumericLiteralApproximate ApproximateNumericLiteral |
Instances
data UnsignedValueSpecification Source #
Constructors
| UnsignedValueSpecificationLiteral UnsignedLiteral | |
| UnsignedValueSpecificationGeneral GeneralValueSpecification |
Instances
newtype UserDefinedTypeValueExpression Source #
Constructors
| UserDefinedTypeValueExpression | |
Instances
data ValueExpression Source #
Constructors
| ValueExpressionCommon CommonValueExpression | |
| ValueExpressionBoolean BooleanValueExpression | |
| ValueExpressionRow RowValueExpression |
Instances
| Read ValueExpression Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS ValueExpression # readList :: ReadS [ValueExpression] # | |
| Show ValueExpression Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> ValueExpression -> ShowS # show :: ValueExpression -> String # showList :: [ValueExpression] -> ShowS # | |
| Eq ValueExpression Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: ValueExpression -> ValueExpression -> Bool # (/=) :: ValueExpression -> ValueExpression -> Bool # | |
| Ord ValueExpression Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: ValueExpression -> ValueExpression -> Ordering # (<) :: ValueExpression -> ValueExpression -> Bool # (<=) :: ValueExpression -> ValueExpression -> Bool # (>) :: ValueExpression -> ValueExpression -> Bool # (>=) :: ValueExpression -> ValueExpression -> Bool # max :: ValueExpression -> ValueExpression -> ValueExpression # min :: ValueExpression -> ValueExpression -> ValueExpression # | |
data ValueExpressionPrimary Source #
Constructors
| ValueExpressionPrimaryParens ParenthesizedValueExpression | |
| ValueExpressionPrimaryNoparens NonparenthesizedValueExpressionPrimary |
Instances
data WindowFunction Source #
Constructors
| WindowFunction | |
Instances
| Read WindowFunction Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods readsPrec :: Int -> ReadS WindowFunction # readList :: ReadS [WindowFunction] # | |
| Show WindowFunction Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods showsPrec :: Int -> WindowFunction -> ShowS # show :: WindowFunction -> String # showList :: [WindowFunction] -> ShowS # | |
| Eq WindowFunction Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods (==) :: WindowFunction -> WindowFunction -> Bool # (/=) :: WindowFunction -> WindowFunction -> Bool # | |
| Ord WindowFunction Source # | |
Defined in Hydra.Langs.Sql.Ansi Methods compare :: WindowFunction -> WindowFunction -> Ordering # (<) :: WindowFunction -> WindowFunction -> Bool # (<=) :: WindowFunction -> WindowFunction -> Bool # (>) :: WindowFunction -> WindowFunction -> Bool # (>=) :: WindowFunction -> WindowFunction -> Bool # max :: WindowFunction -> WindowFunction -> WindowFunction # min :: WindowFunction -> WindowFunction -> WindowFunction # | |