{-# LANGUAGE OverloadedStrings #-}
module Hydra.Sources.Tier4.Langs.Sql.Ansi where
import Hydra.Sources.Tier3.All
import Hydra.Dsl.Grammars
import Hydra.Tools.GrammarToModule
import qualified Hydra.Dsl.Annotations as Ann
import qualified Hydra.Grammar as G
import qualified Data.List as L
sqlModule :: Module
sqlModule :: Module
sqlModule = Namespace -> Grammar -> Maybe [Char] -> Module
grammarToModule Namespace
ns Grammar
sqlGrammar (Maybe [Char] -> Module) -> Maybe [Char] -> Module
forall a b. (a -> b) -> a -> b
$
[Char] -> Maybe [Char]
forall a. a -> Maybe a
Just ([Char]
"A subset of ANSI SQL:2003, capturing selected productions of the BNF grammar provided at "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"https://ronsavage.github.io/SQL/sql-2003-2.bnf.html, which is based on "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"the Final Committee Draft (FCD) of ISO/IEC 9075-2:2003")
where
ns :: Namespace
ns = [Char] -> Namespace
Namespace [Char]
"hydra/langs/sql/ansi"
sqlGrammar :: G.Grammar
sqlGrammar :: Grammar
sqlGrammar = [Production] -> Grammar
G.Grammar ([Production] -> Grammar) -> [Production] -> Grammar
forall a b. (a -> b) -> a -> b
$ [Production]
tokens [Production] -> [Production] -> [Production]
forall a. [a] -> [a] -> [a]
++ [Production]
productions
tokens :: [G.Production]
tokens :: [Production]
tokens = [
[Char] -> [Pattern] -> Production
define [Char]
"ApproximateNumericLiteral" [[Char] -> Pattern
regex ([Char] -> Pattern) -> [Char] -> Pattern
forall a b. (a -> b) -> a -> b
$ [Char]
mantissa [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"E" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
exponent],
[Char] -> [Pattern] -> Production
define [Char]
"BinaryStringLiteral" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"CharacterStringLiteral" [[Char] -> Pattern
regex ([Char] -> Pattern) -> [Char] -> Pattern
forall a b. (a -> b) -> a -> b
$
[Char] -> [Char]
opt([Char]
introducer [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
characterSetSpecification)
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
quote [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
star([Char]
characterRepresentation) [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
quote
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
star([Char]
separator [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
quote [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
star([Char]
characterRepresentation) [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
quote)],
[Char] -> [Pattern] -> Production
define [Char]
"ColumnName" [[Char] -> Pattern
regex [Char]
identifier],
[Char] -> [Pattern] -> Production
define [Char]
"DateString" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"DomainName" [[Char] -> Pattern
regex [Char]
schemaQualifiedName],
[Char] -> [Pattern] -> Production
define [Char]
"ExactNumericLiteral" [[Char] -> Pattern
regex ([Char] -> Pattern) -> [Char] -> Pattern
forall a b. (a -> b) -> a -> b
$ [[Char]] -> [Char]
or [
[Char]
unsignedInteger [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
opt ([Char]
period [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
unsignedInteger),
[Char]
period [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
unsignedInteger]],
[Char] -> [Pattern] -> Production
define [Char]
"LeftBracketOrTrigraph" [[Char] -> Pattern
regex ([Char] -> Pattern) -> [Char] -> Pattern
forall a b. (a -> b) -> a -> b
$ [[Char]] -> [Char]
or [[Char]
leftBracket, [Char]
leftBracketTrigraph]],
[Char] -> [Pattern] -> Production
define [Char]
"RightBracketOrTrigraph" [[Char] -> Pattern
regex ([Char] -> Pattern) -> [Char] -> Pattern
forall a b. (a -> b) -> a -> b
$ [[Char]] -> [Char]
or [[Char]
rightBracket, [Char]
rightBracketTrigraph]],
[Char] -> [Pattern] -> Production
define [Char]
"NationalCharacterStringLiteral" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"PathResolvedUserDefinedTypeName" [[Char] -> Pattern
regex [Char]
userDefinedTypeName],
[Char] -> [Pattern] -> Production
define [Char]
"TableName" [[Char] -> Pattern
regex [Char]
localOrSchemaQualifiedName],
[Char] -> [Pattern] -> Production
define [Char]
"TimeString" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"TimestampLiteral" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"UnicodeCharacterStringLiteral" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"UnsignedInteger" [[Char] -> Pattern
regex [Char]
unsignedInteger]]
where
opt :: [Char] -> [Char]
opt [Char]
pat = [Char] -> [Char]
par [Char]
pat [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"?"
or :: [[Char]] -> [Char]
or [[Char]]
pats = [Char] -> [Char]
par ([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$ [Char] -> [[Char]] -> [Char]
forall a. [a] -> [[a]] -> [a]
L.intercalate [Char]
"|" ([Char] -> [Char]
par ([Char] -> [Char]) -> [[Char]] -> [[Char]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [[Char]]
pats)
par :: [Char] -> [Char]
par [Char]
pat = [Char]
"(" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
pat [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
")"
plus :: [Char] -> [Char]
plus [Char]
pat = [Char] -> [Char]
par [Char]
pat [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"+"
star :: [Char] -> [Char]
star [Char]
pat = [Char] -> [Char]
par [Char]
pat [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"*"
actualIdentifier :: [Char]
actualIdentifier = [Char]
regularIdentifier
asterisk :: [Char]
asterisk = [Char]
"*"
bracketedComment :: [Char]
bracketedComment = [Char]
bracketedCommentIntroducer [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
bracketedCommentContents [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
bracketedCommentTerminator
bracketedCommentContents :: [Char]
bracketedCommentContents = [Char] -> [Char]
star ([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$ [[Char]] -> [Char]
or [[Char]
commentCharacter, [Char]
separator]
bracketedCommentIntroducer :: [Char]
bracketedCommentIntroducer = [Char]
slash [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
asterisk
bracketedCommentTerminator :: [Char]
bracketedCommentTerminator = [Char]
asterisk [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
slash
catalogName :: [Char]
catalogName = [Char]
identifier
characterRepresentation :: [Char]
characterRepresentation = [[Char]] -> [Char]
or [[Char]
nonquoteCharacter, [Char]
quoteSymbol]
characterSetSpecification :: [Char]
characterSetSpecification = [Char]
""
comment :: [Char]
comment = [[Char]] -> [Char]
or[[Char]
simpleComment, [Char]
bracketedComment]
commentCharacter :: [Char]
commentCharacter = [[Char]] -> [Char]
or [[Char]
nonquoteCharacter, [Char]
quote]
digit :: [Char]
digit = [Char]
"[0-9]"
exactNumericLiteral :: [Char]
exactNumericLiteral = [[Char]] -> [Char]
or [
[Char]
unsignedInteger [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
opt ([Char]
period [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
opt [Char]
unsignedInteger),
[Char]
period [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
unsignedInteger]
exponent :: [Char]
exponent = [Char]
signedInteger
identifier :: [Char]
identifier = [Char]
actualIdentifier
identifierBody :: [Char]
identifierBody = [Char]
identifierStart [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
star [Char]
identifierPart
identifierExtend :: [Char]
identifierExtend = [Char]
"[0-9_]"
identifierPart :: [Char]
identifierPart = [[Char]] -> [Char]
or [[Char]
identifierStart, [Char]
identifierExtend]
identifierStart :: [Char]
identifierStart = [Char]
"[A-Za-z]"
introducer :: [Char]
introducer = [Char]
underscore
leftBracket :: [Char]
leftBracket = [Char]
"["
leftBracketTrigraph :: [Char]
leftBracketTrigraph = [Char]
"??("
localOrSchemaQualifier :: [Char]
localOrSchemaQualifier = [[Char]] -> [Char]
or [[Char]
schemaName, [Char]
"MODULE"]
localOrSchemaQualifiedName :: [Char]
localOrSchemaQualifiedName = [Char] -> [Char]
opt ([Char]
localOrSchemaQualifier [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
period) [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
qualifiedIdentifier
mantissa :: [Char]
mantissa = [Char]
exactNumericLiteral
minusSign :: [Char]
minusSign = [Char]
"-"
newline :: [Char]
newline = [Char]
"[\\n]"
nonquoteCharacter :: [Char]
nonquoteCharacter = [Char]
"[ -&(-~]"
period :: [Char]
period = [Char]
"[.]"
plusSign :: [Char]
plusSign = [Char]
"+"
quote :: [Char]
quote = [Char]
"'"
quoteSymbol :: [Char]
quoteSymbol = [Char]
quote [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
quote
qualifiedIdentifier :: [Char]
qualifiedIdentifier = [Char]
identifier
regularIdentifier :: [Char]
regularIdentifier = [Char]
identifierBody
rightBracket :: [Char]
rightBracket = [Char]
"]"
rightBracketTrigraph :: [Char]
rightBracketTrigraph = [Char]
"??)"
separator :: [Char]
separator = [Char] -> [Char]
star([[Char]] -> [Char]
or[[Char]
comment, [Char]
whiteSpace])
schemaName :: [Char]
schemaName = [Char] -> [Char]
opt ([Char]
catalogName [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
period) [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
unqualifiedSchemaName
schemaQualifiedName :: [Char]
schemaQualifiedName = [Char] -> [Char]
opt ([Char]
schemaName [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
period) [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
qualifiedIdentifier
schemaQualifiedTypeName :: [Char]
schemaQualifiedTypeName = [Char] -> [Char]
opt ([Char]
schemaName [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
period) [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
qualifiedIdentifier
sign :: [Char]
sign = [[Char]] -> [Char]
or [[Char]
plusSign, [Char]
minusSign]
signedInteger :: [Char]
signedInteger = [Char] -> [Char]
opt [Char]
sign [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
unsignedInteger
simpleComment :: [Char]
simpleComment = [Char]
simpleCommentIntroducer [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
star([Char]
commentCharacter) [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
newline
simpleCommentIntroducer :: [Char]
simpleCommentIntroducer = [Char]
minusSign [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
plus([Char]
minusSign)
slash :: [Char]
slash = [Char]
"/"
underscore :: [Char]
underscore = [Char]
"_"
unqualifiedSchemaName :: [Char]
unqualifiedSchemaName = [Char]
schemaName
unsignedInteger :: [Char]
unsignedInteger = [Char] -> [Char]
plus [Char]
digit
userDefinedTypeName :: [Char]
userDefinedTypeName = [Char]
schemaQualifiedTypeName
whiteSpace :: [Char]
whiteSpace = [Char]
"[ \\t]"
productions :: [G.Production]
productions :: [Production]
productions = [
[Char] -> [Pattern] -> Production
define [Char]
"ApproximateNumericType" [
[Char]
"float"[Char] -> Pattern -> Pattern
>: [Pattern] -> Pattern
list[Pattern
float_, Pattern -> Pattern
opt([Pattern] -> Pattern
parens[Pattern
"Precision"])],
[Char]
"real"[Char] -> Pattern -> Pattern
>: Pattern
real_,
[Char]
"double"[Char] -> Pattern -> Pattern
>: Pattern
double_precision_],
[Char] -> [Pattern] -> Production
define [Char]
"ArrayElement" [
Pattern
"ValueExpression"],
[Char] -> [Pattern] -> Production
define [Char]
"ArrayElementList" [Pattern -> Pattern
commaList Pattern
"ArrayElement"],
[Char] -> [Pattern] -> Production
define [Char]
"ArrayElementReference" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"ArrayType" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"ArrayValueConstructor" [
[Char]
"enumeration"[Char] -> Pattern -> Pattern
>: Pattern
"ArrayValueConstructorByEnumeration",
[Char]
"query"[Char] -> Pattern -> Pattern
>: Pattern
"ArrayValueConstructorByQuery"],
[Char] -> [Pattern] -> Production
define [Char]
"ArrayValueConstructorByQuery" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"ArrayValueConstructorByEnumeration" [
[Pattern] -> Pattern
list[Pattern
array_, Pattern
"LeftBracketOrTrigraph", Pattern
"ArrayElementList", Pattern
"RightBracketOrTrigraph"]],
[Char] -> [Pattern] -> Production
define [Char]
"ArrayValueExpression" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"AsSubqueryClause" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"AttributeOrMethodReference" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"BinaryLargeObjectStringType" [
[Char]
"binary"[Char] -> Pattern -> Pattern
>: [Pattern] -> Pattern
list[Pattern
binary_large_object_, Pattern -> Pattern
opt([Pattern] -> Pattern
parens[Pattern
"LargeObjectLength"])],
[Char]
"blob"[Char] -> Pattern -> Pattern
>: [Pattern] -> Pattern
list[Pattern
blob_, Pattern -> Pattern
opt([Pattern] -> Pattern
parens[Pattern
"LargeObjectLength"])]],
[Char] -> [Pattern] -> Production
define [Char]
"BooleanFactor" [
[Pattern] -> Pattern
list[Pattern -> Pattern
opt(Pattern
not_), Pattern
"BooleanTest"]],
[Char] -> [Pattern] -> Production
define [Char]
"BooleanLiteral" [
Pattern
true_,
Pattern
false_,
Pattern
unknown_],
[Char] -> [Pattern] -> Production
define [Char]
"BooleanPredicand" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"BooleanPrimary" [
[Char]
"predicate"[Char] -> Pattern -> Pattern
>: Pattern
"Predicate",
[Char]
"predicand"[Char] -> Pattern -> Pattern
>: Pattern
"BooleanPredicand"],
[Char] -> [Pattern] -> Production
define [Char]
"BooleanTerm" [
[Char]
"factor"[Char] -> Pattern -> Pattern
>: Pattern
"BooleanFactor",
[Char]
"and"[Char] -> Pattern -> Pattern
>: [Pattern] -> Pattern
list[
[Char]
"lhs"[Char] -> Pattern -> Pattern
>: Pattern
"BooleanTerm",
Pattern
and_,
[Char]
"rhs"[Char] -> Pattern -> Pattern
>: Pattern
"BooleanFactor"]],
[Char] -> [Pattern] -> Production
define [Char]
"BooleanTest" [
[Pattern] -> Pattern
list[Pattern
"BooleanPrimary", Pattern -> Pattern
opt([Pattern] -> Pattern
list[Pattern
is_, Pattern -> Pattern
opt(Pattern
not_), Pattern
"TruthValue"])]],
[Char] -> [Pattern] -> Production
define [Char]
"BooleanType" [
Pattern
boolean_],
[Char] -> [Pattern] -> Production
define [Char]
"BooleanValueExpression" [
[Char]
"term"[Char] -> Pattern -> Pattern
>: Pattern
"BooleanTerm",
[Char]
"or"[Char] -> Pattern -> Pattern
>: [Pattern] -> Pattern
list[
[Char]
"lhs"[Char] -> Pattern -> Pattern
>: Pattern
"BooleanValueExpression",
Pattern
or_,
[Char]
"rhs"[Char] -> Pattern -> Pattern
>: Pattern
"BooleanTerm"]],
[Char] -> [Pattern] -> Production
define [Char]
"CaseExpression" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"CastSpecification" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"CharacterSetSpecification" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"CharacterStringType" [
[Char]
"character"[Char] -> Pattern -> Pattern
>: [Pattern] -> Pattern
list[Pattern
character_, Pattern -> Pattern
opt([Pattern] -> Pattern
parens[Pattern
"Length"])],
[Char]
"char"[Char] -> Pattern -> Pattern
>: [Pattern] -> Pattern
list[Pattern
char_, Pattern -> Pattern
opt([Pattern] -> Pattern
parens[Pattern
"Length"])],
[Char]
"characterVarying"[Char] -> Pattern -> Pattern
>: [Pattern] -> Pattern
list[Pattern
character_varying_, Pattern
left_paren_, Pattern
"Length", Pattern
right_paren_],
[Char]
"charVarying"[Char] -> Pattern -> Pattern
>: [Pattern] -> Pattern
list[Pattern
char_varying_, Pattern
left_paren_, Pattern
"Length", Pattern
right_paren_],
[Char]
"varchar"[Char] -> Pattern -> Pattern
>: [Pattern] -> Pattern
list[Pattern
varchar_, Pattern
left_paren_, Pattern
"Length", Pattern
right_paren_],
[Char]
"characterLargeObject"[Char] -> Pattern -> Pattern
>: [Pattern] -> Pattern
list[Pattern
character_large_object_, Pattern -> Pattern
opt([Pattern] -> Pattern
parens[Pattern
"LargeObjectLength"])],
[Char]
"charLargeObject"[Char] -> Pattern -> Pattern
>: [Pattern] -> Pattern
list[Pattern
char_large_object_, Pattern -> Pattern
opt([Pattern] -> Pattern
parens[Pattern
"LargeObjectLength"])],
[Char]
"clob"[Char] -> Pattern -> Pattern
>: [Pattern] -> Pattern
list[Pattern
clob_, Pattern -> Pattern
opt([Pattern] -> Pattern
parens[Pattern
"LargeObjectLength"])]],
[Char] -> [Pattern] -> Production
define [Char]
"CollateClause" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"CollectionType" [
[Char]
"array"[Char] -> Pattern -> Pattern
>: Pattern
"ArrayType",
[Char]
"multiset"[Char] -> Pattern -> Pattern
>: Pattern
"MultisetType"],
[Char] -> [Pattern] -> Production
define [Char]
"CollectionValueConstructor" [
[Char]
"array"[Char] -> Pattern -> Pattern
>: Pattern
"ArrayValueConstructor",
[Char]
"multiset"[Char] -> Pattern -> Pattern
>: Pattern
"MultisetValueConstructor"],
[Char] -> [Pattern] -> Production
define [Char]
"CollectionValueExpression" [
[Char]
"array"[Char] -> Pattern -> Pattern
>: Pattern
"ArrayValueExpression",
[Char]
"multiset"[Char] -> Pattern -> Pattern
>: Pattern
"MultisetValueExpression"],
[Char] -> [Pattern] -> Production
define [Char]
"ColumnConstraintDefinition" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"ColumnDefinition" [
[Pattern] -> Pattern
list[
[Char]
"name"[Char] -> Pattern -> Pattern
>: Pattern
"ColumnName",
[Char]
"typeOrDomain"[Char] -> Pattern -> Pattern
>: Pattern -> Pattern
opt([Pattern] -> Pattern
alts[Pattern
"DataType", Pattern
"DomainName"]),
[Char]
"refScope"[Char] -> Pattern -> Pattern
>: Pattern -> Pattern
optPattern
"ReferenceScopeCheck",
[Char]
"defaultOrIdentityOrGeneration"[Char] -> Pattern -> Pattern
>: Pattern -> Pattern
opt([Pattern] -> Pattern
alts[Pattern
"DefaultClause", Pattern
"IdentityColumnSpecification", Pattern
"GenerationClause"]),
[Char]
"constraints"[Char] -> Pattern -> Pattern
>: Pattern -> Pattern
starPattern
"ColumnConstraintDefinition",
[Char]
"collate"[Char] -> Pattern -> Pattern
>: Pattern -> Pattern
optPattern
"CollateClause"]],
[Char] -> [Pattern] -> Production
define [Char]
"ColumnNameList" [Pattern -> Pattern
commaList Pattern
"ColumnName"],
[Char] -> [Pattern] -> Production
define [Char]
"ColumnOptions" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"ColumnReference" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"CommonValueExpression" [
[Char]
"numeric"[Char] -> Pattern -> Pattern
>: Pattern
"NumericValueExpression",
[Char]
"string"[Char] -> Pattern -> Pattern
>: Pattern
"StringValueExpression",
[Char]
"datetime"[Char] -> Pattern -> Pattern
>: Pattern
"DatetimeValueExpression",
[Char]
"interval"[Char] -> Pattern -> Pattern
>: Pattern
"IntervalValueExpression",
[Char]
"userDefined"[Char] -> Pattern -> Pattern
>: Pattern
"UserDefinedTypeValueExpression",
[Char]
"reference"[Char] -> Pattern -> Pattern
>: Pattern
"ReferenceValueExpression",
[Char]
"collection"[Char] -> Pattern -> Pattern
>: Pattern
"CollectionValueExpression"],
[Char] -> [Pattern] -> Production
define [Char]
"ContextuallyTypedRowValueExpression" [
[Char]
"specialCase"[Char] -> Pattern -> Pattern
>: Pattern
"RowValueSpecialCase",
[Char]
"constructor"[Char] -> Pattern -> Pattern
>: Pattern
"ContextuallyTypedRowValueConstructor"],
[Char] -> [Pattern] -> Production
define [Char]
"ContextuallyTypedRowValueConstructor" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"ContextuallyTypedRowValueExpressionList" [Pattern -> Pattern
commaList Pattern
"ContextuallyTypedRowValueExpression"],
[Char] -> [Pattern] -> Production
define [Char]
"ContextuallyTypedTableValueConstructor" [
[Pattern] -> Pattern
list[Pattern
values_, Pattern
"ContextuallyTypedRowValueExpressionList"]],
[Char] -> [Pattern] -> Production
define [Char]
"DataType" [
[Char]
"predefined"[Char] -> Pattern -> Pattern
>: Pattern
"PredefinedType",
[Char]
"row"[Char] -> Pattern -> Pattern
>: Pattern
"RowType",
[Char]
"named"[Char] -> Pattern -> Pattern
>: Pattern
"PathResolvedUserDefinedTypeName",
[Char]
"reference"[Char] -> Pattern -> Pattern
>: Pattern
"ReferenceType",
[Char]
"collection"[Char] -> Pattern -> Pattern
>: Pattern
"CollectionType"],
[Char] -> [Pattern] -> Production
define [Char]
"DateLiteral" [
[Pattern] -> Pattern
list[Pattern
date_, Pattern
"DateString"]],
[Char] -> [Pattern] -> Production
define [Char]
"DatetimeLiteral" [
[Char]
"date"[Char] -> Pattern -> Pattern
>: Pattern
"DateLiteral",
[Char]
"time"[Char] -> Pattern -> Pattern
>: Pattern
"TimeLiteral",
[Char]
"timestamp"[Char] -> Pattern -> Pattern
>: Pattern
"TimestampLiteral"],
[Char] -> [Pattern] -> Production
define [Char]
"DatetimeType" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"DatetimeValueExpression" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"DefaultClause" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"ExactNumericType" [
[Char]
"numeric"[Char] -> Pattern -> Pattern
>: [Pattern] -> Pattern
list[Pattern
numeric_, Pattern -> Pattern
opt([Pattern] -> Pattern
parens[Pattern
"Precision", Pattern -> Pattern
opt([Pattern] -> Pattern
list[Pattern
comma_, Pattern
"Scale"])])],
[Char]
"decimal"[Char] -> Pattern -> Pattern
>: [Pattern] -> Pattern
list[Pattern
decimal_, Pattern -> Pattern
opt([Pattern] -> Pattern
parens[Pattern
"Precision", Pattern -> Pattern
opt([Pattern] -> Pattern
list[Pattern
comma_, Pattern
"Scale"])])],
[Char]
"dec"[Char] -> Pattern -> Pattern
>: [Pattern] -> Pattern
list[Pattern
dec_, Pattern -> Pattern
opt([Pattern] -> Pattern
parens[Pattern
"Precision", Pattern -> Pattern
opt([Pattern] -> Pattern
list[Pattern
comma_, Pattern
"Scale"])])],
[Char]
"smallint"[Char] -> Pattern -> Pattern
>: Pattern
smallint_,
[Char]
"integer"[Char] -> Pattern -> Pattern
>: Pattern
integer_,
[Char]
"int"[Char] -> Pattern -> Pattern
>: Pattern
int_,
[Char]
"bigint"[Char] -> Pattern -> Pattern
>: Pattern
bigint_],
[Char] -> [Pattern] -> Production
define [Char]
"FieldReference" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"FromConstructor" [
[Pattern] -> Pattern
list[
[Char]
"columns"[Char] -> Pattern -> Pattern
>: Pattern -> Pattern
opt([Pattern] -> Pattern
parens[Pattern
"InsertColumnList"]),
[Char]
"override"[Char] -> Pattern -> Pattern
>: Pattern -> Pattern
optPattern
"OverrideClause",
[Char]
"values"[Char] -> Pattern -> Pattern
>: Pattern
"ContextuallyTypedTableValueConstructor"]],
[Char] -> [Pattern] -> Production
define [Char]
"FromDefault" [
Pattern
default_values_],
[Char] -> [Pattern] -> Production
define [Char]
"FromSubquery" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"GeneralLiteral" [
[Char]
"string"[Char] -> Pattern -> Pattern
>: Pattern
"CharacterStringLiteral",
[Char]
"nationalString"[Char] -> Pattern -> Pattern
>: Pattern
"NationalCharacterStringLiteral",
[Char]
"unicode"[Char] -> Pattern -> Pattern
>: Pattern
"UnicodeCharacterStringLiteral",
[Char]
"binary"[Char] -> Pattern -> Pattern
>: Pattern
"BinaryStringLiteral",
[Char]
"dateTime"[Char] -> Pattern -> Pattern
>: Pattern
"DatetimeLiteral",
[Char]
"interval"[Char] -> Pattern -> Pattern
>: Pattern
"IntervalLiteral",
[Char]
"boolean"[Char] -> Pattern -> Pattern
>: Pattern
"BooleanLiteral"],
[Char] -> [Pattern] -> Production
define [Char]
"GeneralValueSpecification" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"GenerationClause" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"GlobalOrLocal" [
[Char]
"global"[Char] -> Pattern -> Pattern
>: Pattern
global_,
[Char]
"local"[Char] -> Pattern -> Pattern
>: Pattern
local_],
[Char] -> [Pattern] -> Production
define [Char]
"IdentityColumnSpecification" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"InsertColumnList" [
Pattern
"ColumnNameList"],
[Char] -> [Pattern] -> Production
define [Char]
"InsertColumnsAndSource" [
[Char]
"subquery"[Char] -> Pattern -> Pattern
>: Pattern
"FromSubquery",
[Char]
"constructor"[Char] -> Pattern -> Pattern
>: Pattern
"FromConstructor",
[Char]
"default"[Char] -> Pattern -> Pattern
>: Pattern
"FromDefault"],
[Char] -> [Pattern] -> Production
define [Char]
"InsertStatement" [
[Pattern] -> Pattern
list[
Pattern
insert_into_,
[Char]
"target"[Char] -> Pattern -> Pattern
>: Pattern
"InsertionTarget",
[Char]
"columnsAndSource"[Char] -> Pattern -> Pattern
>: Pattern
"InsertColumnsAndSource"]],
[Char] -> [Pattern] -> Production
define [Char]
"InsertionTarget" [
Pattern
"TableName"],
[Char] -> [Pattern] -> Production
define [Char]
"IntervalLiteral" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"IntervalType" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"IntervalValueExpression" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"LargeObjectLength" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"Length" [
Pattern
"UnsignedInteger"],
[Char] -> [Pattern] -> Production
define [Char]
"LikeClause" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"MethodInvocation" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"MultisetElementReference" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"MultisetType" [
[Pattern] -> Pattern
list[Pattern
"DataType", Pattern
multiset_]],
[Char] -> [Pattern] -> Production
define [Char]
"MultisetValueConstructor" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"MultisetValueExpression" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"NationalCharacterStringType" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"NewSpecification" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"NextValueExpression" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"NumericType" [
[Char]
"exact"[Char] -> Pattern -> Pattern
>: Pattern
"ExactNumericType",
[Char]
"approximate"[Char] -> Pattern -> Pattern
>: Pattern
"ApproximateNumericType"],
[Char] -> [Pattern] -> Production
define [Char]
"NumericValueExpression" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"OverrideClause" [
Pattern
overriding_user_value_,
Pattern
overriding_system_value],
[Char] -> [Pattern] -> Production
define [Char]
"ParenthesizedValueExpression" [
[Pattern] -> Pattern
parens[Pattern
"ValueExpression"]],
[Char] -> [Pattern] -> Production
define [Char]
"Precision" [
Pattern
"UnsignedInteger"],
[Char] -> [Pattern] -> Production
define [Char]
"PredefinedType" [
[Char]
"string"[Char] -> Pattern -> Pattern
>: [Pattern] -> Pattern
list[
[Char]
"type"[Char] -> Pattern -> Pattern
>: Pattern
"CharacterStringType",
[Char]
"characters"[Char] -> Pattern -> Pattern
>: Pattern -> Pattern
opt([Pattern] -> Pattern
list[Pattern
character_set_, Pattern
"CharacterSetSpecification"]),
[Char]
"collate"[Char] -> Pattern -> Pattern
>: Pattern -> Pattern
optPattern
"CollateClause"],
[Char]
"nationalString"[Char] -> Pattern -> Pattern
>: [Pattern] -> Pattern
list[
[Char]
"type"[Char] -> Pattern -> Pattern
>: Pattern
"NationalCharacterStringType",
[Char]
"collate"[Char] -> Pattern -> Pattern
>: Pattern -> Pattern
optPattern
"CollateClause"],
[Char]
"blob"[Char] -> Pattern -> Pattern
>: Pattern
"BinaryLargeObjectStringType",
[Char]
"numeric"[Char] -> Pattern -> Pattern
>: Pattern
"NumericType",
[Char]
"boolean"[Char] -> Pattern -> Pattern
>: Pattern
"BooleanType",
[Char]
"datetime"[Char] -> Pattern -> Pattern
>: Pattern
"DatetimeType",
[Char]
"interval"[Char] -> Pattern -> Pattern
>: Pattern
"IntervalType"],
[Char] -> [Pattern] -> Production
define [Char]
"Predicate" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"QueryExpression" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"ReferenceScopeCheck" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"ReferenceType" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"RowType" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"RowValueSpecialCase" [
Pattern
"NonparenthesizedValueExpressionPrimary"],
[Char] -> [Pattern] -> Production
define [Char]
"NonparenthesizedValueExpressionPrimary" [
[Char]
"unsigned"[Char] -> Pattern -> Pattern
>: Pattern
"UnsignedValueSpecification",
[Char]
"column"[Char] -> Pattern -> Pattern
>: Pattern
"ColumnReference",
[Char]
"setFunction"[Char] -> Pattern -> Pattern
>: Pattern
"SetFunctionSpecification",
[Char]
"windowFunction"[Char] -> Pattern -> Pattern
>: Pattern
"WindowFunction",
[Char]
"scalarSubquery"[Char] -> Pattern -> Pattern
>: Pattern
"ScalarSubquery",
[Char]
"cases"[Char] -> Pattern -> Pattern
>: Pattern
"CaseExpression",
[Char]
"cast"[Char] -> Pattern -> Pattern
>: Pattern
"CastSpecification",
[Char]
"field"[Char] -> Pattern -> Pattern
>: Pattern
"FieldReference",
[Char]
"subtype"[Char] -> Pattern -> Pattern
>: Pattern
"SubtypeTreatment",
[Char]
"method"[Char] -> Pattern -> Pattern
>: Pattern
"MethodInvocation",
[Char]
"staticMethod"[Char] -> Pattern -> Pattern
>: Pattern
"StaticMethodInvocation",
[Char]
"new"[Char] -> Pattern -> Pattern
>: Pattern
"NewSpecification",
[Char]
"attributeOrMethod"[Char] -> Pattern -> Pattern
>: Pattern
"AttributeOrMethodReference",
[Char]
"reference"[Char] -> Pattern -> Pattern
>: Pattern
"ReferenceResolution",
[Char]
"collection"[Char] -> Pattern -> Pattern
>: Pattern
"CollectionValueConstructor",
[Char]
"arrayElement"[Char] -> Pattern -> Pattern
>: Pattern
"ArrayElementReference",
[Char]
"multisetElement"[Char] -> Pattern -> Pattern
>: Pattern
"MultisetElementReference",
[Char]
"routine"[Char] -> Pattern -> Pattern
>: Pattern
"RoutineInvocation",
[Char]
"next"[Char] -> Pattern -> Pattern
>: Pattern
"NextValueExpression"],
[Char] -> [Pattern] -> Production
define [Char]
"ReferenceResolution" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"ReferenceValueExpression" [
Pattern
"ValueExpressionPrimary"],
[Char] -> [Pattern] -> Production
define [Char]
"RowValueExpression" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"RoutineInvocation" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"ScalarSubquery" [
Pattern
"Subquery"],
[Char] -> [Pattern] -> Production
define [Char]
"Scale" [
Pattern
"UnsignedInteger"],
[Char] -> [Pattern] -> Production
define [Char]
"SelfReferencingColumnSpecification" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"SetFunctionSpecification" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"StaticMethodInvocation" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"StringValueExpression" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"Subquery" [
[Pattern] -> Pattern
parens[Pattern
"QueryExpression"]],
[Char] -> [Pattern] -> Production
define [Char]
"SubtableClause" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"SubtypeTreatment" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"TableCommitAction" [
[Char]
"preserve"[Char] -> Pattern -> Pattern
>: Pattern
preserve_,
[Char]
"delete"[Char] -> Pattern -> Pattern
>: Pattern
delete_],
[Char] -> [Pattern] -> Production
define [Char]
"TableConstraintDefinition" [Pattern]
unsupported,
[Char] -> [Pattern] -> Production
define [Char]
"TableContentsSource" [
[Char]
"list"[Char] -> Pattern -> Pattern
>: Pattern
"TableElementList",
[Char]
"subtable"[Char] -> Pattern -> Pattern
>: [Pattern] -> Pattern
list [
Pattern
of_,
[Char]
"type"[Char] -> Pattern -> Pattern
>: Pattern
"PathResolvedUserDefinedTypeName",
[Char]
"subtable"[Char] -> Pattern -> Pattern
>: Pattern -> Pattern
optPattern
"SubtableClause",
[Char]
"elements"[Char] -> Pattern -> Pattern
>: Pattern -> Pattern
optPattern
"TableElementList"],
[Char]
"subquery"[Char] -> Pattern -> Pattern
>: Pattern
"AsSubqueryClause"],
[Char] -> [Pattern] -> Production
define [Char]
"TableDefinition" [
[Pattern] -> Pattern
list[
Pattern
create_,
[Char]
"scope"[Char] -> Pattern -> Pattern
>: Pattern -> Pattern
optPattern
"TableScope",
Pattern
table_,
[Char]
"name"[Char] -> Pattern -> Pattern
>: Pattern
"TableName",
[Char]
"source"[Char] -> Pattern -> Pattern
>: Pattern
"TableContentsSource",
[Char]
"commitActions"[Char] -> Pattern -> Pattern
>: Pattern -> Pattern
opt([Pattern] -> Pattern
list[Pattern
on_commit_, Pattern
"TableCommitAction", Pattern
rows_])]],
[Char] -> [Pattern] -> Production
define [Char]
"TableElement" [
[Char]
"column"[Char] -> Pattern -> Pattern
>: Pattern
"ColumnDefinition",
[Char]
"tableConstraint"[Char] -> Pattern -> Pattern
>: Pattern
"TableConstraintDefinition",
[Char]
"like"[Char] -> Pattern -> Pattern
>: Pattern
"LikeClause",
[Char]
"selfReferencingColumn"[Char] -> Pattern -> Pattern
>: Pattern
"SelfReferencingColumnSpecification",
[Char]
"columOptions"[Char] -> Pattern -> Pattern
>: Pattern
"ColumnOptions"],
[Char] -> [Pattern] -> Production
define [Char]
"TableElementList" [
[Pattern] -> Pattern
parens[Pattern -> Pattern
commaList Pattern
"TableElement"]],
[Char] -> [Pattern] -> Production
define [Char]
"TableScope" [
[Pattern] -> Pattern
list[Pattern
"GlobalOrLocal", Pattern
temporary_]],
[Char] -> [Pattern] -> Production
define [Char]
"TimeLiteral" [
[Pattern] -> Pattern
list[Pattern
time_, Pattern
"TimeString"]],
[Char] -> [Pattern] -> Production
define [Char]
"TruthValue" [
Pattern
true_,
Pattern
false_,
Pattern
unknown_],
[Char] -> [Pattern] -> Production
define [Char]
"UnsignedLiteral" [
[Char]
"numeric"[Char] -> Pattern -> Pattern
>: Pattern
"UnsignedNumericLiteral",
[Char]
"general"[Char] -> Pattern -> Pattern
>: Pattern
"GeneralLiteral"],
[Char] -> [Pattern] -> Production
define [Char]
"UnsignedNumericLiteral" [
[Char]
"exact"[Char] -> Pattern -> Pattern
>: Pattern
"ExactNumericLiteral",
[Char]
"approximate"[Char] -> Pattern -> Pattern
>: Pattern
"ApproximateNumericLiteral"],
[Char] -> [Pattern] -> Production
define [Char]
"UnsignedValueSpecification" [
[Char]
"literal"[Char] -> Pattern -> Pattern
>: Pattern
"UnsignedLiteral",
[Char]
"general"[Char] -> Pattern -> Pattern
>: Pattern
"GeneralValueSpecification"],
[Char] -> [Pattern] -> Production
define [Char]
"UserDefinedTypeValueExpression" [
Pattern
"ValueExpressionPrimary"],
[Char] -> [Pattern] -> Production
define [Char]
"ValueExpression" [
[Char]
"common"[Char] -> Pattern -> Pattern
>: Pattern
"CommonValueExpression",
[Char]
"boolean"[Char] -> Pattern -> Pattern
>: Pattern
"BooleanValueExpression",
[Char]
"row"[Char] -> Pattern -> Pattern
>: Pattern
"RowValueExpression"],
[Char] -> [Pattern] -> Production
define [Char]
"ValueExpressionPrimary" [
[Char]
"parens"[Char] -> Pattern -> Pattern
>: Pattern
"ParenthesizedValueExpression",
[Char]
"noparens"[Char] -> Pattern -> Pattern
>: Pattern
"NonparenthesizedValueExpressionPrimary"],
[Char] -> [Pattern] -> Production
define [Char]
"WindowFunction" [Pattern]
unsupported]
and_ :: Pattern
and_ = [Char] -> Pattern
terminal [Char]
"AND"
array_ :: Pattern
array_ = [Char] -> Pattern
terminal [Char]
"ARRAY"
bigint_ :: Pattern
bigint_ = [Char] -> Pattern
terminal [Char]
"BIGINT"
binary_large_object_ :: Pattern
binary_large_object_ = [Char] -> Pattern
terminal [Char]
"BINARY LARGE OBJECT"
blob_ :: Pattern
blob_ = [Char] -> Pattern
terminal [Char]
"BLOB"
boolean_ :: Pattern
boolean_ = [Char] -> Pattern
terminal [Char]
"BOOLEAN"
char_ :: Pattern
char_ = [Char] -> Pattern
terminal [Char]
"CHAR"
char_large_object_ :: Pattern
char_large_object_ = [Char] -> Pattern
terminal [Char]
"CHAR LARGE OBJECT"
char_varying_ :: Pattern
char_varying_ = [Char] -> Pattern
terminal [Char]
"CHAR VARYING"
character_ :: Pattern
character_ = [Char] -> Pattern
terminal [Char]
"CHARACTER"
character_large_object_ :: Pattern
character_large_object_ = [Char] -> Pattern
terminal [Char]
"CHARACTER LARGE OBJECT"
character_set_ :: Pattern
character_set_ = [Char] -> Pattern
terminal [Char]
"CHARACTER SET"
character_varying_ :: Pattern
character_varying_ = [Char] -> Pattern
terminal [Char]
"CHARACTER VARYING"
clob_ :: Pattern
clob_ = [Char] -> Pattern
terminal [Char]
"CLOB"
comma_ :: Pattern
comma_ = [Char] -> Pattern
terminal [Char]
","
create_ :: Pattern
create_ = [Char] -> Pattern
terminal [Char]
"CREATE"
date_ :: Pattern
date_ = [Char] -> Pattern
terminal [Char]
"DATE"
dec_ :: Pattern
dec_ = [Char] -> Pattern
terminal [Char]
"DEC"
decimal_ :: Pattern
decimal_ = [Char] -> Pattern
terminal [Char]
"DECIMAL"
default_values_ :: Pattern
default_values_ = [Char] -> Pattern
terminal [Char]
"DEFAULT VALUES"
delete_ :: Pattern
delete_ = [Char] -> Pattern
terminal [Char]
"DELETE"
double_precision_ :: Pattern
double_precision_ = [Char] -> Pattern
terminal [Char]
"DOUBLE PRECISION"
false_ :: Pattern
false_ = [Char] -> Pattern
terminal [Char]
"FALSE"
float_ :: Pattern
float_ = [Char] -> Pattern
terminal [Char]
"FLOAT"
global_ :: Pattern
global_ = [Char] -> Pattern
terminal [Char]
"GLOBAL"
insert_into_ :: Pattern
insert_into_ = [Char] -> Pattern
terminal [Char]
"INSERT INTO"
int_ :: Pattern
int_ = [Char] -> Pattern
terminal [Char]
"INT"
integer_ :: Pattern
integer_ = [Char] -> Pattern
terminal [Char]
"INTEGER"
is_ :: Pattern
is_ = [Char] -> Pattern
terminal [Char]
"IS"
left_paren_ :: Pattern
left_paren_ = [Char] -> Pattern
terminal [Char]
"("
local_ :: Pattern
local_ = [Char] -> Pattern
terminal [Char]
"LOCAL"
multiset_ :: Pattern
multiset_ = [Char] -> Pattern
terminal [Char]
"MULTISET"
numeric_ :: Pattern
numeric_ = [Char] -> Pattern
terminal [Char]
"NUMERIC"
of_ :: Pattern
of_ = [Char] -> Pattern
terminal [Char]
"OF"
not_ :: Pattern
not_ = [Char] -> Pattern
terminal [Char]
"NOT"
on_commit_ :: Pattern
on_commit_ = [Char] -> Pattern
terminal [Char]
"ON COMMIT"
or_ :: Pattern
or_ = [Char] -> Pattern
terminal [Char]
"OR"
overriding_user_value_ :: Pattern
overriding_user_value_ = [Char] -> Pattern
terminal [Char]
"OVERRIDING USER VALUE"
overriding_system_value :: Pattern
overriding_system_value = [Char] -> Pattern
terminal [Char]
"OVERRIDING SYSTEM VALUE"
preserve_ :: Pattern
preserve_ = [Char] -> Pattern
terminal [Char]
"PRESERVE"
real_ :: Pattern
real_ = [Char] -> Pattern
terminal [Char]
"REAL"
right_paren_ :: Pattern
right_paren_ = [Char] -> Pattern
terminal [Char]
")"
rows_ :: Pattern
rows_ = [Char] -> Pattern
terminal [Char]
"ROWS"
smallint_ :: Pattern
smallint_ = [Char] -> Pattern
terminal [Char]
"SMALLINT"
table_ :: Pattern
table_ = [Char] -> Pattern
terminal [Char]
"TABLE"
temporary_ :: Pattern
temporary_ = [Char] -> Pattern
terminal [Char]
"TEMPORARY"
time_ :: Pattern
time_ = [Char] -> Pattern
terminal [Char]
"TIME"
true_ :: Pattern
true_ = [Char] -> Pattern
terminal [Char]
"TRUE"
unknown_ :: Pattern
unknown_ = [Char] -> Pattern
terminal [Char]
"UNKNOWN"
values_ :: Pattern
values_ = [Char] -> Pattern
terminal [Char]
"VALUES"
varchar_ :: Pattern
varchar_ = [Char] -> Pattern
terminal [Char]
"VARCHAR"
commaList :: Pattern -> Pattern
commaList Pattern
pat = [Pattern] -> Pattern
list[
[Char]
"first"[Char] -> Pattern -> Pattern
>: Pattern
pat,
[Char]
"rest"[Char] -> Pattern -> Pattern
>: Pattern -> Pattern
star([Pattern] -> Pattern
list[Pattern
comma_, Pattern
pat])]
parens :: [Pattern] -> Pattern
parens [Pattern]
ps = [Pattern] -> Pattern
list ([Pattern] -> Pattern) -> [Pattern] -> Pattern
forall a b. (a -> b) -> a -> b
$ [Pattern
left_paren_] [Pattern] -> [Pattern] -> [Pattern]
forall a. [a] -> [a] -> [a]
++ [Pattern]
ps [Pattern] -> [Pattern] -> [Pattern]
forall a. [a] -> [a] -> [a]
++ [Pattern
right_paren_]
unsupported :: [Pattern]
unsupported = [[Char] -> Pattern
terminal [Char]
"unsupported"]