rename ValueExpr to ScalarExpr
This commit is contained in:
parent
09223c3de9
commit
a2645ace3f
|
@ -5,7 +5,7 @@ notes
|
|||
Public api
|
||||
Names - parsing identifiers
|
||||
Typenames
|
||||
Value expressions
|
||||
Scalar expressions
|
||||
simple literals
|
||||
star, param
|
||||
parens expression, row constructor and scalar subquery
|
||||
|
@ -14,7 +14,7 @@ Value expressions
|
|||
suffixes: in, between, quantified comparison, match predicate, array
|
||||
subscript, escape, collate
|
||||
operators
|
||||
value expression top level
|
||||
scalar expression top level
|
||||
helpers
|
||||
query expressions
|
||||
select lists
|
||||
|
@ -75,7 +75,7 @@ syntax.
|
|||
There are three big areas which are tricky to left factor:
|
||||
|
||||
* typenames
|
||||
* value expressions which can start with an identifier
|
||||
* scalar expressions which can start with an identifier
|
||||
* infix and suffix operators
|
||||
|
||||
=== typenames
|
||||
|
@ -87,9 +87,9 @@ future. Taking the approach in the standard grammar will limit the
|
|||
extensibility of the parser and might affect the ease of adapting to
|
||||
support other sql dialects.
|
||||
|
||||
=== identifier value expressions
|
||||
=== identifier scalar expressions
|
||||
|
||||
There are a lot of value expression nodes which start with
|
||||
There are a lot of scalar expression nodes which start with
|
||||
identifiers, and can't be distinguished the tokens after the initial
|
||||
identifier are parsed. Using try to implement these variations is very
|
||||
simple but makes the code much harder to debug and makes the parser
|
||||
|
@ -106,7 +106,7 @@ Here is a list of these nodes:
|
|||
|
||||
There is further ambiguity e.g. with typed literals with precision,
|
||||
functions, aggregates, etc. - these are an identifier, followed by
|
||||
parens comma separated value expressions or something similar, and it
|
||||
parens comma separated scalar expressions or something similar, and it
|
||||
is only later that we can find a token which tells us which flavour it
|
||||
is.
|
||||
|
||||
|
@ -163,10 +163,10 @@ the special case of interval type names. E.g. you can write 'int
|
|||
collate C' or 'int(15,2)' and this will parse as a character type name
|
||||
or a precision scale type name instead of being rejected.
|
||||
|
||||
value expressions: every variation on value expressions uses the same
|
||||
scalar expressions: every variation on scalar expressions uses the same
|
||||
parser/syntax. This means we don't try to stop non boolean valued
|
||||
expressions in boolean valued contexts in the parser. Another area
|
||||
this affects is that we allow general value expressions in group by,
|
||||
this affects is that we allow general scalar expressions in group by,
|
||||
whereas the standard only allows column names with optional collation.
|
||||
|
||||
These are all areas which are specified (roughly speaking) in the
|
||||
|
@ -178,7 +178,7 @@ fixing them in the syntax but leaving them till the semantic checking
|
|||
> -- | This is the module with the parser functions.
|
||||
> module Language.SQL.SimpleSQL.Parse
|
||||
> (parseQueryExpr
|
||||
> ,parseValueExpr
|
||||
> ,parseScalarExpr
|
||||
> ,parseStatement
|
||||
> ,parseStatements
|
||||
> ,ParseError(..)) where
|
||||
|
@ -250,8 +250,8 @@ fixing them in the syntax but leaving them till the semantic checking
|
|||
> -> Either ParseError [Statement]
|
||||
> parseStatements = wrapParse statements
|
||||
|
||||
> -- | Parses a value expression.
|
||||
> parseValueExpr :: Dialect
|
||||
> -- | Parses a scalar expression.
|
||||
> parseScalarExpr :: Dialect
|
||||
> -- ^ dialect of SQL to use
|
||||
> -> FilePath
|
||||
> -- ^ filename to use in error messages
|
||||
|
@ -260,8 +260,8 @@ fixing them in the syntax but leaving them till the semantic checking
|
|||
> -- in the source to use in error messages
|
||||
> -> String
|
||||
> -- ^ the SQL source to parse
|
||||
> -> Either ParseError ValueExpr
|
||||
> parseValueExpr = wrapParse valueExpr
|
||||
> -> Either ParseError ScalarExpr
|
||||
> parseScalarExpr = wrapParse scalarExpr
|
||||
|
||||
This helper function takes the parser given and:
|
||||
|
||||
|
@ -302,7 +302,7 @@ identifiers and unicode quoted identifiers.
|
|||
|
||||
Dots: dots in identifier chains are parsed here and represented in the
|
||||
Iden constructor usually. If parts of the chains are non identifier
|
||||
value expressions, then this is represented by a BinOp "."
|
||||
scalar expressions, then this is represented by a BinOp "."
|
||||
instead. Dotten chain identifiers which appear in other contexts (such
|
||||
as function names, table names, are represented as [Name] only.
|
||||
|
||||
|
@ -547,19 +547,19 @@ factoring in this function, and it is a little dense.
|
|||
> ,"varbinary"
|
||||
> ]
|
||||
|
||||
= Value expressions
|
||||
= Scalar expressions
|
||||
|
||||
== simple literals
|
||||
|
||||
See the stringToken lexer below for notes on string literal syntax.
|
||||
|
||||
> stringLit :: Parser ValueExpr
|
||||
> stringLit :: Parser ScalarExpr
|
||||
> stringLit = (\(s,e,t) -> StringLit s e t) <$> stringTokExtend
|
||||
|
||||
> numberLit :: Parser ValueExpr
|
||||
> numberLit :: Parser ScalarExpr
|
||||
> numberLit = NumLit <$> sqlNumberTok False
|
||||
|
||||
> simpleLiteral :: Parser ValueExpr
|
||||
> simpleLiteral :: Parser ScalarExpr
|
||||
> simpleLiteral = numberLit <|> stringLit
|
||||
|
||||
== star, param, host param
|
||||
|
@ -568,9 +568,9 @@ See the stringToken lexer below for notes on string literal syntax.
|
|||
|
||||
used in select *, select x.*, and agg(*) variations, and some other
|
||||
places as well. The parser doesn't attempt to check that the star is
|
||||
in a valid context, it parses it OK in any value expression context.
|
||||
in a valid context, it parses it OK in any scalar expression context.
|
||||
|
||||
> star :: Parser ValueExpr
|
||||
> star :: Parser ScalarExpr
|
||||
> star = Star <$ symbol "*"
|
||||
|
||||
== parameter
|
||||
|
@ -579,7 +579,7 @@ unnamed parameter or named parameter
|
|||
use in e.g. select * from t where a = ?
|
||||
select x from t where x > :param
|
||||
|
||||
> parameter :: Parser ValueExpr
|
||||
> parameter :: Parser ScalarExpr
|
||||
> parameter = choice
|
||||
> [Parameter <$ questionMark
|
||||
> ,HostParameter
|
||||
|
@ -588,17 +588,17 @@ select x from t where x > :param
|
|||
|
||||
== positional arg
|
||||
|
||||
> positionalArg :: Parser ValueExpr
|
||||
> positionalArg :: Parser ScalarExpr
|
||||
> positionalArg = PositionalArg <$> positionalArgTok
|
||||
|
||||
== parens
|
||||
|
||||
value expression parens, row ctor and scalar subquery
|
||||
scalar expression parens, row ctor and scalar subquery
|
||||
|
||||
> parensExpr :: Parser ValueExpr
|
||||
> parensExpr :: Parser ScalarExpr
|
||||
> parensExpr = parens $ choice
|
||||
> [SubQueryExpr SqSq <$> queryExpr
|
||||
> ,ctor <$> commaSep1 valueExpr]
|
||||
> ,ctor <$> commaSep1 scalarExpr]
|
||||
> where
|
||||
> ctor [a] = Parens a
|
||||
> ctor as = SpecialOp [Name Nothing "rowctor"] as
|
||||
|
@ -610,24 +610,24 @@ syntax can start with the same keyword.
|
|||
|
||||
=== case expression
|
||||
|
||||
> caseExpr :: Parser ValueExpr
|
||||
> caseExpr :: Parser ScalarExpr
|
||||
> caseExpr =
|
||||
> Case <$> (keyword_ "case" *> optionMaybe valueExpr)
|
||||
> Case <$> (keyword_ "case" *> optionMaybe scalarExpr)
|
||||
> <*> many1 whenClause
|
||||
> <*> optionMaybe elseClause
|
||||
> <* keyword_ "end"
|
||||
> where
|
||||
> whenClause = (,) <$> (keyword_ "when" *> commaSep1 valueExpr)
|
||||
> <*> (keyword_ "then" *> valueExpr)
|
||||
> elseClause = keyword_ "else" *> valueExpr
|
||||
> whenClause = (,) <$> (keyword_ "when" *> commaSep1 scalarExpr)
|
||||
> <*> (keyword_ "then" *> scalarExpr)
|
||||
> elseClause = keyword_ "else" *> scalarExpr
|
||||
|
||||
=== cast
|
||||
|
||||
cast: cast(expr as type)
|
||||
|
||||
> cast :: Parser ValueExpr
|
||||
> cast :: Parser ScalarExpr
|
||||
> cast = keyword_ "cast" *>
|
||||
> parens (Cast <$> valueExpr
|
||||
> parens (Cast <$> scalarExpr
|
||||
> <*> (keyword_ "as" *> typeName))
|
||||
|
||||
=== exists, unique
|
||||
|
@ -635,33 +635,33 @@ cast: cast(expr as type)
|
|||
subquery expression:
|
||||
[exists|unique] (queryexpr)
|
||||
|
||||
> subquery :: Parser ValueExpr
|
||||
> subquery :: Parser ScalarExpr
|
||||
> subquery = SubQueryExpr <$> sqkw <*> parens queryExpr
|
||||
> where
|
||||
> sqkw = SqExists <$ keyword_ "exists" <|> SqUnique <$ keyword_ "unique"
|
||||
|
||||
=== array/multiset constructor
|
||||
|
||||
> arrayCtor :: Parser ValueExpr
|
||||
> arrayCtor :: Parser ScalarExpr
|
||||
> arrayCtor = keyword_ "array" >>
|
||||
> choice
|
||||
> [ArrayCtor <$> parens queryExpr
|
||||
> ,Array (Iden [Name Nothing "array"]) <$> brackets (commaSep valueExpr)]
|
||||
> ,Array (Iden [Name Nothing "array"]) <$> brackets (commaSep scalarExpr)]
|
||||
|
||||
As far as I can tell, table(query expr) is just syntax sugar for
|
||||
multiset(query expr). It must be there for compatibility or something.
|
||||
|
||||
> multisetCtor :: Parser ValueExpr
|
||||
> multisetCtor :: Parser ScalarExpr
|
||||
> multisetCtor =
|
||||
> choice
|
||||
> [keyword_ "multiset" >>
|
||||
> choice
|
||||
> [MultisetQueryCtor <$> parens queryExpr
|
||||
> ,MultisetCtor <$> brackets (commaSep valueExpr)]
|
||||
> ,MultisetCtor <$> brackets (commaSep scalarExpr)]
|
||||
> ,keyword_ "table" >>
|
||||
> MultisetQueryCtor <$> parens queryExpr]
|
||||
|
||||
> nextValueFor :: Parser ValueExpr
|
||||
> nextValueFor :: Parser ScalarExpr
|
||||
> nextValueFor = keywords_ ["next","value","for"] >>
|
||||
> NextValueFor <$> names
|
||||
|
||||
|
@ -684,7 +684,7 @@ interval-datetime-field suffix to parse as an intervallit
|
|||
It uses try because of a conflict with interval type names: todo, fix
|
||||
this. also fix the monad -> applicative
|
||||
|
||||
> intervalLit :: Parser ValueExpr
|
||||
> intervalLit :: Parser ScalarExpr
|
||||
> intervalLit = try (keyword_ "interval" >> do
|
||||
> s <- optionMaybe $ choice [True <$ symbol_ "+"
|
||||
> ,False <$ symbol_ "-"]
|
||||
|
@ -707,11 +707,11 @@ The windows is a suffix on the app parser
|
|||
|
||||
=== iden prefix term
|
||||
|
||||
all the value expressions which start with an identifier
|
||||
all the scalar expressions which start with an identifier
|
||||
|
||||
(todo: really put all of them here instead of just some of them)
|
||||
|
||||
> idenExpr :: Parser ValueExpr
|
||||
> idenExpr :: Parser ScalarExpr
|
||||
> idenExpr =
|
||||
> -- todo: work out how to left factor this
|
||||
> try (TypedLit <$> typeName <*> singleQuotesOnlyStringTok)
|
||||
|
@ -724,7 +724,7 @@ all the value expressions which start with an identifier
|
|||
> multisetSetFunction =
|
||||
> App [Name Nothing "set"] . (:[]) <$>
|
||||
> (try (keyword_ "set" *> openParen)
|
||||
> *> valueExpr <* closeParen)
|
||||
> *> scalarExpr <* closeParen)
|
||||
> keywordFunction =
|
||||
> let makeKeywordFunction x = if map toLower x `elem` keywordFunctionNames
|
||||
> then return [Name Nothing x]
|
||||
|
@ -809,12 +809,12 @@ operatorname(firstArg keyword0 arg0 keyword1 arg1 etc.)
|
|||
> -> SpecialOpKFirstArg -- has a first arg without a keyword
|
||||
> -> [(String,Bool)] -- the other args with their keywords
|
||||
> -- and whether they are optional
|
||||
> -> Parser ValueExpr
|
||||
> -> Parser ScalarExpr
|
||||
> specialOpK opName firstArg kws =
|
||||
> keyword_ opName >> do
|
||||
> void openParen
|
||||
> let pfa = do
|
||||
> e <- valueExpr
|
||||
> e <- scalarExpr
|
||||
> -- check we haven't parsed the first
|
||||
> -- keyword as an identifier
|
||||
> case (e,kws) of
|
||||
|
@ -832,7 +832,7 @@ operatorname(firstArg keyword0 arg0 keyword1 arg1 etc.)
|
|||
> pure $ SpecialOpK [Name Nothing opName] fa $ catMaybes as
|
||||
> where
|
||||
> parseArg (nm,mand) =
|
||||
> let p = keyword_ nm >> valueExpr
|
||||
> let p = keyword_ nm >> scalarExpr
|
||||
> in fmap (nm,) <$> if mand
|
||||
> then Just <$> p
|
||||
> else optionMaybe (try p)
|
||||
|
@ -857,31 +857,31 @@ TRIM( [ [{LEADING | TRAILING | BOTH}] [removal_char] FROM ]
|
|||
target_string
|
||||
[COLLATE collation_name] )
|
||||
|
||||
> specialOpKs :: Parser ValueExpr
|
||||
> specialOpKs :: Parser ScalarExpr
|
||||
> specialOpKs = choice $ map try
|
||||
> [extract, position, substring, convert, translate, overlay, trim]
|
||||
|
||||
> extract :: Parser ValueExpr
|
||||
> extract :: Parser ScalarExpr
|
||||
> extract = specialOpK "extract" SOKMandatory [("from", True)]
|
||||
|
||||
> position :: Parser ValueExpr
|
||||
> position :: Parser ScalarExpr
|
||||
> position = specialOpK "position" SOKMandatory [("in", True)]
|
||||
|
||||
strictly speaking, the substring must have at least one of from and
|
||||
for, but the parser doens't enforce this
|
||||
|
||||
> substring :: Parser ValueExpr
|
||||
> substring :: Parser ScalarExpr
|
||||
> substring = specialOpK "substring" SOKMandatory
|
||||
> [("from", False),("for", False)]
|
||||
|
||||
> convert :: Parser ValueExpr
|
||||
> convert :: Parser ScalarExpr
|
||||
> convert = specialOpK "convert" SOKMandatory [("using", True)]
|
||||
|
||||
|
||||
> translate :: Parser ValueExpr
|
||||
> translate :: Parser ScalarExpr
|
||||
> translate = specialOpK "translate" SOKMandatory [("using", True)]
|
||||
|
||||
> overlay :: Parser ValueExpr
|
||||
> overlay :: Parser ScalarExpr
|
||||
> overlay = specialOpK "overlay" SOKMandatory
|
||||
> [("placing", True),("from", True),("for", False)]
|
||||
|
||||
|
@ -889,13 +889,13 @@ trim is too different because of the optional char, so a custom parser
|
|||
the both ' ' is filled in as the default if either parts are missing
|
||||
in the source
|
||||
|
||||
> trim :: Parser ValueExpr
|
||||
> trim :: Parser ScalarExpr
|
||||
> trim =
|
||||
> keyword "trim" >>
|
||||
> parens (mkTrim
|
||||
> <$> option "both" sides
|
||||
> <*> option " " singleQuotesOnlyStringTok
|
||||
> <*> (keyword_ "from" *> valueExpr))
|
||||
> <*> (keyword_ "from" *> scalarExpr))
|
||||
> where
|
||||
> sides = choice ["leading" <$ keyword_ "leading"
|
||||
> ,"trailing" <$ keyword_ "trailing"
|
||||
|
@ -908,7 +908,7 @@ in the source
|
|||
=== app, aggregate, window
|
||||
|
||||
This parses all these variations:
|
||||
normal function application with just a csv of value exprs
|
||||
normal function application with just a csv of scalar exprs
|
||||
aggregate variations (distinct, order by in parens, filter and where
|
||||
suffixes)
|
||||
window apps (fn/agg followed by over)
|
||||
|
@ -917,16 +917,16 @@ This code is also a little dense like the typename code because of
|
|||
left factoring, later they will even have to be partially combined
|
||||
together.
|
||||
|
||||
> app :: Parser ([Name] -> ValueExpr)
|
||||
> app :: Parser ([Name] -> ScalarExpr)
|
||||
> app =
|
||||
> openParen *> choice
|
||||
> [duplicates
|
||||
> <**> (commaSep1 valueExpr
|
||||
> <**> (commaSep1 scalarExpr
|
||||
> <**> (((option [] orderBy) <* closeParen)
|
||||
> <**> (optionMaybe afilter <$$$$$> AggregateApp)))
|
||||
> -- separate cases with no all or distinct which must have at
|
||||
> -- least one value expr
|
||||
> ,commaSep1 valueExpr
|
||||
> -- least one scalar expr
|
||||
> ,commaSep1 scalarExpr
|
||||
> <**> choice
|
||||
> [closeParen *> choice
|
||||
> [window
|
||||
|
@ -935,17 +935,17 @@ together.
|
|||
> ,pure (flip App)]
|
||||
> ,orderBy <* closeParen
|
||||
> <**> (optionMaybe afilter <$$$$> aggAppWithoutDupe)]
|
||||
> -- no valueExprs: duplicates and order by not allowed
|
||||
> -- no scalarExprs: duplicates and order by not allowed
|
||||
> ,([] <$ closeParen) <**> option (flip App) (window <|> withinGroup)
|
||||
> ]
|
||||
> where
|
||||
> aggAppWithoutDupeOrd n es f = AggregateApp n SQDefault es [] f
|
||||
> aggAppWithoutDupe n = AggregateApp n SQDefault
|
||||
|
||||
> afilter :: Parser ValueExpr
|
||||
> afilter = keyword_ "filter" *> parens (keyword_ "where" *> valueExpr)
|
||||
> afilter :: Parser ScalarExpr
|
||||
> afilter = keyword_ "filter" *> parens (keyword_ "where" *> scalarExpr)
|
||||
|
||||
> withinGroup :: Parser ([ValueExpr] -> [Name] -> ValueExpr)
|
||||
> withinGroup :: Parser ([ScalarExpr] -> [Name] -> ScalarExpr)
|
||||
> withinGroup =
|
||||
> (keywords_ ["within", "group"] *> parens orderBy) <$$$> AggregateAppGroup
|
||||
|
||||
|
@ -960,13 +960,13 @@ No support for explicit frames yet.
|
|||
TODO: add window support for other aggregate variations, needs some
|
||||
changes to the syntax also
|
||||
|
||||
> window :: Parser ([ValueExpr] -> [Name] -> ValueExpr)
|
||||
> window :: Parser ([ScalarExpr] -> [Name] -> ScalarExpr)
|
||||
> window =
|
||||
> keyword_ "over" *> openParen *> option [] partitionBy
|
||||
> <**> (option [] orderBy
|
||||
> <**> (((optionMaybe frameClause) <* closeParen) <$$$$$> WindowApp))
|
||||
> where
|
||||
> partitionBy = keywords_ ["partition","by"] *> commaSep1 valueExpr
|
||||
> partitionBy = keywords_ ["partition","by"] *> commaSep1 scalarExpr
|
||||
> frameClause =
|
||||
> frameRowsRange -- TODO: this 'and' could be an issue
|
||||
> <**> (choice [(keyword_ "between" *> frameLimit True)
|
||||
|
@ -984,14 +984,14 @@ changes to the syntax also
|
|||
> ,keyword_ "unbounded" *>
|
||||
> choice [UnboundedPreceding <$ keyword_ "preceding"
|
||||
> ,UnboundedFollowing <$ keyword_ "following"]
|
||||
> ,(if useB then valueExprB else valueExpr)
|
||||
> ,(if useB then scalarExprB else scalarExpr)
|
||||
> <**> (Preceding <$ keyword_ "preceding"
|
||||
> <|> Following <$ keyword_ "following")
|
||||
> ]
|
||||
|
||||
== suffixes
|
||||
|
||||
These are all generic suffixes on any value expr
|
||||
These are all generic suffixes on any scalar expr
|
||||
|
||||
=== in
|
||||
|
||||
|
@ -999,12 +999,12 @@ in: two variations:
|
|||
a in (expr0, expr1, ...)
|
||||
a in (queryexpr)
|
||||
|
||||
> inSuffix :: Parser (ValueExpr -> ValueExpr)
|
||||
> inSuffix :: Parser (ScalarExpr -> ScalarExpr)
|
||||
> inSuffix =
|
||||
> mkIn <$> inty
|
||||
> <*> parens (choice
|
||||
> [InQueryExpr <$> queryExpr
|
||||
> ,InList <$> commaSep1 valueExpr])
|
||||
> ,InList <$> commaSep1 scalarExpr])
|
||||
> where
|
||||
> inty = choice [True <$ keyword_ "in"
|
||||
> ,False <$ keywords_ ["not","in"]]
|
||||
|
@ -1021,15 +1021,15 @@ binary operator or part of the between. This code follows what
|
|||
postgres does, which might be standard across SQL implementations,
|
||||
which is that you can't have a binary and operator in the middle
|
||||
expression in a between unless it is wrapped in parens. The 'bExpr
|
||||
parsing' is used to create alternative value expression parser which
|
||||
parsing' is used to create alternative scalar expression parser which
|
||||
is identical to the normal one expect it doesn't recognise the binary
|
||||
and operator. This is the call to valueExprB.
|
||||
and operator. This is the call to scalarExprB.
|
||||
|
||||
> betweenSuffix :: Parser (ValueExpr -> ValueExpr)
|
||||
> betweenSuffix :: Parser (ScalarExpr -> ScalarExpr)
|
||||
> betweenSuffix =
|
||||
> makeOp <$> Name Nothing <$> opName
|
||||
> <*> valueExprB
|
||||
> <*> (keyword_ "and" *> valueExprB)
|
||||
> <*> scalarExprB
|
||||
> <*> (keyword_ "and" *> scalarExprB)
|
||||
> where
|
||||
> opName = choice
|
||||
> ["between" <$ keyword_ "between"
|
||||
|
@ -1040,7 +1040,7 @@ and operator. This is the call to valueExprB.
|
|||
|
||||
a = any (select * from t)
|
||||
|
||||
> quantifiedComparisonSuffix :: Parser (ValueExpr -> ValueExpr)
|
||||
> quantifiedComparisonSuffix :: Parser (ScalarExpr -> ScalarExpr)
|
||||
> quantifiedComparisonSuffix = do
|
||||
> c <- comp
|
||||
> cq <- compQuan
|
||||
|
@ -1058,7 +1058,7 @@ a = any (select * from t)
|
|||
|
||||
a match (select a from t)
|
||||
|
||||
> matchPredicateSuffix :: Parser (ValueExpr -> ValueExpr)
|
||||
> matchPredicateSuffix :: Parser (ScalarExpr -> ScalarExpr)
|
||||
> matchPredicateSuffix = do
|
||||
> keyword_ "match"
|
||||
> u <- option False (True <$ keyword_ "unique")
|
||||
|
@ -1067,9 +1067,9 @@ a match (select a from t)
|
|||
|
||||
=== array subscript
|
||||
|
||||
> arraySuffix :: Parser (ValueExpr -> ValueExpr)
|
||||
> arraySuffix :: Parser (ScalarExpr -> ScalarExpr)
|
||||
> arraySuffix = do
|
||||
> es <- brackets (commaSep valueExpr)
|
||||
> es <- brackets (commaSep scalarExpr)
|
||||
> pure $ \v -> Array v es
|
||||
|
||||
=== escape
|
||||
|
@ -1080,7 +1080,7 @@ for the escape now there is a separate lexer ...
|
|||
TODO: this needs fixing. Escape is only part of other nodes, and not a
|
||||
separate suffix.
|
||||
|
||||
> {-escapeSuffix :: Parser (ValueExpr -> ValueExpr)
|
||||
> {-escapeSuffix :: Parser (ScalarExpr -> ScalarExpr)
|
||||
> escapeSuffix = do
|
||||
> ctor <- choice
|
||||
> [Escape <$ keyword_ "escape"
|
||||
|
@ -1098,7 +1098,7 @@ separate suffix.
|
|||
|
||||
=== collate
|
||||
|
||||
> collateSuffix:: Parser (ValueExpr -> ValueExpr)
|
||||
> collateSuffix:: Parser (ScalarExpr -> ScalarExpr)
|
||||
> collateSuffix = do
|
||||
> keyword_ "collate"
|
||||
> i <- names
|
||||
|
@ -1110,7 +1110,7 @@ the parser supports three kinds of odbc syntax, two of which are
|
|||
scalar expressions (the other is a variation on joins)
|
||||
|
||||
|
||||
> odbcExpr :: Parser ValueExpr
|
||||
> odbcExpr :: Parser ScalarExpr
|
||||
> odbcExpr = between (symbol "{") (symbol "}")
|
||||
> (odbcTimeLit <|> odbcFunc)
|
||||
> where
|
||||
|
@ -1122,7 +1122,7 @@ scalar expressions (the other is a variation on joins)
|
|||
> -- todo: this parser is too general, the expr part
|
||||
> -- should be only a function call (from a whitelist of functions)
|
||||
> -- or the extract operator
|
||||
> odbcFunc = OdbcFunc <$> (keyword "fn" *> valueExpr)
|
||||
> odbcFunc = OdbcFunc <$> (keyword "fn" *> scalarExpr)
|
||||
|
||||
== operators
|
||||
|
||||
|
@ -1139,7 +1139,7 @@ syntax is way too messy. It might be possible to avoid this if we
|
|||
wanted to avoid extensibility and to not be concerned with parse error
|
||||
messages, but both of these are too important.
|
||||
|
||||
> opTable :: Bool -> [[E.Operator [Token] ParseState Identity ValueExpr]]
|
||||
> opTable :: Bool -> [[E.Operator [Token] ParseState Identity ScalarExpr]]
|
||||
> opTable bExpr =
|
||||
> [-- parse match and quantified comparisons as postfix ops
|
||||
> -- todo: left factor the quantified comparison with regular
|
||||
|
@ -1248,18 +1248,18 @@ messages, but both of these are too important.
|
|||
> prefix' p = E.Prefix . chainl1 p $ pure (.)
|
||||
> postfix' p = E.Postfix . chainl1 p $ pure (flip (.))
|
||||
|
||||
== value expression top level
|
||||
== scalar expression top level
|
||||
|
||||
This parses most of the value exprs.The order of the parsers and use
|
||||
This parses most of the scalar exprs.The order of the parsers and use
|
||||
of try is carefully done to make everything work. It is a little
|
||||
fragile and could at least do with some heavy explanation. Update: the
|
||||
'try's have migrated into the individual parsers, they still need
|
||||
documenting/fixing.
|
||||
|
||||
> valueExpr :: Parser ValueExpr
|
||||
> valueExpr = E.buildExpressionParser (opTable False) term
|
||||
> scalarExpr :: Parser ScalarExpr
|
||||
> scalarExpr = E.buildExpressionParser (opTable False) term
|
||||
|
||||
> term :: Parser ValueExpr
|
||||
> term :: Parser ScalarExpr
|
||||
> term = choice [simpleLiteral
|
||||
> ,parameter
|
||||
> ,positionalArg
|
||||
|
@ -1275,12 +1275,12 @@ documenting/fixing.
|
|||
> ,specialOpKs
|
||||
> ,idenExpr
|
||||
> ,odbcExpr]
|
||||
> <?> "value expression"
|
||||
> <?> "scalar expression"
|
||||
|
||||
expose the b expression for window frame clause range between
|
||||
|
||||
> valueExprB :: Parser ValueExpr
|
||||
> valueExprB = E.buildExpressionParser (opTable True) term
|
||||
> scalarExprB :: Parser ScalarExpr
|
||||
> scalarExprB = E.buildExpressionParser (opTable True) term
|
||||
|
||||
== helper parsers
|
||||
|
||||
|
@ -1306,7 +1306,7 @@ use a data type for the datetime field?
|
|||
> ,"hour","minute","second"])
|
||||
> <?> "datetime field"
|
||||
|
||||
This is used in multiset operations (value expr), selects (query expr)
|
||||
This is used in multiset operations (scalar expr), selects (query expr)
|
||||
and set operations (query expr).
|
||||
|
||||
> duplicates :: Parser SetQuantifier
|
||||
|
@ -1320,11 +1320,11 @@ and set operations (query expr).
|
|||
|
||||
== select lists
|
||||
|
||||
> selectItem :: Parser (ValueExpr,Maybe Name)
|
||||
> selectItem = (,) <$> valueExpr <*> optionMaybe als
|
||||
> selectItem :: Parser (ScalarExpr,Maybe Name)
|
||||
> selectItem = (,) <$> scalarExpr <*> optionMaybe als
|
||||
> where als = optional (keyword_ "as") *> name
|
||||
|
||||
> selectList :: Parser [(ValueExpr,Maybe Name)]
|
||||
> selectList :: Parser [(ScalarExpr,Maybe Name)]
|
||||
> selectList = commaSep1 selectItem
|
||||
|
||||
== from
|
||||
|
@ -1355,7 +1355,7 @@ aliases.
|
|||
> ,do
|
||||
> n <- names
|
||||
> choice [TRFunction n
|
||||
> <$> parens (commaSep valueExpr)
|
||||
> <$> parens (commaSep scalarExpr)
|
||||
> ,pure $ TRSimple n]
|
||||
> -- todo: I think you can only have outer joins inside the oj,
|
||||
> -- not sure.
|
||||
|
@ -1389,7 +1389,7 @@ it more readable)
|
|||
|
||||
> joinCondition :: Parser JoinCondition
|
||||
> joinCondition = choice
|
||||
> [keyword_ "on" >> JoinOn <$> valueExpr
|
||||
> [keyword_ "on" >> JoinOn <$> scalarExpr
|
||||
> ,keyword_ "using" >> JoinUsing <$> parens (commaSep1 name)]
|
||||
|
||||
> fromAlias :: Parser Alias
|
||||
|
@ -1403,8 +1403,8 @@ it more readable)
|
|||
Parsers for where, group by, having, order by and limit, which are
|
||||
pretty trivial.
|
||||
|
||||
> whereClause :: Parser ValueExpr
|
||||
> whereClause = keyword_ "where" *> valueExpr
|
||||
> whereClause :: Parser ScalarExpr
|
||||
> whereClause = keyword_ "where" *> scalarExpr
|
||||
|
||||
> groupByClause :: Parser [GroupingExpr]
|
||||
> groupByClause = keywords_ ["group","by"] *> commaSep1 groupingExpression
|
||||
|
@ -1417,17 +1417,17 @@ pretty trivial.
|
|||
> ,GroupingParens <$> parens (commaSep groupingExpression)
|
||||
> ,keywords_ ["grouping", "sets"] >>
|
||||
> GroupingSets <$> parens (commaSep groupingExpression)
|
||||
> ,SimpleGroup <$> valueExpr
|
||||
> ,SimpleGroup <$> scalarExpr
|
||||
> ]
|
||||
|
||||
> having :: Parser ValueExpr
|
||||
> having = keyword_ "having" *> valueExpr
|
||||
> having :: Parser ScalarExpr
|
||||
> having = keyword_ "having" *> scalarExpr
|
||||
|
||||
> orderBy :: Parser [SortSpec]
|
||||
> orderBy = keywords_ ["order","by"] *> commaSep1 ob
|
||||
> where
|
||||
> ob = SortSpec
|
||||
> <$> valueExpr
|
||||
> <$> scalarExpr
|
||||
> <*> option DirDefault (choice [Asc <$ keyword_ "asc"
|
||||
> ,Desc <$ keyword_ "desc"])
|
||||
> <*> option NullsOrderDefault
|
||||
|
@ -1439,25 +1439,25 @@ pretty trivial.
|
|||
allows offset and fetch in either order
|
||||
+ postgresql offset without row(s) and limit instead of fetch also
|
||||
|
||||
> offsetFetch :: Parser (Maybe ValueExpr, Maybe ValueExpr)
|
||||
> offsetFetch :: Parser (Maybe ScalarExpr, Maybe ScalarExpr)
|
||||
> offsetFetch = permute ((,) <$?> (Nothing, Just <$> offset)
|
||||
> <|?> (Nothing, Just <$> fetch))
|
||||
|
||||
> offset :: Parser ValueExpr
|
||||
> offset = keyword_ "offset" *> valueExpr
|
||||
> offset :: Parser ScalarExpr
|
||||
> offset = keyword_ "offset" *> scalarExpr
|
||||
> <* option () (choice [keyword_ "rows"
|
||||
> ,keyword_ "row"])
|
||||
|
||||
> fetch :: Parser ValueExpr
|
||||
> fetch :: Parser ScalarExpr
|
||||
> fetch = fetchFirst <|> limit
|
||||
> where
|
||||
> fetchFirst = guardDialect [ANSI2011]
|
||||
> *> fs *> valueExpr <* ro
|
||||
> *> fs *> scalarExpr <* ro
|
||||
> fs = makeKeywordTree ["fetch first", "fetch next"]
|
||||
> ro = makeKeywordTree ["rows only", "row only"]
|
||||
> -- todo: not in ansi sql dialect
|
||||
> limit = guardDialect [MySQL] *>
|
||||
> keyword_ "limit" *> valueExpr
|
||||
> keyword_ "limit" *> scalarExpr
|
||||
|
||||
== common table expressions
|
||||
|
||||
|
@ -1489,7 +1489,7 @@ and union, etc..
|
|||
> mkSelect d sl (Just (TableExpression f w g h od ofs fe)) =
|
||||
> Select d sl f w g h od ofs fe
|
||||
> values = keyword_ "values"
|
||||
> >> Values <$> commaSep (parens (commaSep valueExpr))
|
||||
> >> Values <$> commaSep (parens (commaSep scalarExpr))
|
||||
> table = keyword_ "table" >> Table <$> names
|
||||
|
||||
local data type to help with parsing the bit after the select list,
|
||||
|
@ -1499,12 +1499,12 @@ be in the public syntax?
|
|||
> data TableExpression
|
||||
> = TableExpression
|
||||
> {_teFrom :: [TableRef]
|
||||
> ,_teWhere :: Maybe ValueExpr
|
||||
> ,_teWhere :: Maybe ScalarExpr
|
||||
> ,_teGroupBy :: [GroupingExpr]
|
||||
> ,_teHaving :: Maybe ValueExpr
|
||||
> ,_teHaving :: Maybe ScalarExpr
|
||||
> ,_teOrderBy :: [SortSpec]
|
||||
> ,_teOffset :: Maybe ValueExpr
|
||||
> ,_teFetchFirst :: Maybe ValueExpr}
|
||||
> ,_teOffset :: Maybe ScalarExpr
|
||||
> ,_teFetchFirst :: Maybe ScalarExpr}
|
||||
|
||||
> tableExpression :: Parser TableExpression
|
||||
> tableExpression = mkTe <$> from
|
||||
|
@ -1597,10 +1597,10 @@ TODO: change style
|
|||
> where
|
||||
> defaultClause = choice [
|
||||
> keyword_ "default" >>
|
||||
> DefaultClause <$> valueExpr
|
||||
> DefaultClause <$> scalarExpr
|
||||
> -- todo: left factor
|
||||
> ,try (keywords_ ["generated","always","as"] >>
|
||||
> GenerationClause <$> parens valueExpr)
|
||||
> GenerationClause <$> parens scalarExpr)
|
||||
> ,keyword_ "generated" >>
|
||||
> IdentityColumnSpec
|
||||
> <$> (GeneratedAlways <$ keyword_ "always"
|
||||
|
@ -1619,7 +1619,7 @@ TODO: change style
|
|||
> TableUniqueConstraint <$> parens (commaSep1 name)
|
||||
> primaryKey = keywords_ ["primary", "key"] >>
|
||||
> TablePrimaryKeyConstraint <$> parens (commaSep1 name)
|
||||
> check = keyword_ "check" >> TableCheckConstraint <$> parens valueExpr
|
||||
> check = keyword_ "check" >> TableCheckConstraint <$> parens scalarExpr
|
||||
> references = keywords_ ["foreign", "key"] >>
|
||||
> (\cs ft ftcs m (u,d) -> TableReferencesConstraint cs ft ftcs m u d)
|
||||
> <$> parens (commaSep1 name)
|
||||
|
@ -1658,7 +1658,7 @@ TODO: change style
|
|||
> notNull = ColNotNullConstraint <$ keywords_ ["not", "null"]
|
||||
> unique = ColUniqueConstraint <$ keyword_ "unique"
|
||||
> primaryKey = ColPrimaryKeyConstraint <$ keywords_ ["primary", "key"]
|
||||
> check = keyword_ "check" >> ColCheckConstraint <$> parens valueExpr
|
||||
> check = keyword_ "check" >> ColCheckConstraint <$> parens scalarExpr
|
||||
> references = keyword_ "references" >>
|
||||
> (\t c m (ou,od) -> ColReferencesConstraint t c m ou od)
|
||||
> <$> names
|
||||
|
@ -1733,7 +1733,7 @@ slightly hacky parser for signed integers
|
|||
> setDefault :: Parser (Name -> AlterTableAction)
|
||||
> -- todo: left factor
|
||||
> setDefault = try (keywords_ ["set","default"]) >>
|
||||
> valueExpr <$$> AlterColumnSetDefault
|
||||
> scalarExpr <$$> AlterColumnSetDefault
|
||||
> dropDefault = AlterColumnDropDefault <$ try (keywords_ ["drop","default"])
|
||||
> setNotNull = AlterColumnSetNotNull <$ try (keywords_ ["set","not","null"])
|
||||
> dropNotNull = AlterColumnDropNotNull <$ try (keywords_ ["drop","not","null"])
|
||||
|
@ -1779,11 +1779,11 @@ slightly hacky parser for signed integers
|
|||
> CreateDomain
|
||||
> <$> names
|
||||
> <*> (optional (keyword_ "as") *> typeName)
|
||||
> <*> optionMaybe (keyword_ "default" *> valueExpr)
|
||||
> <*> optionMaybe (keyword_ "default" *> scalarExpr)
|
||||
> <*> many con
|
||||
> where
|
||||
> con = (,) <$> optionMaybe (keyword_ "constraint" *> names)
|
||||
> <*> (keyword_ "check" *> parens valueExpr)
|
||||
> <*> (keyword_ "check" *> parens scalarExpr)
|
||||
|
||||
> alterDomain :: Parser Statement
|
||||
> alterDomain = keyword_ "domain" >>
|
||||
|
@ -1792,11 +1792,11 @@ slightly hacky parser for signed integers
|
|||
> <*> (setDefault <|> constraint
|
||||
> <|> (keyword_ "drop" *> (dropDefault <|> dropConstraint)))
|
||||
> where
|
||||
> setDefault = keywords_ ["set", "default"] >> ADSetDefault <$> valueExpr
|
||||
> setDefault = keywords_ ["set", "default"] >> ADSetDefault <$> scalarExpr
|
||||
> constraint = keyword_ "add" >>
|
||||
> ADAddConstraint
|
||||
> <$> optionMaybe (keyword_ "constraint" *> names)
|
||||
> <*> (keyword_ "check" *> parens valueExpr)
|
||||
> <*> (keyword_ "check" *> parens scalarExpr)
|
||||
> dropDefault = ADDropDefault <$ keyword_ "default"
|
||||
> dropConstraint = keyword_ "constraint" >> ADDropConstraint <$> names
|
||||
|
||||
|
@ -1824,7 +1824,7 @@ slightly hacky parser for signed integers
|
|||
> createAssertion = keyword_ "assertion" >>
|
||||
> CreateAssertion
|
||||
> <$> names
|
||||
> <*> (keyword_ "check" *> parens valueExpr)
|
||||
> <*> (keyword_ "check" *> parens scalarExpr)
|
||||
|
||||
|
||||
> dropAssertion :: Parser Statement
|
||||
|
@ -1840,7 +1840,7 @@ slightly hacky parser for signed integers
|
|||
> Delete
|
||||
> <$> names
|
||||
> <*> optionMaybe (optional (keyword_ "as") *> name)
|
||||
> <*> optionMaybe (keyword_ "where" *> valueExpr)
|
||||
> <*> optionMaybe (keyword_ "where" *> scalarExpr)
|
||||
|
||||
> truncateSt :: Parser Statement
|
||||
> truncateSt = keywords_ ["truncate", "table"] >>
|
||||
|
@ -1864,15 +1864,15 @@ slightly hacky parser for signed integers
|
|||
> <$> names
|
||||
> <*> optionMaybe (optional (keyword_ "as") *> name)
|
||||
> <*> (keyword_ "set" *> commaSep1 setClause)
|
||||
> <*> optionMaybe (keyword_ "where" *> valueExpr)
|
||||
> <*> optionMaybe (keyword_ "where" *> scalarExpr)
|
||||
> where
|
||||
> setClause = multipleSet <|> singleSet
|
||||
> multipleSet = SetMultiple
|
||||
> <$> parens (commaSep1 names)
|
||||
> <*> (symbol "=" *> parens (commaSep1 valueExpr))
|
||||
> <*> (symbol "=" *> parens (commaSep1 scalarExpr))
|
||||
> singleSet = Set
|
||||
> <$> names
|
||||
> <*> (symbol "=" *> valueExpr)
|
||||
> <*> (symbol "=" *> scalarExpr)
|
||||
|
||||
> dropBehaviour :: Parser DropBehaviour
|
||||
> dropBehaviour =
|
||||
|
|
|
@ -4,7 +4,7 @@
|
|||
> -- readable way.
|
||||
> module Language.SQL.SimpleSQL.Pretty
|
||||
> (prettyQueryExpr
|
||||
> ,prettyValueExpr
|
||||
> ,prettyScalarExpr
|
||||
> ,prettyStatement
|
||||
> ,prettyStatements
|
||||
> ) where
|
||||
|
@ -25,8 +25,8 @@ which have been changed to try to improve the layout of the output.
|
|||
> prettyQueryExpr d = render . queryExpr d
|
||||
|
||||
> -- | Convert a value expr ast to concrete syntax.
|
||||
> prettyValueExpr :: Dialect -> ValueExpr -> String
|
||||
> prettyValueExpr d = render . valueExpr d
|
||||
> prettyScalarExpr :: Dialect -> ScalarExpr -> String
|
||||
> prettyScalarExpr d = render . scalarExpr d
|
||||
|
||||
> -- | Convert a statement ast to concrete syntax.
|
||||
> prettyStatement :: Dialect -> Statement -> String
|
||||
|
@ -37,53 +37,53 @@ which have been changed to try to improve the layout of the output.
|
|||
> prettyStatements :: Dialect -> [Statement] -> String
|
||||
> prettyStatements d = render . vcat . map ((<> text ";\n") . statement d)
|
||||
|
||||
= value expressions
|
||||
= scalar expressions
|
||||
|
||||
> valueExpr :: Dialect -> ValueExpr -> Doc
|
||||
> valueExpr _ (StringLit s e t) = text s <> text t <> text e
|
||||
> scalarExpr :: Dialect -> ScalarExpr -> Doc
|
||||
> scalarExpr _ (StringLit s e t) = text s <> text t <> text e
|
||||
|
||||
> valueExpr _ (NumLit s) = text s
|
||||
> valueExpr _ (IntervalLit s v f t) =
|
||||
> scalarExpr _ (NumLit s) = text s
|
||||
> scalarExpr _ (IntervalLit s v f t) =
|
||||
> text "interval"
|
||||
> <+> me (\x -> if x then text "+" else text "-") s
|
||||
> <+> quotes (text v)
|
||||
> <+> intervalTypeField f
|
||||
> <+> me (\x -> text "to" <+> intervalTypeField x) t
|
||||
> valueExpr _ (Iden i) = names i
|
||||
> valueExpr _ Star = text "*"
|
||||
> valueExpr _ Parameter = text "?"
|
||||
> valueExpr _ (PositionalArg n) = text $ "$" ++ show n
|
||||
> valueExpr _ (HostParameter p i) =
|
||||
> scalarExpr _ (Iden i) = names i
|
||||
> scalarExpr _ Star = text "*"
|
||||
> scalarExpr _ Parameter = text "?"
|
||||
> scalarExpr _ (PositionalArg n) = text $ "$" ++ show n
|
||||
> scalarExpr _ (HostParameter p i) =
|
||||
> text p
|
||||
> <+> me (\i' -> text "indicator" <+> text i') i
|
||||
|
||||
> valueExpr d (App f es) = names f <> parens (commaSep (map (valueExpr d) es))
|
||||
> scalarExpr d (App f es) = names f <> parens (commaSep (map (scalarExpr d) es))
|
||||
|
||||
> valueExpr dia (AggregateApp f d es od fil) =
|
||||
> scalarExpr dia (AggregateApp f d es od fil) =
|
||||
> names f
|
||||
> <> parens ((case d of
|
||||
> Distinct -> text "distinct"
|
||||
> All -> text "all"
|
||||
> SQDefault -> empty)
|
||||
> <+> commaSep (map (valueExpr dia) es)
|
||||
> <+> commaSep (map (scalarExpr dia) es)
|
||||
> <+> orderBy dia od)
|
||||
> <+> me (\x -> text "filter"
|
||||
> <+> parens (text "where" <+> valueExpr dia x)) fil
|
||||
> <+> parens (text "where" <+> scalarExpr dia x)) fil
|
||||
|
||||
> valueExpr d (AggregateAppGroup f es od) =
|
||||
> scalarExpr d (AggregateAppGroup f es od) =
|
||||
> names f
|
||||
> <> parens (commaSep (map (valueExpr d) es))
|
||||
> <> parens (commaSep (map (scalarExpr d) es))
|
||||
> <+> if null od
|
||||
> then empty
|
||||
> else text "within group" <+> parens (orderBy d od)
|
||||
|
||||
> valueExpr d (WindowApp f es pb od fr) =
|
||||
> names f <> parens (commaSep $ map (valueExpr d) es)
|
||||
> scalarExpr d (WindowApp f es pb od fr) =
|
||||
> names f <> parens (commaSep $ map (scalarExpr d) es)
|
||||
> <+> text "over"
|
||||
> <+> parens ((case pb of
|
||||
> [] -> empty
|
||||
> _ -> text "partition by"
|
||||
> <+> nest 13 (commaSep $ map (valueExpr d) pb))
|
||||
> <+> nest 13 (commaSep $ map (scalarExpr d) pb))
|
||||
> <+> orderBy d od
|
||||
> <+> me frd fr)
|
||||
> where
|
||||
|
@ -97,73 +97,73 @@ which have been changed to try to improve the layout of the output.
|
|||
> fpd UnboundedPreceding = text "unbounded preceding"
|
||||
> fpd UnboundedFollowing = text "unbounded following"
|
||||
> fpd Current = text "current row"
|
||||
> fpd (Preceding e) = valueExpr d e <+> text "preceding"
|
||||
> fpd (Following e) = valueExpr d e <+> text "following"
|
||||
> fpd (Preceding e) = scalarExpr d e <+> text "preceding"
|
||||
> fpd (Following e) = scalarExpr d e <+> text "following"
|
||||
|
||||
> valueExpr dia (SpecialOp nm [a,b,c]) | nm `elem` [[Name Nothing "between"]
|
||||
> scalarExpr dia (SpecialOp nm [a,b,c]) | nm `elem` [[Name Nothing "between"]
|
||||
> ,[Name Nothing "not between"]] =
|
||||
> sep [valueExpr dia a
|
||||
> ,names nm <+> valueExpr dia b
|
||||
> ,nest (length (unnames nm) + 1) $ text "and" <+> valueExpr dia c]
|
||||
> sep [scalarExpr dia a
|
||||
> ,names nm <+> scalarExpr dia b
|
||||
> ,nest (length (unnames nm) + 1) $ text "and" <+> scalarExpr dia c]
|
||||
|
||||
> valueExpr d (SpecialOp [Name Nothing "rowctor"] as) =
|
||||
> parens $ commaSep $ map (valueExpr d) as
|
||||
> scalarExpr d (SpecialOp [Name Nothing "rowctor"] as) =
|
||||
> parens $ commaSep $ map (scalarExpr d) as
|
||||
|
||||
> valueExpr d (SpecialOp nm es) =
|
||||
> names nm <+> parens (commaSep $ map (valueExpr d) es)
|
||||
> scalarExpr d (SpecialOp nm es) =
|
||||
> names nm <+> parens (commaSep $ map (scalarExpr d) es)
|
||||
|
||||
> valueExpr d (SpecialOpK nm fs as) =
|
||||
> scalarExpr d (SpecialOpK nm fs as) =
|
||||
> names nm <> parens (sep $ catMaybes
|
||||
> (fmap (valueExpr d) fs
|
||||
> : map (\(n,e) -> Just (text n <+> valueExpr d e)) as))
|
||||
> (fmap (scalarExpr d) fs
|
||||
> : map (\(n,e) -> Just (text n <+> scalarExpr d e)) as))
|
||||
|
||||
> valueExpr d (PrefixOp f e) = names f <+> valueExpr d e
|
||||
> valueExpr d (PostfixOp f e) = valueExpr d e <+> names f
|
||||
> valueExpr d e@(BinOp _ op _) | op `elem` [[Name Nothing "and"]
|
||||
> scalarExpr d (PrefixOp f e) = names f <+> scalarExpr d e
|
||||
> scalarExpr d (PostfixOp f e) = scalarExpr d e <+> names f
|
||||
> scalarExpr d e@(BinOp _ op _) | op `elem` [[Name Nothing "and"]
|
||||
> ,[Name Nothing "or"]] =
|
||||
> -- special case for and, or, get all the ands so we can vcat them
|
||||
> -- nicely
|
||||
> case ands e of
|
||||
> (e':es) -> vcat (valueExpr d e'
|
||||
> : map ((names op <+>) . valueExpr d) es)
|
||||
> (e':es) -> vcat (scalarExpr d e'
|
||||
> : map ((names op <+>) . scalarExpr d) es)
|
||||
> [] -> empty -- shouldn't be possible
|
||||
> where
|
||||
> ands (BinOp a op' b) | op == op' = ands a ++ ands b
|
||||
> ands x = [x]
|
||||
> -- special case for . we don't use whitespace
|
||||
> valueExpr d (BinOp e0 [Name Nothing "."] e1) =
|
||||
> valueExpr d e0 <> text "." <> valueExpr d e1
|
||||
> valueExpr d (BinOp e0 f e1) =
|
||||
> valueExpr d e0 <+> names f <+> valueExpr d e1
|
||||
> scalarExpr d (BinOp e0 [Name Nothing "."] e1) =
|
||||
> scalarExpr d e0 <> text "." <> scalarExpr d e1
|
||||
> scalarExpr d (BinOp e0 f e1) =
|
||||
> scalarExpr d e0 <+> names f <+> scalarExpr d e1
|
||||
|
||||
> valueExpr dia (Case t ws els) =
|
||||
> sep $ [text "case" <+> me (valueExpr dia) t]
|
||||
> scalarExpr dia (Case t ws els) =
|
||||
> sep $ [text "case" <+> me (scalarExpr dia) t]
|
||||
> ++ map w ws
|
||||
> ++ maybeToList (fmap e els)
|
||||
> ++ [text "end"]
|
||||
> where
|
||||
> w (t0,t1) =
|
||||
> text "when" <+> nest 5 (commaSep $ map (valueExpr dia) t0)
|
||||
> <+> text "then" <+> nest 5 (valueExpr dia t1)
|
||||
> e el = text "else" <+> nest 5 (valueExpr dia el)
|
||||
> valueExpr d (Parens e) = parens $ valueExpr d e
|
||||
> valueExpr d (Cast e tn) =
|
||||
> text "cast" <> parens (sep [valueExpr d e
|
||||
> text "when" <+> nest 5 (commaSep $ map (scalarExpr dia) t0)
|
||||
> <+> text "then" <+> nest 5 (scalarExpr dia t1)
|
||||
> e el = text "else" <+> nest 5 (scalarExpr dia el)
|
||||
> scalarExpr d (Parens e) = parens $ scalarExpr d e
|
||||
> scalarExpr d (Cast e tn) =
|
||||
> text "cast" <> parens (sep [scalarExpr d e
|
||||
> ,text "as"
|
||||
> ,typeName tn])
|
||||
|
||||
> valueExpr _ (TypedLit tn s) =
|
||||
> scalarExpr _ (TypedLit tn s) =
|
||||
> typeName tn <+> quotes (text s)
|
||||
|
||||
> valueExpr d (SubQueryExpr ty qe) =
|
||||
> scalarExpr d (SubQueryExpr ty qe) =
|
||||
> (case ty of
|
||||
> SqSq -> empty
|
||||
> SqExists -> text "exists"
|
||||
> SqUnique -> text "unique"
|
||||
> ) <+> parens (queryExpr d qe)
|
||||
|
||||
> valueExpr d (QuantifiedComparison v c cp sq) =
|
||||
> valueExpr d v
|
||||
> scalarExpr d (QuantifiedComparison v c cp sq) =
|
||||
> scalarExpr d v
|
||||
> <+> names c
|
||||
> <+> (text $ case cp of
|
||||
> CPAny -> "any"
|
||||
|
@ -171,36 +171,36 @@ which have been changed to try to improve the layout of the output.
|
|||
> CPAll -> "all")
|
||||
> <+> parens (queryExpr d sq)
|
||||
|
||||
> valueExpr d (Match v u sq) =
|
||||
> valueExpr d v
|
||||
> scalarExpr d (Match v u sq) =
|
||||
> scalarExpr d v
|
||||
> <+> text "match"
|
||||
> <+> (if u then text "unique" else empty)
|
||||
> <+> parens (queryExpr d sq)
|
||||
|
||||
> valueExpr d (In b se x) =
|
||||
> valueExpr d se <+>
|
||||
> scalarExpr d (In b se x) =
|
||||
> scalarExpr d se <+>
|
||||
> (if b then empty else text "not")
|
||||
> <+> text "in"
|
||||
> <+> parens (nest (if b then 3 else 7) $
|
||||
> case x of
|
||||
> InList es -> commaSep $ map (valueExpr d) es
|
||||
> InList es -> commaSep $ map (scalarExpr d) es
|
||||
> InQueryExpr qe -> queryExpr d qe)
|
||||
|
||||
> valueExpr d (Array v es) =
|
||||
> valueExpr d v <> brackets (commaSep $ map (valueExpr d) es)
|
||||
> scalarExpr d (Array v es) =
|
||||
> scalarExpr d v <> brackets (commaSep $ map (scalarExpr d) es)
|
||||
|
||||
> valueExpr d (ArrayCtor q) =
|
||||
> scalarExpr d (ArrayCtor q) =
|
||||
> text "array" <> parens (queryExpr d q)
|
||||
|
||||
> valueExpr d (MultisetCtor es) =
|
||||
> text "multiset" <> brackets (commaSep $ map (valueExpr d) es)
|
||||
> scalarExpr d (MultisetCtor es) =
|
||||
> text "multiset" <> brackets (commaSep $ map (scalarExpr d) es)
|
||||
|
||||
> valueExpr d (MultisetQueryCtor q) =
|
||||
> scalarExpr d (MultisetQueryCtor q) =
|
||||
> text "multiset" <> parens (queryExpr d q)
|
||||
|
||||
> valueExpr d (MultisetBinOp a c q b) =
|
||||
> scalarExpr d (MultisetBinOp a c q b) =
|
||||
> sep
|
||||
> [valueExpr d a
|
||||
> [scalarExpr d a
|
||||
> ,text "multiset"
|
||||
> ,text $ case c of
|
||||
> Union -> "union"
|
||||
|
@ -210,32 +210,32 @@ which have been changed to try to improve the layout of the output.
|
|||
> SQDefault -> empty
|
||||
> All -> text "all"
|
||||
> Distinct -> text "distinct"
|
||||
> ,valueExpr d b]
|
||||
> ,scalarExpr d b]
|
||||
|
||||
> {-valueExpr d (Escape v e) =
|
||||
> valueExpr d v <+> text "escape" <+> text [e]
|
||||
> {-scalarExpr d (Escape v e) =
|
||||
> scalarExpr d v <+> text "escape" <+> text [e]
|
||||
|
||||
> valueExpr d (UEscape v e) =
|
||||
> valueExpr d v <+> text "uescape" <+> text [e]-}
|
||||
> scalarExpr d (UEscape v e) =
|
||||
> scalarExpr d v <+> text "uescape" <+> text [e]-}
|
||||
|
||||
> valueExpr d (Collate v c) =
|
||||
> valueExpr d v <+> text "collate" <+> names c
|
||||
> scalarExpr d (Collate v c) =
|
||||
> scalarExpr d v <+> text "collate" <+> names c
|
||||
|
||||
> valueExpr _ (NextValueFor ns) =
|
||||
> scalarExpr _ (NextValueFor ns) =
|
||||
> text "next value for" <+> names ns
|
||||
|
||||
> valueExpr d (VEComment cmt v) =
|
||||
> vcat $ map comment cmt ++ [valueExpr d v]
|
||||
> scalarExpr d (VEComment cmt v) =
|
||||
> vcat $ map comment cmt ++ [scalarExpr d v]
|
||||
|
||||
> valueExpr _ (OdbcLiteral t s) =
|
||||
> scalarExpr _ (OdbcLiteral t s) =
|
||||
> text "{" <> lt t <+> quotes (text s) <> text "}"
|
||||
> where
|
||||
> lt OLDate = text "d"
|
||||
> lt OLTime = text "t"
|
||||
> lt OLTimestamp = text "ts"
|
||||
|
||||
> valueExpr d (OdbcFunc e) =
|
||||
> text "{fn" <+> valueExpr d e <> text "}"
|
||||
> scalarExpr d (OdbcFunc e) =
|
||||
> text "{fn" <+> scalarExpr d e <> text "}"
|
||||
|
||||
> unname :: Name -> String
|
||||
> unname (Name Nothing n) = n
|
||||
|
@ -319,18 +319,18 @@ which have been changed to try to improve the layout of the output.
|
|||
> Distinct -> text "distinct"
|
||||
> ,nest 7 $ sep [selectList dia sl]
|
||||
> ,from dia fr
|
||||
> ,maybeValueExpr dia "where" wh
|
||||
> ,maybeScalarExpr dia "where" wh
|
||||
> ,grpBy dia gb
|
||||
> ,maybeValueExpr dia "having" hv
|
||||
> ,maybeScalarExpr dia "having" hv
|
||||
> ,orderBy dia od
|
||||
> ,me (\e -> text "offset" <+> valueExpr dia e <+> text "rows") off
|
||||
> ,me (\e -> text "offset" <+> scalarExpr dia e <+> text "rows") off
|
||||
> ,fetchFirst
|
||||
> ]
|
||||
> where
|
||||
> fetchFirst =
|
||||
> me (\e -> if diSyntaxFlavour dia == MySQL
|
||||
> then text "limit" <+> valueExpr dia e
|
||||
> else text "fetch first" <+> valueExpr dia e
|
||||
> then text "limit" <+> scalarExpr dia e
|
||||
> else text "fetch first" <+> scalarExpr dia e
|
||||
> <+> text "rows only") fe
|
||||
|
||||
> queryExpr dia (CombineQueryExpr q1 ct d c q2) =
|
||||
|
@ -355,7 +355,7 @@ which have been changed to try to improve the layout of the output.
|
|||
> ,queryExpr d qe]
|
||||
> queryExpr d (Values vs) =
|
||||
> text "values"
|
||||
> <+> nest 7 (commaSep (map (parens . commaSep . map (valueExpr d)) vs))
|
||||
> <+> nest 7 (commaSep (map (parens . commaSep . map (scalarExpr d)) vs))
|
||||
> queryExpr _ (Table t) = text "table" <+> names t
|
||||
> queryExpr d (QEComment cmt v) =
|
||||
> vcat $ map comment cmt ++ [queryExpr d v]
|
||||
|
@ -366,10 +366,10 @@ which have been changed to try to improve the layout of the output.
|
|||
> text "as" <+> name nm
|
||||
> <+> me (parens . commaSep . map name) cols
|
||||
|
||||
> selectList :: Dialect -> [(ValueExpr,Maybe Name)] -> Doc
|
||||
> selectList :: Dialect -> [(ScalarExpr,Maybe Name)] -> Doc
|
||||
> selectList d is = commaSep $ map si is
|
||||
> where
|
||||
> si (e,al) = valueExpr d e <+> me als al
|
||||
> si (e,al) = scalarExpr d e <+> me als al
|
||||
> als al = text "as" <+> name al
|
||||
|
||||
> from :: Dialect -> [TableRef] -> Doc
|
||||
|
@ -381,7 +381,7 @@ which have been changed to try to improve the layout of the output.
|
|||
> tr (TRSimple t) = names t
|
||||
> tr (TRLateral t) = text "lateral" <+> tr t
|
||||
> tr (TRFunction f as) =
|
||||
> names f <> parens (commaSep $ map (valueExpr d) as)
|
||||
> names f <> parens (commaSep $ map (scalarExpr d) as)
|
||||
> tr (TRAlias t a) = sep [tr t, alias a]
|
||||
> tr (TRParens t) = parens $ tr t
|
||||
> tr (TRQueryExpr q) = parens $ queryExpr d q
|
||||
|
@ -399,22 +399,22 @@ which have been changed to try to improve the layout of the output.
|
|||
> JFull -> text "full"
|
||||
> JCross -> text "cross"
|
||||
> ,text "join"]
|
||||
> joinCond (Just (JoinOn e)) = text "on" <+> valueExpr d e
|
||||
> joinCond (Just (JoinOn e)) = text "on" <+> scalarExpr d e
|
||||
> joinCond (Just (JoinUsing es)) =
|
||||
> text "using" <+> parens (commaSep $ map name es)
|
||||
> joinCond Nothing = empty
|
||||
|
||||
> maybeValueExpr :: Dialect -> String -> Maybe ValueExpr -> Doc
|
||||
> maybeValueExpr d k = me
|
||||
> maybeScalarExpr :: Dialect -> String -> Maybe ScalarExpr -> Doc
|
||||
> maybeScalarExpr d k = me
|
||||
> (\e -> sep [text k
|
||||
> ,nest (length k + 1) $ valueExpr d e])
|
||||
> ,nest (length k + 1) $ scalarExpr d e])
|
||||
|
||||
> grpBy :: Dialect -> [GroupingExpr] -> Doc
|
||||
> grpBy _ [] = empty
|
||||
> grpBy d gs = sep [text "group by"
|
||||
> ,nest 9 $ commaSep $ map ge gs]
|
||||
> where
|
||||
> ge (SimpleGroup e) = valueExpr d e
|
||||
> ge (SimpleGroup e) = scalarExpr d e
|
||||
> ge (GroupingParens g) = parens (commaSep $ map ge g)
|
||||
> ge (Cube es) = text "cube" <> parens (commaSep $ map ge es)
|
||||
> ge (Rollup es) = text "rollup" <> parens (commaSep $ map ge es)
|
||||
|
@ -426,7 +426,7 @@ which have been changed to try to improve the layout of the output.
|
|||
> ,nest 9 $ commaSep $ map f os]
|
||||
> where
|
||||
> f (SortSpec e d n) =
|
||||
> valueExpr dia e
|
||||
> scalarExpr dia e
|
||||
> <+> (case d of
|
||||
> Asc -> text "asc"
|
||||
> Desc -> text "desc"
|
||||
|
@ -465,24 +465,24 @@ which have been changed to try to improve the layout of the output.
|
|||
> statement d (CreateDomain nm ty def cs) =
|
||||
> text "create" <+> text "domain" <+> names nm
|
||||
> <+> typeName ty
|
||||
> <+> maybe empty (\def' -> text "default" <+> valueExpr d def') def
|
||||
> <+> maybe empty (\def' -> text "default" <+> scalarExpr d def') def
|
||||
> <+> sep (map con cs)
|
||||
> where
|
||||
> con (cn, e) =
|
||||
> maybe empty (\cn' -> text "constraint" <+> names cn') cn
|
||||
> <+> text "check" <> parens (valueExpr d e)
|
||||
> <+> text "check" <> parens (scalarExpr d e)
|
||||
|
||||
> statement d (AlterDomain nm act) =
|
||||
> texts ["alter","domain"]
|
||||
> <+> names nm
|
||||
> <+> a act
|
||||
> where
|
||||
> a (ADSetDefault v) = texts ["set","default"] <+> valueExpr d v
|
||||
> a (ADSetDefault v) = texts ["set","default"] <+> scalarExpr d v
|
||||
> a (ADDropDefault) = texts ["drop","default"]
|
||||
> a (ADAddConstraint cnm e) =
|
||||
> text "add"
|
||||
> <+> maybe empty (\cnm' -> text "constraint" <+> names cnm') cnm
|
||||
> <+> text "check" <> parens (valueExpr d e)
|
||||
> <+> text "check" <> parens (scalarExpr d e)
|
||||
> a (ADDropConstraint cnm) = texts ["drop", "constraint"]
|
||||
> <+> names cnm
|
||||
|
||||
|
@ -504,7 +504,7 @@ which have been changed to try to improve the layout of the output.
|
|||
|
||||
> statement d (CreateAssertion nm ex) =
|
||||
> texts ["create","assertion"] <+> names nm
|
||||
> <+> text "check" <+> parens (valueExpr d ex)
|
||||
> <+> text "check" <+> parens (scalarExpr d ex)
|
||||
|
||||
> statement _ (DropAssertion nm db) =
|
||||
> text "drop" <+> text "assertion" <+> names nm <+> dropBehav db
|
||||
|
@ -516,7 +516,7 @@ which have been changed to try to improve the layout of the output.
|
|||
> statement d (Delete t a w) =
|
||||
> text "delete" <+> text "from"
|
||||
> <+> names t <+> maybe empty (\x -> text "as" <+> name x) a
|
||||
> <+> maybeValueExpr d "where" w
|
||||
> <+> maybeScalarExpr d "where" w
|
||||
|
||||
> statement _ (Truncate t ir) =
|
||||
> text "truncate" <+> text "table" <+> names t
|
||||
|
@ -536,11 +536,11 @@ which have been changed to try to improve the layout of the output.
|
|||
> text "update" <+> names t
|
||||
> <+> maybe empty (\x -> text "as" <+> name x) a
|
||||
> <+> text "set" <+> commaSep (map sc sts)
|
||||
> <+> maybeValueExpr d "where" whr
|
||||
> <+> maybeScalarExpr d "where" whr
|
||||
> where
|
||||
> sc (Set tg v) = names tg <+> text "=" <+> valueExpr d v
|
||||
> sc (Set tg v) = names tg <+> text "=" <+> scalarExpr d v
|
||||
> sc (SetMultiple ts vs) = parens (commaSep $ map names ts) <+> text "="
|
||||
> <+> parens (commaSep $ map (valueExpr d) vs)
|
||||
> <+> parens (commaSep $ map (scalarExpr d) vs)
|
||||
|
||||
> statement _ (DropTable n b) =
|
||||
> text "drop" <+> text "table" <+> names n <+> dropBehav b
|
||||
|
@ -643,9 +643,9 @@ which have been changed to try to improve the layout of the output.
|
|||
> <+> case mdef of
|
||||
> Nothing -> empty
|
||||
> Just (DefaultClause def) ->
|
||||
> text "default" <+> valueExpr d def
|
||||
> text "default" <+> scalarExpr d def
|
||||
> Just (GenerationClause e) ->
|
||||
> texts ["generated","always","as"] <+> parens (valueExpr d e)
|
||||
> texts ["generated","always","as"] <+> parens (scalarExpr d e)
|
||||
> Just (IdentityColumnSpec w o) ->
|
||||
> text "generated"
|
||||
> <+> (case w of
|
||||
|
@ -663,7 +663,7 @@ which have been changed to try to improve the layout of the output.
|
|||
> pcon ColNotNullConstraint = texts ["not","null"]
|
||||
> pcon ColUniqueConstraint = text "unique"
|
||||
> pcon ColPrimaryKeyConstraint = texts ["primary","key"]
|
||||
> pcon (ColCheckConstraint v) = text "check" <+> parens (valueExpr d v)
|
||||
> pcon (ColCheckConstraint v) = text "check" <+> parens (scalarExpr d v)
|
||||
> pcon (ColReferencesConstraint tb c m u del) =
|
||||
> text "references"
|
||||
> <+> names tb
|
||||
|
@ -709,7 +709,7 @@ which have been changed to try to improve the layout of the output.
|
|||
> alterTableAction d (AlterColumnSetDefault n v) =
|
||||
> texts ["alter", "column"]
|
||||
> <+> name n
|
||||
> <+> texts ["set","default"] <+> valueExpr d v
|
||||
> <+> texts ["set","default"] <+> scalarExpr d v
|
||||
> alterTableAction _ (AlterColumnDropDefault n) =
|
||||
> texts ["alter", "column"]
|
||||
> <+> name n
|
||||
|
@ -761,7 +761,7 @@ which have been changed to try to improve the layout of the output.
|
|||
> <+> refMatch m
|
||||
> <+> refAct "update" u
|
||||
> <+> refAct "delete" del
|
||||
> tableConstraint d (TableCheckConstraint v) = text "check" <+> parens (valueExpr d v)
|
||||
> tableConstraint d (TableCheckConstraint v) = text "check" <+> parens (scalarExpr d v)
|
||||
|
||||
|
||||
> privAct :: PrivilegeAction -> Doc
|
||||
|
|
|
@ -2,8 +2,8 @@
|
|||
> -- | The AST for SQL.
|
||||
> {-# LANGUAGE DeriveDataTypeable #-}
|
||||
> module Language.SQL.SimpleSQL.Syntax
|
||||
> (-- * Value expressions
|
||||
> ValueExpr(..)
|
||||
> (-- * Scalar expressions
|
||||
> ScalarExpr(..)
|
||||
> ,Name(..)
|
||||
> ,TypeName(..)
|
||||
> ,IntervalTypeField(..)
|
||||
|
@ -73,7 +73,7 @@
|
|||
> -- | Represents a value expression. This is used for the expressions
|
||||
> -- in select lists. It is also used for expressions in where, group
|
||||
> -- by, having, order by and so on.
|
||||
> data ValueExpr
|
||||
> data ScalarExpr
|
||||
> = -- | a numeric literal optional decimal point, e+-
|
||||
> -- integral exponent, e.g
|
||||
> --
|
||||
|
@ -121,21 +121,21 @@
|
|||
> -- | Infix binary operators. This is used for symbol operators
|
||||
> -- (a + b), keyword operators (a and b) and multiple keyword
|
||||
> -- operators (a is similar to b)
|
||||
> | BinOp ValueExpr [Name] ValueExpr
|
||||
> | BinOp ScalarExpr [Name] ScalarExpr
|
||||
> -- | Prefix unary operators. This is used for symbol
|
||||
> -- operators, keyword operators and multiple keyword operators.
|
||||
> | PrefixOp [Name] ValueExpr
|
||||
> | PrefixOp [Name] ScalarExpr
|
||||
> -- | Postfix unary operators. This is used for symbol
|
||||
> -- operators, keyword operators and multiple keyword operators.
|
||||
> | PostfixOp [Name] ValueExpr
|
||||
> | PostfixOp [Name] ScalarExpr
|
||||
> -- | Used for ternary, mixfix and other non orthodox
|
||||
> -- operators. Currently used for row constructors, and for
|
||||
> -- between.
|
||||
> | SpecialOp [Name] [ValueExpr]
|
||||
> | SpecialOp [Name] [ScalarExpr]
|
||||
|
||||
> -- | function application (anything that looks like c style
|
||||
> -- function application syntactically)
|
||||
> | App [Name] [ValueExpr]
|
||||
> | App [Name] [ScalarExpr]
|
||||
|
||||
|
||||
> -- | aggregate application, which adds distinct or all, and
|
||||
|
@ -143,14 +143,14 @@
|
|||
> | AggregateApp
|
||||
> {aggName :: [Name] -- ^ aggregate function name
|
||||
> ,aggDistinct :: SetQuantifier -- ^ distinct
|
||||
> ,aggArgs :: [ValueExpr]-- ^ args
|
||||
> ,aggArgs :: [ScalarExpr]-- ^ args
|
||||
> ,aggOrderBy :: [SortSpec] -- ^ order by
|
||||
> ,aggFilter :: Maybe ValueExpr -- ^ filter
|
||||
> ,aggFilter :: Maybe ScalarExpr -- ^ filter
|
||||
> }
|
||||
> -- | aggregates with within group
|
||||
> | AggregateAppGroup
|
||||
> {aggName :: [Name] -- ^ aggregate function name
|
||||
> ,aggArgs :: [ValueExpr] -- ^ args
|
||||
> ,aggArgs :: [ScalarExpr] -- ^ args
|
||||
> ,aggGroup :: [SortSpec] -- ^ within group
|
||||
> }
|
||||
> -- | window application, which adds over (partition by a order
|
||||
|
@ -158,8 +158,8 @@
|
|||
> -- not currently supported
|
||||
> | WindowApp
|
||||
> {wnName :: [Name] -- ^ window function name
|
||||
> ,wnArgs :: [ValueExpr] -- ^ args
|
||||
> ,wnPartition :: [ValueExpr] -- ^ partition by
|
||||
> ,wnArgs :: [ScalarExpr] -- ^ args
|
||||
> ,wnPartition :: [ScalarExpr] -- ^ partition by
|
||||
> ,wnOrderBy :: [SortSpec] -- ^ order by
|
||||
> ,wnFrame :: Maybe Frame -- ^ frame clause
|
||||
> }
|
||||
|
@ -169,56 +169,56 @@
|
|||
> -- of commas. The maybe is for the first unnamed argument
|
||||
> -- if it is present, and the list is for the keyword argument
|
||||
> -- pairs.
|
||||
> | SpecialOpK [Name] (Maybe ValueExpr) [(String,ValueExpr)]
|
||||
> | SpecialOpK [Name] (Maybe ScalarExpr) [(String,ScalarExpr)]
|
||||
|
||||
> -- | cast(a as typename)
|
||||
> | Cast ValueExpr TypeName
|
||||
> | Cast ScalarExpr TypeName
|
||||
|
||||
> -- | case expression. both flavours supported
|
||||
> | Case
|
||||
> {caseTest :: Maybe ValueExpr -- ^ test value
|
||||
> ,caseWhens :: [([ValueExpr],ValueExpr)] -- ^ when branches
|
||||
> ,caseElse :: Maybe ValueExpr -- ^ else value
|
||||
> {caseTest :: Maybe ScalarExpr -- ^ test value
|
||||
> ,caseWhens :: [([ScalarExpr],ScalarExpr)] -- ^ when branches
|
||||
> ,caseElse :: Maybe ScalarExpr -- ^ else value
|
||||
> }
|
||||
|
||||
> | Parens ValueExpr
|
||||
> | Parens ScalarExpr
|
||||
|
||||
> -- | in list literal and in subquery, if the bool is false it
|
||||
> -- means not in was used ('a not in (1,2)')
|
||||
> | In Bool ValueExpr InPredValue
|
||||
> | In Bool ScalarExpr InPredValue
|
||||
|
||||
> -- | exists, all, any, some subqueries
|
||||
> | SubQueryExpr SubQueryExprType QueryExpr
|
||||
|
||||
> | QuantifiedComparison
|
||||
> ValueExpr
|
||||
> ScalarExpr
|
||||
> [Name] -- operator
|
||||
> CompPredQuantifier
|
||||
> QueryExpr
|
||||
|
||||
> | Match ValueExpr Bool -- true if unique
|
||||
> | Match ScalarExpr Bool -- true if unique
|
||||
> QueryExpr
|
||||
> | Array ValueExpr [ValueExpr] -- ^ represents an array
|
||||
> | Array ScalarExpr [ScalarExpr] -- ^ represents an array
|
||||
> -- access expression, or an array ctor
|
||||
> -- e.g. a[3]. The first
|
||||
> -- valueExpr is the array, the
|
||||
> -- scalarExpr is the array, the
|
||||
> -- second is the subscripts/ctor args
|
||||
> | ArrayCtor QueryExpr -- ^ this is used for the query expression version of array constructors, e.g. array(select * from t)
|
||||
|
||||
todo: special syntax for like, similar with escape - escape cannot go
|
||||
in other places
|
||||
|
||||
> -- | Escape ValueExpr Char
|
||||
> -- | UEscape ValueExpr Char
|
||||
> | Collate ValueExpr [Name]
|
||||
> | MultisetBinOp ValueExpr CombineOp SetQuantifier ValueExpr
|
||||
> | MultisetCtor [ValueExpr]
|
||||
> -- | Escape ScalarExpr Char
|
||||
> -- | UEscape ScalarExpr Char
|
||||
> | Collate ScalarExpr [Name]
|
||||
> | MultisetBinOp ScalarExpr CombineOp SetQuantifier ScalarExpr
|
||||
> | MultisetCtor [ScalarExpr]
|
||||
> | MultisetQueryCtor QueryExpr
|
||||
> | NextValueFor [Name]
|
||||
> | VEComment [Comment] ValueExpr
|
||||
> | VEComment [Comment] ScalarExpr
|
||||
> | OdbcLiteral OdbcLiteralType String
|
||||
> -- ^ an odbc literal e.g. {d '2000-01-01'}
|
||||
> | OdbcFunc ValueExpr
|
||||
> | OdbcFunc ScalarExpr
|
||||
> -- ^ an odbc function call e.g. {fn CHARACTER_LENGTH('test')}
|
||||
> deriving (Eq,Show,Read,Data,Typeable)
|
||||
|
||||
|
@ -256,15 +256,15 @@ in other places
|
|||
> | PrecOctets
|
||||
> deriving (Eq,Show,Read,Data,Typeable)
|
||||
|
||||
> -- | Used for 'expr in (value expression list)', and 'expr in
|
||||
> -- | Used for 'expr in (scalar expression list)', and 'expr in
|
||||
> -- (subquery)' syntax.
|
||||
> data InPredValue = InList [ValueExpr]
|
||||
> data InPredValue = InList [ScalarExpr]
|
||||
> | InQueryExpr QueryExpr
|
||||
> deriving (Eq,Show,Read,Data,Typeable)
|
||||
|
||||
not sure if scalar subquery, exists and unique should be represented like this
|
||||
|
||||
> -- | A subquery in a value expression.
|
||||
> -- | A subquery in a scalar expression.
|
||||
> data SubQueryExprType
|
||||
> = -- | exists (query expr)
|
||||
> SqExists
|
||||
|
@ -281,7 +281,7 @@ not sure if scalar subquery, exists and unique should be represented like this
|
|||
> deriving (Eq,Show,Read,Data,Typeable)
|
||||
|
||||
> -- | Represents one field in an order by list.
|
||||
> data SortSpec = SortSpec ValueExpr Direction NullsOrder
|
||||
> data SortSpec = SortSpec ScalarExpr Direction NullsOrder
|
||||
> deriving (Eq,Show,Read,Data,Typeable)
|
||||
|
||||
> -- | Represents 'nulls first' or 'nulls last' in an order by clause.
|
||||
|
@ -303,9 +303,9 @@ not sure if scalar subquery, exists and unique should be represented like this
|
|||
|
||||
> -- | represents the start or end of a frame
|
||||
> data FramePos = UnboundedPreceding
|
||||
> | Preceding ValueExpr
|
||||
> | Preceding ScalarExpr
|
||||
> | Current
|
||||
> | Following ValueExpr
|
||||
> | Following ScalarExpr
|
||||
> | UnboundedFollowing
|
||||
> deriving (Eq,Show,Read,Data,Typeable)
|
||||
|
||||
|
@ -332,7 +332,7 @@ not sure if scalar subquery, exists and unique should be represented like this
|
|||
> data QueryExpr
|
||||
> = Select
|
||||
> {qeSetQuantifier :: SetQuantifier
|
||||
> ,qeSelectList :: [(ValueExpr,Maybe Name)]
|
||||
> ,qeSelectList :: [(ScalarExpr,Maybe Name)]
|
||||
> -- ^ the expressions and the column aliases
|
||||
|
||||
TODO: consider breaking this up. The SQL grammar has
|
||||
|
@ -342,12 +342,12 @@ table expression = <from> [where] [groupby] [having] ...
|
|||
This would make some things a bit cleaner?
|
||||
|
||||
> ,qeFrom :: [TableRef]
|
||||
> ,qeWhere :: Maybe ValueExpr
|
||||
> ,qeWhere :: Maybe ScalarExpr
|
||||
> ,qeGroupBy :: [GroupingExpr]
|
||||
> ,qeHaving :: Maybe ValueExpr
|
||||
> ,qeHaving :: Maybe ScalarExpr
|
||||
> ,qeOrderBy :: [SortSpec]
|
||||
> ,qeOffset :: Maybe ValueExpr
|
||||
> ,qeFetchFirst :: Maybe ValueExpr
|
||||
> ,qeOffset :: Maybe ScalarExpr
|
||||
> ,qeFetchFirst :: Maybe ScalarExpr
|
||||
> }
|
||||
> | CombineQueryExpr
|
||||
> {qe0 :: QueryExpr
|
||||
|
@ -360,7 +360,7 @@ This would make some things a bit cleaner?
|
|||
> {qeWithRecursive :: Bool
|
||||
> ,qeViews :: [(Alias,QueryExpr)]
|
||||
> ,qeQueryExpression :: QueryExpr}
|
||||
> | Values [[ValueExpr]]
|
||||
> | Values [[ScalarExpr]]
|
||||
> | Table [Name]
|
||||
> | QEComment [Comment] QueryExpr
|
||||
> deriving (Eq,Show,Read,Data,Typeable)
|
||||
|
@ -412,7 +412,7 @@ I'm not sure if this is valid syntax or not.
|
|||
> | Cube [GroupingExpr]
|
||||
> | Rollup [GroupingExpr]
|
||||
> | GroupingSets [GroupingExpr]
|
||||
> | SimpleGroup ValueExpr
|
||||
> | SimpleGroup ScalarExpr
|
||||
> deriving (Eq,Show,Read,Data,Typeable)
|
||||
|
||||
> -- | Represents a entry in the csv of tables in the from clause.
|
||||
|
@ -427,7 +427,7 @@ I'm not sure if this is valid syntax or not.
|
|||
> -- | from (query expr)
|
||||
> | TRQueryExpr QueryExpr
|
||||
> -- | from function(args)
|
||||
> | TRFunction [Name] [ValueExpr]
|
||||
> | TRFunction [Name] [ScalarExpr]
|
||||
> -- | from lateral t
|
||||
> | TRLateral TableRef
|
||||
> -- | ODBC {oj t1 left outer join t2 on expr} syntax
|
||||
|
@ -445,7 +445,7 @@ I'm not sure if this is valid syntax or not.
|
|||
> deriving (Eq,Show,Read,Data,Typeable)
|
||||
|
||||
> -- | The join condition.
|
||||
> data JoinCondition = JoinOn ValueExpr -- ^ on expr
|
||||
> data JoinCondition = JoinOn ScalarExpr -- ^ on expr
|
||||
> | JoinUsing [Name] -- ^ using (column list)
|
||||
> deriving (Eq,Show,Read,Data,Typeable)
|
||||
|
||||
|
@ -461,8 +461,8 @@ I'm not sure if this is valid syntax or not.
|
|||
> | CreateView Bool [Name] (Maybe [Name])
|
||||
> QueryExpr (Maybe CheckOption)
|
||||
> | DropView [Name] DropBehaviour
|
||||
> | CreateDomain [Name] TypeName (Maybe ValueExpr)
|
||||
> [(Maybe [Name], ValueExpr)]
|
||||
> | CreateDomain [Name] TypeName (Maybe ScalarExpr)
|
||||
> [(Maybe [Name], ScalarExpr)]
|
||||
> | AlterDomain [Name] AlterDomainAction
|
||||
> | DropDomain [Name] DropBehaviour
|
||||
|
||||
|
@ -475,7 +475,7 @@ I'm not sure if this is valid syntax or not.
|
|||
> | DropCollation
|
||||
> | CreateTranslation
|
||||
> | DropTranslation -}
|
||||
> | CreateAssertion [Name] ValueExpr
|
||||
> | CreateAssertion [Name] ScalarExpr
|
||||
> | DropAssertion [Name] DropBehaviour
|
||||
> {- | CreateTrigger
|
||||
> | DropTrigger
|
||||
|
@ -499,11 +499,11 @@ I'm not sure if this is valid syntax or not.
|
|||
> | CloseCursor
|
||||
> | SelectInto -}
|
||||
> -- | DeletePositioned
|
||||
> | Delete [Name] (Maybe Name) (Maybe ValueExpr)
|
||||
> | Delete [Name] (Maybe Name) (Maybe ScalarExpr)
|
||||
> | Truncate [Name] IdentityRestart
|
||||
> | Insert [Name] (Maybe [Name]) InsertSource
|
||||
> -- | Merge
|
||||
> | Update [Name] (Maybe Name) [SetClause] (Maybe ValueExpr)
|
||||
> | Update [Name] (Maybe Name) [SetClause] (Maybe ScalarExpr)
|
||||
> {- | TemporaryTable
|
||||
> | FreeLocator
|
||||
> | HoldLocator -}
|
||||
|
@ -553,8 +553,8 @@ I'm not sure if this is valid syntax or not.
|
|||
> deriving (Eq,Show,Read,Data,Typeable)
|
||||
|
||||
> data SetClause =
|
||||
> Set [Name] ValueExpr
|
||||
> | SetMultiple [[Name]] [ValueExpr]
|
||||
> Set [Name] ScalarExpr
|
||||
> | SetMultiple [[Name]] [ScalarExpr]
|
||||
> deriving (Eq,Show,Read,Data,Typeable)
|
||||
|
||||
> data TableElement =
|
||||
|
@ -581,7 +581,7 @@ I'm not sure if this is valid syntax or not.
|
|||
> ReferenceMatch
|
||||
> ReferentialAction
|
||||
> ReferentialAction
|
||||
> | ColCheckConstraint ValueExpr
|
||||
> | ColCheckConstraint ScalarExpr
|
||||
> deriving (Eq,Show,Read,Data,Typeable)
|
||||
|
||||
> data TableConstraint =
|
||||
|
@ -591,7 +591,7 @@ I'm not sure if this is valid syntax or not.
|
|||
> ReferenceMatch
|
||||
> ReferentialAction
|
||||
> ReferentialAction
|
||||
> | TableCheckConstraint ValueExpr
|
||||
> | TableCheckConstraint ScalarExpr
|
||||
> deriving (Eq,Show,Read,Data,Typeable)
|
||||
|
||||
|
||||
|
@ -613,7 +613,7 @@ I'm not sure if this is valid syntax or not.
|
|||
|
||||
> data AlterTableAction =
|
||||
> AddColumnDef ColumnDef
|
||||
> | AlterColumnSetDefault Name ValueExpr
|
||||
> | AlterColumnSetDefault Name ScalarExpr
|
||||
> | AlterColumnDropDefault Name
|
||||
> | AlterColumnSetNotNull Name
|
||||
> | AlterColumnDropNotNull Name
|
||||
|
@ -656,9 +656,9 @@ I'm not sure if this is valid syntax or not.
|
|||
> deriving (Eq,Show,Read,Data,Typeable) -}
|
||||
|
||||
> data DefaultClause =
|
||||
> DefaultClause ValueExpr
|
||||
> DefaultClause ScalarExpr
|
||||
> | IdentityColumnSpec IdentityWhen [SequenceGeneratorOption]
|
||||
> | GenerationClause ValueExpr
|
||||
> | GenerationClause ScalarExpr
|
||||
> deriving (Eq,Show,Read,Data,Typeable)
|
||||
|
||||
> data IdentityWhen =
|
||||
|
@ -686,9 +686,9 @@ I'm not sure if this is valid syntax or not.
|
|||
> deriving (Eq,Show,Read,Data,Typeable)
|
||||
|
||||
> data AlterDomainAction =
|
||||
> ADSetDefault ValueExpr
|
||||
> ADSetDefault ScalarExpr
|
||||
> | ADDropDefault
|
||||
> | ADAddConstraint (Maybe [Name]) ValueExpr
|
||||
> | ADAddConstraint (Maybe [Name]) ScalarExpr
|
||||
> | ADDropConstraint [Name]
|
||||
> deriving (Eq,Show,Read,Data,Typeable)
|
||||
|
||||
|
|
17
TODO
17
TODO
|
@ -1,21 +1,24 @@
|
|||
medium tasks next release
|
||||
unescaping identifiers and strings
|
||||
continuation strings testing
|
||||
refactor the symbol lexers - lots of duplicated code
|
||||
rename valueexpr to scalarexpr
|
||||
syntax from hssqlppp:
|
||||
query hints, join hints
|
||||
|
||||
rename combinequeryexpr
|
||||
add comment to statements?
|
||||
review simple enums to make sure they have default
|
||||
use enum in sign in interval literal
|
||||
|
||||
syntax from hssqlppp:
|
||||
query hints, join hints
|
||||
|
||||
unescaping identifiers and strings
|
||||
continuation strings testing
|
||||
|
||||
work on better dialect design: more basic customizability and rule /
|
||||
callback driven
|
||||
|
||||
review/fix documentation and website
|
||||
fix the groups for generated tests
|
||||
|
||||
check the .cabal file module lists
|
||||
|
||||
|
||||
medium tasks next release + 1
|
||||
add annotation
|
||||
|
@ -87,7 +90,7 @@ compare every so often to catch regressions and approve improvements
|
|||
start with tpch, and then add some others
|
||||
|
||||
same with invalid statements to see the error messages
|
||||
start with some simple value exprs and a big query expr which has
|
||||
start with some simple scalar exprs and a big query expr which has
|
||||
stuff (either tokens, whitespace or junk strings)
|
||||
semi-systematically added and/or removed
|
||||
|
||||
|
|
|
@ -30,6 +30,8 @@
|
|||
fix parsing of functions whose name is a keyword (e.g. abs)
|
||||
add basic support for parsing odbc syntax ({d 'literals'} {fn
|
||||
app(something)} and {oj t1 left outer join ... }
|
||||
rename ValueExpr -> ScalarExpr (I think scalar expression is
|
||||
slightly less incorrect)
|
||||
0.4.1 (commit c156c5c34e91e1f7ef449d2c1ea14e282104fd90)
|
||||
tested with ghc 7.4.2, 7.6.3, 7.8.4,7.10.0.20150123
|
||||
simple demonstration of how dialects could be handled internally
|
||||
|
|
|
@ -83,7 +83,7 @@ Test-Suite Tests
|
|||
Language.SQL.SimpleSQL.TestTypes,
|
||||
Language.SQL.SimpleSQL.Tests,
|
||||
Language.SQL.SimpleSQL.Tpch,
|
||||
Language.SQL.SimpleSQL.ValueExprs,
|
||||
Language.SQL.SimpleSQL.ScalarExprs,
|
||||
Language.SQL.SimpleSQL.LexerTests
|
||||
|
||||
other-extensions: TupleSections,DeriveDataTypeable
|
||||
|
|
|
@ -18,10 +18,10 @@ limit syntax
|
|||
[LIMIT {[offset,] row_count | row_count OFFSET offset}]
|
||||
|
||||
> backtickQuotes :: TestItem
|
||||
> backtickQuotes = Group "backtickQuotes" (map (uncurry (TestValueExpr mysql))
|
||||
> backtickQuotes = Group "backtickQuotes" (map (uncurry (TestScalarExpr mysql))
|
||||
> [("`test`", Iden [Name (Just ("`","`")) "test"])
|
||||
> ]
|
||||
> ++ [ParseValueExprFails ansi2011 "`test`"]
|
||||
> ++ [ParseScalarExprFails ansi2011 "`test`"]
|
||||
> )
|
||||
|
||||
> limit :: TestItem
|
||||
|
|
|
@ -45,7 +45,7 @@
|
|||
> ,qeFrom = [TRSimple [Name Nothing "t"]]}]
|
||||
> ]
|
||||
> where
|
||||
> e = TestValueExpr ansi2011 {allowOdbc = True}
|
||||
> e = TestScalarExpr ansi2011 {allowOdbc = True}
|
||||
> --tsql = ParseProcSql defaultParseFlags {pfDialect=sqlServerDialect}
|
||||
> ap n = App [Name Nothing n]
|
||||
> iden n = Iden [Name Nothing n]
|
||||
|
|
|
@ -504,7 +504,7 @@ Specify a non-null value.
|
|||
|
||||
> characterStringLiterals :: TestItem
|
||||
> characterStringLiterals = Group "character string literals"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("'a regular string literal'"
|
||||
> ,StringLit "'" "'" "a regular string literal")
|
||||
> ,("'something' ' some more' 'and more'"
|
||||
|
@ -532,7 +532,7 @@ character set allows them.
|
|||
|
||||
> nationalCharacterStringLiterals :: TestItem
|
||||
> nationalCharacterStringLiterals = Group "national character string literals"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("N'something'", StringLit "N'" "'" "something")
|
||||
> ,("n'something'", StringLit "n'" "'" "something")
|
||||
> ]
|
||||
|
@ -549,7 +549,7 @@ character set allows them.
|
|||
|
||||
> unicodeCharacterStringLiterals :: TestItem
|
||||
> unicodeCharacterStringLiterals = Group "unicode character string literals"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("U&'something'", StringLit "U&'" "'" "something")
|
||||
> {-,("u&'something' escape ="
|
||||
> ,Escape (StringLit "u&'" "'" "something") '=')
|
||||
|
@ -568,7 +568,7 @@ TODO: unicode escape
|
|||
|
||||
> binaryStringLiterals :: TestItem
|
||||
> binaryStringLiterals = Group "binary string literals"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [--("B'101010'", CSStringLit "B" "101010")
|
||||
> ("X'7f7f7f'", StringLit "X'" "'" "7f7f7f")
|
||||
> --,("X'7f7f7f' escape z", Escape (StringLit "X'" "'" "7f7f7f") 'z')
|
||||
|
@ -598,7 +598,7 @@ TODO: unicode escape
|
|||
|
||||
> numericLiterals :: TestItem
|
||||
> numericLiterals = Group "numeric literals"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("11", NumLit "11")
|
||||
> ,("11.11", NumLit "11.11")
|
||||
|
||||
|
@ -704,7 +704,7 @@ TODO: unicode escape
|
|||
|
||||
> intervalLiterals :: TestItem
|
||||
> intervalLiterals = Group "intervalLiterals literals"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("interval '1'", TypedLit (TypeName [Name Nothing "interval"]) "1")
|
||||
> ,("interval '1' day"
|
||||
> ,IntervalLit Nothing "1" (Itf "day" Nothing) Nothing)
|
||||
|
@ -727,7 +727,7 @@ TODO: unicode escape
|
|||
|
||||
> booleanLiterals :: TestItem
|
||||
> booleanLiterals = Group "boolean literals"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("true", Iden [Name Nothing "true"])
|
||||
> ,("false", Iden [Name Nothing "false"])
|
||||
> ,("unknown", Iden [Name Nothing "unknown"])
|
||||
|
@ -747,7 +747,7 @@ Specify names.
|
|||
|
||||
> identifiers :: TestItem
|
||||
> identifiers = Group "identifiers"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("test",Iden [Name Nothing "test"])
|
||||
> ,("_test",Iden [Name Nothing "_test"])
|
||||
> ,("t1",Iden [Name Nothing "t1"])
|
||||
|
@ -1188,11 +1188,11 @@ expression
|
|||
|
||||
> typeNameTests :: TestItem
|
||||
> typeNameTests = Group "type names"
|
||||
> [Group "type names" $ map (uncurry (TestValueExpr ansi2011))
|
||||
> [Group "type names" $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> $ concatMap makeSimpleTests $ fst typeNames
|
||||
> ,Group "generated casts" $ map (uncurry (TestValueExpr ansi2011))
|
||||
> ,Group "generated casts" $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> $ concatMap makeCastTests $ fst typeNames
|
||||
> ,Group "generated typename" $ map (uncurry (TestValueExpr ansi2011))
|
||||
> ,Group "generated typename" $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> $ concatMap makeTests $ snd typeNames]
|
||||
> where
|
||||
> makeSimpleTests (ctn, stn) =
|
||||
|
@ -1213,7 +1213,7 @@ Define a field of a row type.
|
|||
|
||||
> fieldDefinition :: TestItem
|
||||
> fieldDefinition = Group "field definition"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("cast('(1,2)' as row(a int,b char))"
|
||||
> ,Cast (StringLit "'" "'" "(1,2)")
|
||||
> $ RowTypeName [(Name Nothing "a", TypeName [Name Nothing "int"])
|
||||
|
@ -1269,31 +1269,31 @@ Specify a value that is syntactically self-delimited.
|
|||
> ,nestedWindowFunction
|
||||
> ,caseExpression
|
||||
> ,castSpecification
|
||||
> ,nextValueExpression
|
||||
> ,nextScalarExpression
|
||||
> ,fieldReference
|
||||
> ,arrayElementReference
|
||||
> ,multisetElementReference
|
||||
> ,numericValueExpression
|
||||
> ,numericScalarExpression
|
||||
> ,numericValueFunction
|
||||
> ,stringValueExpression
|
||||
> ,stringScalarExpression
|
||||
> ,stringValueFunction
|
||||
> ,datetimeValueExpression
|
||||
> ,datetimeScalarExpression
|
||||
> ,datetimeValueFunction
|
||||
> ,intervalValueExpression
|
||||
> ,intervalScalarExpression
|
||||
> ,intervalValueFunction
|
||||
> ,booleanValueExpression
|
||||
> ,arrayValueExpression
|
||||
> ,booleanScalarExpression
|
||||
> ,arrayScalarExpression
|
||||
> ,arrayValueFunction
|
||||
> ,arrayValueConstructor
|
||||
> ,multisetValueExpression
|
||||
> ,multisetScalarExpression
|
||||
> ,multisetValueFunction
|
||||
> ,multisetValueConstructor
|
||||
> ,parenthesizedValueExpression
|
||||
> ,parenthesizedScalarExpression
|
||||
> ]
|
||||
|
||||
> parenthesizedValueExpression :: TestItem
|
||||
> parenthesizedValueExpression = Group "parenthesized value expression"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> parenthesizedScalarExpression :: TestItem
|
||||
> parenthesizedScalarExpression = Group "parenthesized value expression"
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("(3)", Parens (NumLit "3"))
|
||||
> ,("((3))", Parens $ Parens (NumLit "3"))
|
||||
> ]
|
||||
|
@ -1329,7 +1329,7 @@ Specify one or more values, host parameters, SQL parameters, dynamic parameters,
|
|||
|
||||
> generalValueSpecification :: TestItem
|
||||
> generalValueSpecification = Group "general value specification"
|
||||
> $ map (uncurry (TestValueExpr ansi2011)) $
|
||||
> $ map (uncurry (TestScalarExpr ansi2011)) $
|
||||
> map mkIden ["CURRENT_DEFAULT_TRANSFORM_GROUP"
|
||||
> ,"CURRENT_PATH"
|
||||
> ,"CURRENT_ROLE"
|
||||
|
@ -1383,7 +1383,7 @@ TODO: add the missing bits
|
|||
|
||||
> parameterSpecification :: TestItem
|
||||
> parameterSpecification = Group "parameter specification"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [(":hostparam", HostParameter ":hostparam" Nothing)
|
||||
> ,(":hostparam indicator :another_host_param"
|
||||
> ,HostParameter ":hostparam" $ Just ":another_host_param")
|
||||
|
@ -1420,7 +1420,7 @@ Specify a value whose data type is to be inferred from its context.
|
|||
> contextuallyTypedValueSpecification :: TestItem
|
||||
> contextuallyTypedValueSpecification =
|
||||
> Group "contextually typed value specification"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("null", Iden [Name Nothing "null"])
|
||||
> ,("array[]", Array (Iden [Name Nothing "array"]) [])
|
||||
> ,("multiset[]", MultisetCtor [])
|
||||
|
@ -1438,7 +1438,7 @@ Disambiguate a <period>-separated chain of identifiers.
|
|||
|
||||
> identifierChain :: TestItem
|
||||
> identifierChain = Group "identifier chain"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("a.b", Iden [Name Nothing "a",Name Nothing "b"])]
|
||||
|
||||
== 6.7 <column reference>
|
||||
|
@ -1452,7 +1452,7 @@ Reference a column.
|
|||
|
||||
> columnReference :: TestItem
|
||||
> columnReference = Group "column reference"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("module.a.b", Iden [Name Nothing "module",Name Nothing "a",Name Nothing "b"])]
|
||||
|
||||
== 6.8 <SQL parameter reference>
|
||||
|
@ -1676,7 +1676,7 @@ Specify a data conversion.
|
|||
|
||||
> castSpecification :: TestItem
|
||||
> castSpecification = Group "cast specification"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("cast(a as int)"
|
||||
> ,Cast (Iden [Name Nothing "a"]) (TypeName [Name Nothing "int"]))
|
||||
> ]
|
||||
|
@ -1688,9 +1688,9 @@ Return the next value of a sequence generator.
|
|||
|
||||
<next value expression> ::= NEXT VALUE FOR <sequence generator name>
|
||||
|
||||
> nextValueExpression :: TestItem
|
||||
> nextValueExpression = Group "next value expression"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> nextScalarExpression :: TestItem
|
||||
> nextScalarExpression = Group "next value expression"
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("next value for a.b", NextValueFor [Name Nothing "a", Name Nothing "b"])
|
||||
> ]
|
||||
|
||||
|
@ -1703,7 +1703,7 @@ Reference a field of a row value.
|
|||
|
||||
> fieldReference :: TestItem
|
||||
> fieldReference = Group "field reference"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("f(something).a"
|
||||
> ,BinOp (App [Name Nothing "f"] [Iden [Name Nothing "something"]])
|
||||
> [Name Nothing "."]
|
||||
|
@ -1827,7 +1827,7 @@ Return an element of an array.
|
|||
|
||||
> arrayElementReference :: TestItem
|
||||
> arrayElementReference = Group "array element reference"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("something[3]"
|
||||
> ,Array (Iden [Name Nothing "something"]) [NumLit "3"])
|
||||
> ,("(something(a))[x]"
|
||||
|
@ -1850,7 +1850,7 @@ Return the sole element of a multiset of one element.
|
|||
|
||||
> multisetElementReference :: TestItem
|
||||
> multisetElementReference = Group "multisetElementReference"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("element(something)"
|
||||
> ,App [Name Nothing "element"] [Iden [Name Nothing "something"]])
|
||||
> ]
|
||||
|
@ -1898,9 +1898,9 @@ Specify a numeric value.
|
|||
|
||||
<numeric primary> ::= <value expression primary> | <numeric value function>
|
||||
|
||||
> numericValueExpression :: TestItem
|
||||
> numericValueExpression = Group "numeric value expression"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> numericScalarExpression :: TestItem
|
||||
> numericScalarExpression = Group "numeric value expression"
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("a + b", binOp "+")
|
||||
> ,("a - b", binOp "-")
|
||||
> ,("a * b", binOp "*")
|
||||
|
@ -2086,8 +2086,8 @@ Specify a character string value or a binary string value.
|
|||
<binary concatenation> ::=
|
||||
<binary value expression> <concatenation operator> <binary factor>
|
||||
|
||||
> stringValueExpression :: TestItem
|
||||
> stringValueExpression = Group "string value expression"
|
||||
> stringScalarExpression :: TestItem
|
||||
> stringScalarExpression = Group "string value expression"
|
||||
> [-- todo: string value expression
|
||||
> ]
|
||||
|
||||
|
@ -2229,8 +2229,8 @@ Specify a datetime value.
|
|||
| <datetime value expression> <plus sign> <interval term>
|
||||
| <datetime value expression> <minus sign> <interval term>
|
||||
|
||||
> datetimeValueExpression :: TestItem
|
||||
> datetimeValueExpression = Group "datetime value expression"
|
||||
> datetimeScalarExpression :: TestItem
|
||||
> datetimeScalarExpression = Group "datetime value expression"
|
||||
> [-- todo: datetime value expression
|
||||
> datetimeValueFunction
|
||||
> ]
|
||||
|
@ -2288,8 +2288,8 @@ Specify an interval value.
|
|||
| <left paren> <datetime value expression> <minus sign> <datetime term> <right paren>
|
||||
<interval qualifier>
|
||||
|
||||
> intervalValueExpression :: TestItem
|
||||
> intervalValueExpression = Group "interval value expression"
|
||||
> intervalScalarExpression :: TestItem
|
||||
> intervalScalarExpression = Group "interval value expression"
|
||||
> [-- todo: interval value expression
|
||||
> ]
|
||||
|
||||
|
@ -2355,9 +2355,9 @@ Specify a boolean value.
|
|||
<left paren> <boolean value expression> <right paren>
|
||||
|
||||
|
||||
> booleanValueExpression :: TestItem
|
||||
> booleanValueExpression = Group "booleab value expression"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> booleanScalarExpression :: TestItem
|
||||
> booleanScalarExpression = Group "booleab value expression"
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("a or b", BinOp a [Name Nothing "or"] b)
|
||||
> ,("a and b", BinOp a [Name Nothing "and"] b)
|
||||
> ,("not a", PrefixOp [Name Nothing "not"] a)
|
||||
|
@ -2391,8 +2391,8 @@ Specify an array value.
|
|||
|
||||
<array primary> ::= <array value function> | <value expression primary>
|
||||
|
||||
> arrayValueExpression :: TestItem
|
||||
> arrayValueExpression = Group "array value expression"
|
||||
> arrayScalarExpression :: TestItem
|
||||
> arrayScalarExpression = Group "array value expression"
|
||||
> [-- todo: array value expression
|
||||
> ]
|
||||
|
||||
|
@ -2432,7 +2432,7 @@ Specify construction of an array.
|
|||
|
||||
> arrayValueConstructor :: TestItem
|
||||
> arrayValueConstructor = Group "array value constructor"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("array[1,2,3]"
|
||||
> ,Array (Iden [Name Nothing "array"])
|
||||
> [NumLit "1", NumLit "2", NumLit "3"])
|
||||
|
@ -2468,9 +2468,9 @@ Specify a multiset value.
|
|||
|
||||
<multiset primary> ::= <multiset value function> | <value expression primary>
|
||||
|
||||
> multisetValueExpression :: TestItem
|
||||
> multisetValueExpression = Group "multiset value expression"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> multisetScalarExpression :: TestItem
|
||||
> multisetScalarExpression = Group "multiset value expression"
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("a multiset union b"
|
||||
> ,MultisetBinOp (Iden [Name Nothing "a"]) Union SQDefault (Iden [Name Nothing "b"]))
|
||||
> ,("a multiset union all b"
|
||||
|
@ -2500,7 +2500,7 @@ special case term.
|
|||
|
||||
> multisetValueFunction :: TestItem
|
||||
> multisetValueFunction = Group "multiset value function"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("set(a)", App [Name Nothing "set"] [Iden [Name Nothing "a"]])
|
||||
> ]
|
||||
|
||||
|
@ -2528,7 +2528,7 @@ Specify construction of a multiset.
|
|||
|
||||
> multisetValueConstructor :: TestItem
|
||||
> multisetValueConstructor = Group "multiset value constructor"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("multiset[a,b,c]", MultisetCtor[Iden [Name Nothing "a"]
|
||||
> ,Iden [Name Nothing "b"], Iden [Name Nothing "c"]])
|
||||
> ,("multiset(select * from t)", MultisetQueryCtor qe)
|
||||
|
@ -2606,7 +2606,7 @@ Specify a value or list of values to be constructed into a row.
|
|||
|
||||
> rowValueConstructor :: TestItem
|
||||
> rowValueConstructor = Group "row value constructor"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("(a,b)"
|
||||
> ,SpecialOp [Name Nothing "rowctor"] [Iden [Name Nothing "a"], Iden [Name Nothing "b"]])
|
||||
> ,("row(1)",App [Name Nothing "row"] [NumLit "1"])
|
||||
|
@ -3460,7 +3460,7 @@ Specify a comparison of two row values.
|
|||
|
||||
> comparisonPredicates :: TestItem
|
||||
> comparisonPredicates = Group "comparison predicates"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> $ map mkOp ["=", "<>", "<", ">", "<=", ">="]
|
||||
> ++ [("ROW(a) = ROW(b)"
|
||||
> ,BinOp (App [Name Nothing "ROW"] [a])
|
||||
|
@ -3664,7 +3664,7 @@ Specify a quantified comparison.
|
|||
|
||||
> quantifiedComparisonPredicate :: TestItem
|
||||
> quantifiedComparisonPredicate = Group "quantified comparison predicate"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
|
||||
> [("a = any (select * from t)"
|
||||
> ,QuantifiedComparison (Iden [Name Nothing "a"]) [Name Nothing "="] CPAny qe)
|
||||
|
@ -3691,7 +3691,7 @@ Specify a test for a non-empty set.
|
|||
|
||||
> existsPredicate :: TestItem
|
||||
> existsPredicate = Group "exists predicate"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("exists(select * from t where a = 4)"
|
||||
> ,SubQueryExpr SqExists
|
||||
> $ makeSelect
|
||||
|
@ -3710,7 +3710,7 @@ Specify a test for the absence of duplicate rows.
|
|||
|
||||
> uniquePredicate :: TestItem
|
||||
> uniquePredicate = Group "unique predicate"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("unique(select * from t where a = 4)"
|
||||
> ,SubQueryExpr SqUnique
|
||||
> $ makeSelect
|
||||
|
@ -3746,7 +3746,7 @@ Specify a test for matching rows.
|
|||
|
||||
> matchPredicate :: TestItem
|
||||
> matchPredicate = Group "match predicate"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("a match (select a from t)"
|
||||
> ,Match (Iden [Name Nothing "a"]) False qe)
|
||||
> ,("(a,b) match (select a,b from t)"
|
||||
|
@ -4098,7 +4098,7 @@ Specify a default collation.
|
|||
|
||||
> collateClause :: TestItem
|
||||
> collateClause = Group "collate clause"
|
||||
> $ map (uncurry (TestValueExpr ansi2011))
|
||||
> $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("a collate my_collation"
|
||||
> ,Collate (Iden [Name Nothing "a"]) [Name Nothing "my_collation"])]
|
||||
|
||||
|
@ -4209,7 +4209,7 @@ Specify a value computed from a collection of rows.
|
|||
|
||||
> aggregateFunction :: TestItem
|
||||
> aggregateFunction = Group "aggregate function"
|
||||
> $ map (uncurry (TestValueExpr ansi2011)) $
|
||||
> $ map (uncurry (TestScalarExpr ansi2011)) $
|
||||
> [("count(*)",App [Name Nothing "count"] [Star])
|
||||
> ,("count(*) filter (where something > 5)"
|
||||
> ,AggregateApp [Name Nothing "count"] SQDefault [Star] [] fil)
|
||||
|
|
|
@ -1,13 +1,13 @@
|
|||
|
||||
Tests for parsing value expressions
|
||||
Tests for parsing scalar expressions
|
||||
|
||||
> module Language.SQL.SimpleSQL.ValueExprs (valueExprTests) where
|
||||
> module Language.SQL.SimpleSQL.ScalarExprs (scalarExprTests) where
|
||||
|
||||
> import Language.SQL.SimpleSQL.TestTypes
|
||||
> import Language.SQL.SimpleSQL.Syntax
|
||||
|
||||
> valueExprTests :: TestItem
|
||||
> valueExprTests = Group "valueExprTests"
|
||||
> scalarExprTests :: TestItem
|
||||
> scalarExprTests = Group "scalarExprTests"
|
||||
> [literals
|
||||
> ,identifiers
|
||||
> ,star
|
||||
|
@ -24,7 +24,7 @@ Tests for parsing value expressions
|
|||
> ]
|
||||
|
||||
> literals :: TestItem
|
||||
> literals = Group "literals" $ map (uncurry (TestValueExpr ansi2011))
|
||||
> literals = Group "literals" $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("3", NumLit "3")
|
||||
> ,("3.", NumLit "3.")
|
||||
> ,("3.3", NumLit "3.3")
|
||||
|
@ -46,14 +46,14 @@ Tests for parsing value expressions
|
|||
> ]
|
||||
|
||||
> identifiers :: TestItem
|
||||
> identifiers = Group "identifiers" $ map (uncurry (TestValueExpr ansi2011))
|
||||
> identifiers = Group "identifiers" $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("iden1", Iden [Name Nothing "iden1"])
|
||||
> --,("t.a", Iden2 "t" "a")
|
||||
> ,("\"quoted identifier\"", Iden [Name (Just ("\"","\"")) "quoted identifier"])
|
||||
> ]
|
||||
|
||||
> star :: TestItem
|
||||
> star = Group "star" $ map (uncurry (TestValueExpr ansi2011))
|
||||
> star = Group "star" $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("*", Star)
|
||||
> --,("t.*", Star2 "t")
|
||||
> --,("ROW(t.*,42)", App "ROW" [Star2 "t", NumLit "42"])
|
||||
|
@ -61,12 +61,12 @@ Tests for parsing value expressions
|
|||
|
||||
> parameter :: TestItem
|
||||
> parameter = Group "parameter"
|
||||
> [TestValueExpr ansi2011 "?" Parameter
|
||||
> ,TestValueExpr postgres "$13" $ PositionalArg 13]
|
||||
> [TestScalarExpr ansi2011 "?" Parameter
|
||||
> ,TestScalarExpr postgres "$13" $ PositionalArg 13]
|
||||
|
||||
|
||||
> dots :: TestItem
|
||||
> dots = Group "dot" $ map (uncurry (TestValueExpr ansi2011))
|
||||
> dots = Group "dot" $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("t.a", Iden [Name Nothing "t",Name Nothing "a"])
|
||||
> ,("t.*", BinOp (Iden [Name Nothing "t"]) [Name Nothing "."] Star)
|
||||
> ,("a.b.c", Iden [Name Nothing "a",Name Nothing "b",Name Nothing "c"])
|
||||
|
@ -74,14 +74,14 @@ Tests for parsing value expressions
|
|||
> ]
|
||||
|
||||
> app :: TestItem
|
||||
> app = Group "app" $ map (uncurry (TestValueExpr ansi2011))
|
||||
> app = Group "app" $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("f()", App [Name Nothing "f"] [])
|
||||
> ,("f(a)", App [Name Nothing "f"] [Iden [Name Nothing "a"]])
|
||||
> ,("f(a,b)", App [Name Nothing "f"] [Iden [Name Nothing "a"], Iden [Name Nothing "b"]])
|
||||
> ]
|
||||
|
||||
> caseexp :: TestItem
|
||||
> caseexp = Group "caseexp" $ map (uncurry (TestValueExpr ansi2011))
|
||||
> caseexp = Group "caseexp" $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("case a when 1 then 2 end"
|
||||
> ,Case (Just $ Iden [Name Nothing "a"]) [([NumLit "1"]
|
||||
> ,NumLit "2")] Nothing)
|
||||
|
@ -117,7 +117,7 @@ Tests for parsing value expressions
|
|||
> ,miscOps]
|
||||
|
||||
> binaryOperators :: TestItem
|
||||
> binaryOperators = Group "binaryOperators" $ map (uncurry (TestValueExpr ansi2011))
|
||||
> binaryOperators = Group "binaryOperators" $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("a + b", BinOp (Iden [Name Nothing "a"]) [Name Nothing "+"] (Iden [Name Nothing "b"]))
|
||||
> -- sanity check fixities
|
||||
> -- todo: add more fixity checking
|
||||
|
@ -132,7 +132,7 @@ Tests for parsing value expressions
|
|||
> ]
|
||||
|
||||
> unaryOperators :: TestItem
|
||||
> unaryOperators = Group "unaryOperators" $ map (uncurry (TestValueExpr ansi2011))
|
||||
> unaryOperators = Group "unaryOperators" $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("not a", PrefixOp [Name Nothing "not"] $ Iden [Name Nothing "a"])
|
||||
> ,("not not a", PrefixOp [Name Nothing "not"] $ PrefixOp [Name Nothing "not"] $ Iden [Name Nothing "a"])
|
||||
> ,("+a", PrefixOp [Name Nothing "+"] $ Iden [Name Nothing "a"])
|
||||
|
@ -141,7 +141,7 @@ Tests for parsing value expressions
|
|||
|
||||
|
||||
> casts :: TestItem
|
||||
> casts = Group "operators" $ map (uncurry (TestValueExpr ansi2011))
|
||||
> casts = Group "operators" $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("cast('1' as int)"
|
||||
> ,Cast (StringLit "'" "'" "1") $ TypeName [Name Nothing "int"])
|
||||
|
||||
|
@ -163,7 +163,7 @@ Tests for parsing value expressions
|
|||
> ]
|
||||
|
||||
> subqueries :: TestItem
|
||||
> subqueries = Group "unaryOperators" $ map (uncurry (TestValueExpr ansi2011))
|
||||
> subqueries = Group "unaryOperators" $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("exists (select a from t)", SubQueryExpr SqExists ms)
|
||||
> ,("(select a from t)", SubQueryExpr SqSq ms)
|
||||
|
||||
|
@ -189,7 +189,7 @@ Tests for parsing value expressions
|
|||
> }
|
||||
|
||||
> miscOps :: TestItem
|
||||
> miscOps = Group "unaryOperators" $ map (uncurry (TestValueExpr ansi2011))
|
||||
> miscOps = Group "unaryOperators" $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("a in (1,2,3)"
|
||||
> ,In True (Iden [Name Nothing "a"]) $ InList $ map NumLit ["1","2","3"])
|
||||
|
||||
|
@ -327,7 +327,7 @@ target_string
|
|||
> ]
|
||||
|
||||
> aggregates :: TestItem
|
||||
> aggregates = Group "aggregates" $ map (uncurry (TestValueExpr ansi2011))
|
||||
> aggregates = Group "aggregates" $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("count(*)",App [Name Nothing "count"] [Star])
|
||||
|
||||
> ,("sum(a order by a)"
|
||||
|
@ -342,7 +342,7 @@ target_string
|
|||
> ]
|
||||
|
||||
> windowFunctions :: TestItem
|
||||
> windowFunctions = Group "windowFunctions" $ map (uncurry (TestValueExpr ansi2011))
|
||||
> windowFunctions = Group "windowFunctions" $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("max(a) over ()", WindowApp [Name Nothing "max"] [Iden [Name Nothing "a"]] [] [] Nothing)
|
||||
> ,("count(*) over ()", WindowApp [Name Nothing "count"] [Star] [] [] Nothing)
|
||||
|
||||
|
@ -401,7 +401,7 @@ target_string
|
|||
> ]
|
||||
|
||||
> parens :: TestItem
|
||||
> parens = Group "parens" $ map (uncurry (TestValueExpr ansi2011))
|
||||
> parens = Group "parens" $ map (uncurry (TestScalarExpr ansi2011))
|
||||
> [("(a)", Parens (Iden [Name Nothing "a"]))
|
||||
> ,("(a + b)", Parens (BinOp (Iden [Name Nothing "a"]) [Name Nothing "+"] (Iden [Name Nothing "b"])))
|
||||
> ]
|
||||
|
@ -412,4 +412,4 @@ target_string
|
|||
> ,"char_length"
|
||||
> ]
|
||||
> where
|
||||
> t fn = TestValueExpr ansi2011 (fn ++ "(a)") $ App [Name Nothing fn] [Iden [Name Nothing "a"]]
|
||||
> t fn = TestScalarExpr ansi2011 (fn ++ "(a)") $ App [Name Nothing fn] [Iden [Name Nothing "a"]]
|
|
@ -16,7 +16,7 @@ mentioned give a parse error. Not sure if this will be too awkward due
|
|||
to lots of tricky exceptions/variationsx.
|
||||
|
||||
> data TestItem = Group String [TestItem]
|
||||
> | TestValueExpr Dialect String ValueExpr
|
||||
> | TestScalarExpr Dialect String ScalarExpr
|
||||
> | TestQueryExpr Dialect String QueryExpr
|
||||
> | TestStatement Dialect String Statement
|
||||
> | TestStatements Dialect String [Statement]
|
||||
|
@ -30,7 +30,7 @@ should all be TODO to convert to a testqueryexpr test.
|
|||
check that the string given fails to parse
|
||||
|
||||
> | ParseQueryExprFails Dialect String
|
||||
> | ParseValueExprFails Dialect String
|
||||
> | ParseScalarExprFails Dialect String
|
||||
> | LexTest Dialect String [Token]
|
||||
> | LexFails Dialect String
|
||||
> deriving (Eq,Show)
|
||||
|
|
|
@ -25,7 +25,7 @@ test data to the Test.Framework tests.
|
|||
> import Language.SQL.SimpleSQL.QueryExprComponents
|
||||
> import Language.SQL.SimpleSQL.QueryExprs
|
||||
> import Language.SQL.SimpleSQL.TableRefs
|
||||
> import Language.SQL.SimpleSQL.ValueExprs
|
||||
> import Language.SQL.SimpleSQL.ScalarExprs
|
||||
> import Language.SQL.SimpleSQL.Odbc
|
||||
> import Language.SQL.SimpleSQL.Tpch
|
||||
> import Language.SQL.SimpleSQL.LexerTests
|
||||
|
@ -45,7 +45,7 @@ order on the generated documentation.
|
|||
> testData =
|
||||
> Group "parserTest"
|
||||
> [lexerTests
|
||||
> ,valueExprTests
|
||||
> ,scalarExprTests
|
||||
> ,odbcTests
|
||||
> ,queryExprComponentTests
|
||||
> ,queryExprsTests
|
||||
|
@ -71,8 +71,8 @@ order on the generated documentation.
|
|||
> itemToTest :: TestItem -> T.TestTree
|
||||
> itemToTest (Group nm ts) =
|
||||
> T.testGroup nm $ map itemToTest ts
|
||||
> itemToTest (TestValueExpr d str expected) =
|
||||
> toTest parseValueExpr prettyValueExpr d str expected
|
||||
> itemToTest (TestScalarExpr d str expected) =
|
||||
> toTest parseScalarExpr prettyScalarExpr d str expected
|
||||
> itemToTest (TestQueryExpr d str expected) =
|
||||
> toTest parseQueryExpr prettyQueryExpr d str expected
|
||||
> itemToTest (TestStatement d str expected) =
|
||||
|
@ -85,8 +85,8 @@ order on the generated documentation.
|
|||
> itemToTest (ParseQueryExprFails d str) =
|
||||
> toFTest parseQueryExpr prettyQueryExpr d str
|
||||
|
||||
> itemToTest (ParseValueExprFails d str) =
|
||||
> toFTest parseValueExpr prettyValueExpr d str
|
||||
> itemToTest (ParseScalarExprFails d str) =
|
||||
> toFTest parseScalarExpr prettyScalarExpr d str
|
||||
|
||||
> itemToTest (LexTest d s ts) = makeLexerTest d s ts
|
||||
> itemToTest (LexFails d s) = makeLexingFailsTest d s
|
||||
|
|
|
@ -17,7 +17,7 @@ Converts the test data to asciidoc
|
|||
> doc n (Group nm is) =
|
||||
> Heading n nm
|
||||
> : concatMap (doc (n + 1)) is
|
||||
> doc _ (TestValueExpr _ str e) =
|
||||
> doc _ (TestScalarExpr _ str e) =
|
||||
> [Row str (ppShow e)]
|
||||
> doc _ (TestQueryExpr _ str e) =
|
||||
> [Row str (ppShow e)]
|
||||
|
@ -29,8 +29,8 @@ Converts the test data to asciidoc
|
|||
> [Row str (ppShow $ parseQueryExpr d "" Nothing str)]
|
||||
> doc _ (ParseQueryExprFails d str) =
|
||||
> [Row str (ppShow $ parseQueryExpr d "" Nothing str)]
|
||||
> doc _ (ParseValueExprFails d str) =
|
||||
> [Row str (ppShow $ parseValueExpr d "" Nothing str)]
|
||||
> doc _ (ParseScalarExprFails d str) =
|
||||
> [Row str (ppShow $ parseScalarExpr d "" Nothing str)]
|
||||
|
||||
> doc _ (LexTest d str t) =
|
||||
> [Row str (ppShow $ lexSQL d "" Nothing str)]
|
||||
|
|
|
@ -56,7 +56,7 @@ link:https://github.com/JakeWheat/intro_to_parsing/blob/master/SimpleSQLQueryPar
|
|||
** offset and fetch
|
||||
** set operators
|
||||
** common table expressions
|
||||
** wide range of value expressions
|
||||
** wide range of scalar expressions
|
||||
* DDL
|
||||
** TODO
|
||||
* non-query DML
|
||||
|
|
|
@ -28,7 +28,7 @@ get the best parser error messages possible.
|
|||
|
||||
=== Select lists
|
||||
|
||||
Supports value expressions, aliases with optional 'as'.
|
||||
Supports scalar expressions, aliases with optional 'as'.
|
||||
|
||||
Doesn't support 'select * as (a,b,c) from t' yet.
|
||||
|
||||
|
@ -52,12 +52,12 @@ Supports 'select distinct' and explicit 'select all'.
|
|||
|
||||
=== Group by clause
|
||||
|
||||
Supports value expressions, group by (), cube, rollup, grouping
|
||||
Supports scalar expressions, group by (), cube, rollup, grouping
|
||||
parentheses and grouping sets with nested grouping expressions.
|
||||
|
||||
=== Order by clause
|
||||
|
||||
Supports value expressions, asc/desc and nulls first/last.
|
||||
Supports scalar expressions, asc/desc and nulls first/last.
|
||||
|
||||
=== Offset and fetch
|
||||
|
||||
|
@ -75,9 +75,9 @@ For example: values (1,2),(3,4).
|
|||
|
||||
For example: 'table t', which is shorthand for 'select * from t'.
|
||||
|
||||
=== Value expressions
|
||||
=== Scalar expressions
|
||||
|
||||
The value expressions type and parser is used in many contexts,
|
||||
The scalar expressions type and parser is used in many contexts,
|
||||
including:
|
||||
|
||||
* select lists;
|
||||
|
@ -91,7 +91,7 @@ including:
|
|||
This doesn't exactly follow the ANSI Standards, which have separate
|
||||
grammars for most of these.
|
||||
|
||||
The supported value expressions include:
|
||||
The supported scalar expressions include:
|
||||
|
||||
* basic string literals in single quotes
|
||||
* number literals: digits.digitse+-exp
|
||||
|
|
Loading…
Reference in a new issue