1
Fork 0

rename ValueExpr to ScalarExpr

This commit is contained in:
Jake Wheat 2016-02-22 23:24:25 +02:00
parent 09223c3de9
commit a2645ace3f
15 changed files with 418 additions and 413 deletions

View file

@ -5,7 +5,7 @@ notes
Public api Public api
Names - parsing identifiers Names - parsing identifiers
Typenames Typenames
Value expressions Scalar expressions
simple literals simple literals
star, param star, param
parens expression, row constructor and scalar subquery parens expression, row constructor and scalar subquery
@ -14,7 +14,7 @@ Value expressions
suffixes: in, between, quantified comparison, match predicate, array suffixes: in, between, quantified comparison, match predicate, array
subscript, escape, collate subscript, escape, collate
operators operators
value expression top level scalar expression top level
helpers helpers
query expressions query expressions
select lists select lists
@ -75,7 +75,7 @@ syntax.
There are three big areas which are tricky to left factor: There are three big areas which are tricky to left factor:
* typenames * typenames
* value expressions which can start with an identifier * scalar expressions which can start with an identifier
* infix and suffix operators * infix and suffix operators
=== typenames === 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 extensibility of the parser and might affect the ease of adapting to
support other sql dialects. 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 identifiers, and can't be distinguished the tokens after the initial
identifier are parsed. Using try to implement these variations is very identifier are parsed. Using try to implement these variations is very
simple but makes the code much harder to debug and makes the parser 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, There is further ambiguity e.g. with typed literals with precision,
functions, aggregates, etc. - these are an identifier, followed by 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 only later that we can find a token which tells us which flavour it
is. 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 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. 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 parser/syntax. This means we don't try to stop non boolean valued
expressions in boolean valued contexts in the parser. Another area 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. whereas the standard only allows column names with optional collation.
These are all areas which are specified (roughly speaking) in the 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. > -- | This is the module with the parser functions.
> module Language.SQL.SimpleSQL.Parse > module Language.SQL.SimpleSQL.Parse
> (parseQueryExpr > (parseQueryExpr
> ,parseValueExpr > ,parseScalarExpr
> ,parseStatement > ,parseStatement
> ,parseStatements > ,parseStatements
> ,ParseError(..)) where > ,ParseError(..)) where
@ -250,8 +250,8 @@ fixing them in the syntax but leaving them till the semantic checking
> -> Either ParseError [Statement] > -> Either ParseError [Statement]
> parseStatements = wrapParse statements > parseStatements = wrapParse statements
> -- | Parses a value expression. > -- | Parses a scalar expression.
> parseValueExpr :: Dialect > parseScalarExpr :: Dialect
> -- ^ dialect of SQL to use > -- ^ dialect of SQL to use
> -> FilePath > -> FilePath
> -- ^ filename to use in error messages > -- ^ 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 > -- in the source to use in error messages
> -> String > -> String
> -- ^ the SQL source to parse > -- ^ the SQL source to parse
> -> Either ParseError ValueExpr > -> Either ParseError ScalarExpr
> parseValueExpr = wrapParse valueExpr > parseScalarExpr = wrapParse scalarExpr
This helper function takes the parser given and: 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 Dots: dots in identifier chains are parsed here and represented in the
Iden constructor usually. If parts of the chains are non identifier 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 instead. Dotten chain identifiers which appear in other contexts (such
as function names, table names, are represented as [Name] only. 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" > ,"varbinary"
> ] > ]
= Value expressions = Scalar expressions
== simple literals == simple literals
See the stringToken lexer below for notes on string literal syntax. 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 > stringLit = (\(s,e,t) -> StringLit s e t) <$> stringTokExtend
> numberLit :: Parser ValueExpr > numberLit :: Parser ScalarExpr
> numberLit = NumLit <$> sqlNumberTok False > numberLit = NumLit <$> sqlNumberTok False
> simpleLiteral :: Parser ValueExpr > simpleLiteral :: Parser ScalarExpr
> simpleLiteral = numberLit <|> stringLit > simpleLiteral = numberLit <|> stringLit
== star, param, host param == 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 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 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 "*" > star = Star <$ symbol "*"
== parameter == parameter
@ -579,7 +579,7 @@ unnamed parameter or named parameter
use in e.g. select * from t where a = ? use in e.g. select * from t where a = ?
select x from t where x > :param select x from t where x > :param
> parameter :: Parser ValueExpr > parameter :: Parser ScalarExpr
> parameter = choice > parameter = choice
> [Parameter <$ questionMark > [Parameter <$ questionMark
> ,HostParameter > ,HostParameter
@ -588,17 +588,17 @@ select x from t where x > :param
== positional arg == positional arg
> positionalArg :: Parser ValueExpr > positionalArg :: Parser ScalarExpr
> positionalArg = PositionalArg <$> positionalArgTok > positionalArg = PositionalArg <$> positionalArgTok
== parens == 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 > parensExpr = parens $ choice
> [SubQueryExpr SqSq <$> queryExpr > [SubQueryExpr SqSq <$> queryExpr
> ,ctor <$> commaSep1 valueExpr] > ,ctor <$> commaSep1 scalarExpr]
> where > where
> ctor [a] = Parens a > ctor [a] = Parens a
> ctor as = SpecialOp [Name Nothing "rowctor"] as > ctor as = SpecialOp [Name Nothing "rowctor"] as
@ -610,24 +610,24 @@ syntax can start with the same keyword.
=== case expression === case expression
> caseExpr :: Parser ValueExpr > caseExpr :: Parser ScalarExpr
> caseExpr = > caseExpr =
> Case <$> (keyword_ "case" *> optionMaybe valueExpr) > Case <$> (keyword_ "case" *> optionMaybe scalarExpr)
> <*> many1 whenClause > <*> many1 whenClause
> <*> optionMaybe elseClause > <*> optionMaybe elseClause
> <* keyword_ "end" > <* keyword_ "end"
> where > where
> whenClause = (,) <$> (keyword_ "when" *> commaSep1 valueExpr) > whenClause = (,) <$> (keyword_ "when" *> commaSep1 scalarExpr)
> <*> (keyword_ "then" *> valueExpr) > <*> (keyword_ "then" *> scalarExpr)
> elseClause = keyword_ "else" *> valueExpr > elseClause = keyword_ "else" *> scalarExpr
=== cast === cast
cast: cast(expr as type) cast: cast(expr as type)
> cast :: Parser ValueExpr > cast :: Parser ScalarExpr
> cast = keyword_ "cast" *> > cast = keyword_ "cast" *>
> parens (Cast <$> valueExpr > parens (Cast <$> scalarExpr
> <*> (keyword_ "as" *> typeName)) > <*> (keyword_ "as" *> typeName))
=== exists, unique === exists, unique
@ -635,33 +635,33 @@ cast: cast(expr as type)
subquery expression: subquery expression:
[exists|unique] (queryexpr) [exists|unique] (queryexpr)
> subquery :: Parser ValueExpr > subquery :: Parser ScalarExpr
> subquery = SubQueryExpr <$> sqkw <*> parens queryExpr > subquery = SubQueryExpr <$> sqkw <*> parens queryExpr
> where > where
> sqkw = SqExists <$ keyword_ "exists" <|> SqUnique <$ keyword_ "unique" > sqkw = SqExists <$ keyword_ "exists" <|> SqUnique <$ keyword_ "unique"
=== array/multiset constructor === array/multiset constructor
> arrayCtor :: Parser ValueExpr > arrayCtor :: Parser ScalarExpr
> arrayCtor = keyword_ "array" >> > arrayCtor = keyword_ "array" >>
> choice > choice
> [ArrayCtor <$> parens queryExpr > [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 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. multiset(query expr). It must be there for compatibility or something.
> multisetCtor :: Parser ValueExpr > multisetCtor :: Parser ScalarExpr
> multisetCtor = > multisetCtor =
> choice > choice
> [keyword_ "multiset" >> > [keyword_ "multiset" >>
> choice > choice
> [MultisetQueryCtor <$> parens queryExpr > [MultisetQueryCtor <$> parens queryExpr
> ,MultisetCtor <$> brackets (commaSep valueExpr)] > ,MultisetCtor <$> brackets (commaSep scalarExpr)]
> ,keyword_ "table" >> > ,keyword_ "table" >>
> MultisetQueryCtor <$> parens queryExpr] > MultisetQueryCtor <$> parens queryExpr]
> nextValueFor :: Parser ValueExpr > nextValueFor :: Parser ScalarExpr
> nextValueFor = keywords_ ["next","value","for"] >> > nextValueFor = keywords_ ["next","value","for"] >>
> NextValueFor <$> names > 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 It uses try because of a conflict with interval type names: todo, fix
this. also fix the monad -> applicative this. also fix the monad -> applicative
> intervalLit :: Parser ValueExpr > intervalLit :: Parser ScalarExpr
> intervalLit = try (keyword_ "interval" >> do > intervalLit = try (keyword_ "interval" >> do
> s <- optionMaybe $ choice [True <$ symbol_ "+" > s <- optionMaybe $ choice [True <$ symbol_ "+"
> ,False <$ symbol_ "-"] > ,False <$ symbol_ "-"]
@ -707,11 +707,11 @@ The windows is a suffix on the app parser
=== iden prefix term === 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) (todo: really put all of them here instead of just some of them)
> idenExpr :: Parser ValueExpr > idenExpr :: Parser ScalarExpr
> idenExpr = > idenExpr =
> -- todo: work out how to left factor this > -- todo: work out how to left factor this
> try (TypedLit <$> typeName <*> singleQuotesOnlyStringTok) > try (TypedLit <$> typeName <*> singleQuotesOnlyStringTok)
@ -724,7 +724,7 @@ all the value expressions which start with an identifier
> multisetSetFunction = > multisetSetFunction =
> App [Name Nothing "set"] . (:[]) <$> > App [Name Nothing "set"] . (:[]) <$>
> (try (keyword_ "set" *> openParen) > (try (keyword_ "set" *> openParen)
> *> valueExpr <* closeParen) > *> scalarExpr <* closeParen)
> keywordFunction = > keywordFunction =
> let makeKeywordFunction x = if map toLower x `elem` keywordFunctionNames > let makeKeywordFunction x = if map toLower x `elem` keywordFunctionNames
> then return [Name Nothing x] > then return [Name Nothing x]
@ -809,12 +809,12 @@ operatorname(firstArg keyword0 arg0 keyword1 arg1 etc.)
> -> SpecialOpKFirstArg -- has a first arg without a keyword > -> SpecialOpKFirstArg -- has a first arg without a keyword
> -> [(String,Bool)] -- the other args with their keywords > -> [(String,Bool)] -- the other args with their keywords
> -- and whether they are optional > -- and whether they are optional
> -> Parser ValueExpr > -> Parser ScalarExpr
> specialOpK opName firstArg kws = > specialOpK opName firstArg kws =
> keyword_ opName >> do > keyword_ opName >> do
> void openParen > void openParen
> let pfa = do > let pfa = do
> e <- valueExpr > e <- scalarExpr
> -- check we haven't parsed the first > -- check we haven't parsed the first
> -- keyword as an identifier > -- keyword as an identifier
> case (e,kws) of > case (e,kws) of
@ -832,7 +832,7 @@ operatorname(firstArg keyword0 arg0 keyword1 arg1 etc.)
> pure $ SpecialOpK [Name Nothing opName] fa $ catMaybes as > pure $ SpecialOpK [Name Nothing opName] fa $ catMaybes as
> where > where
> parseArg (nm,mand) = > parseArg (nm,mand) =
> let p = keyword_ nm >> valueExpr > let p = keyword_ nm >> scalarExpr
> in fmap (nm,) <$> if mand > in fmap (nm,) <$> if mand
> then Just <$> p > then Just <$> p
> else optionMaybe (try p) > else optionMaybe (try p)
@ -857,31 +857,31 @@ TRIM( [ [{LEADING | TRAILING | BOTH}] [removal_char] FROM ]
target_string target_string
[COLLATE collation_name] ) [COLLATE collation_name] )
> specialOpKs :: Parser ValueExpr > specialOpKs :: Parser ScalarExpr
> specialOpKs = choice $ map try > specialOpKs = choice $ map try
> [extract, position, substring, convert, translate, overlay, trim] > [extract, position, substring, convert, translate, overlay, trim]
> extract :: Parser ValueExpr > extract :: Parser ScalarExpr
> extract = specialOpK "extract" SOKMandatory [("from", True)] > extract = specialOpK "extract" SOKMandatory [("from", True)]
> position :: Parser ValueExpr > position :: Parser ScalarExpr
> position = specialOpK "position" SOKMandatory [("in", True)] > position = specialOpK "position" SOKMandatory [("in", True)]
strictly speaking, the substring must have at least one of from and strictly speaking, the substring must have at least one of from and
for, but the parser doens't enforce this for, but the parser doens't enforce this
> substring :: Parser ValueExpr > substring :: Parser ScalarExpr
> substring = specialOpK "substring" SOKMandatory > substring = specialOpK "substring" SOKMandatory
> [("from", False),("for", False)] > [("from", False),("for", False)]
> convert :: Parser ValueExpr > convert :: Parser ScalarExpr
> convert = specialOpK "convert" SOKMandatory [("using", True)] > convert = specialOpK "convert" SOKMandatory [("using", True)]
> translate :: Parser ValueExpr > translate :: Parser ScalarExpr
> translate = specialOpK "translate" SOKMandatory [("using", True)] > translate = specialOpK "translate" SOKMandatory [("using", True)]
> overlay :: Parser ValueExpr > overlay :: Parser ScalarExpr
> overlay = specialOpK "overlay" SOKMandatory > overlay = specialOpK "overlay" SOKMandatory
> [("placing", True),("from", True),("for", False)] > [("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 the both ' ' is filled in as the default if either parts are missing
in the source in the source
> trim :: Parser ValueExpr > trim :: Parser ScalarExpr
> trim = > trim =
> keyword "trim" >> > keyword "trim" >>
> parens (mkTrim > parens (mkTrim
> <$> option "both" sides > <$> option "both" sides
> <*> option " " singleQuotesOnlyStringTok > <*> option " " singleQuotesOnlyStringTok
> <*> (keyword_ "from" *> valueExpr)) > <*> (keyword_ "from" *> scalarExpr))
> where > where
> sides = choice ["leading" <$ keyword_ "leading" > sides = choice ["leading" <$ keyword_ "leading"
> ,"trailing" <$ keyword_ "trailing" > ,"trailing" <$ keyword_ "trailing"
@ -908,7 +908,7 @@ in the source
=== app, aggregate, window === app, aggregate, window
This parses all these variations: 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 aggregate variations (distinct, order by in parens, filter and where
suffixes) suffixes)
window apps (fn/agg followed by over) 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 left factoring, later they will even have to be partially combined
together. together.
> app :: Parser ([Name] -> ValueExpr) > app :: Parser ([Name] -> ScalarExpr)
> app = > app =
> openParen *> choice > openParen *> choice
> [duplicates > [duplicates
> <**> (commaSep1 valueExpr > <**> (commaSep1 scalarExpr
> <**> (((option [] orderBy) <* closeParen) > <**> (((option [] orderBy) <* closeParen)
> <**> (optionMaybe afilter <$$$$$> AggregateApp))) > <**> (optionMaybe afilter <$$$$$> AggregateApp)))
> -- separate cases with no all or distinct which must have at > -- separate cases with no all or distinct which must have at
> -- least one value expr > -- least one scalar expr
> ,commaSep1 valueExpr > ,commaSep1 scalarExpr
> <**> choice > <**> choice
> [closeParen *> choice > [closeParen *> choice
> [window > [window
@ -935,17 +935,17 @@ together.
> ,pure (flip App)] > ,pure (flip App)]
> ,orderBy <* closeParen > ,orderBy <* closeParen
> <**> (optionMaybe afilter <$$$$> aggAppWithoutDupe)] > <**> (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) > ,([] <$ closeParen) <**> option (flip App) (window <|> withinGroup)
> ] > ]
> where > where
> aggAppWithoutDupeOrd n es f = AggregateApp n SQDefault es [] f > aggAppWithoutDupeOrd n es f = AggregateApp n SQDefault es [] f
> aggAppWithoutDupe n = AggregateApp n SQDefault > aggAppWithoutDupe n = AggregateApp n SQDefault
> afilter :: Parser ValueExpr > afilter :: Parser ScalarExpr
> afilter = keyword_ "filter" *> parens (keyword_ "where" *> valueExpr) > afilter = keyword_ "filter" *> parens (keyword_ "where" *> scalarExpr)
> withinGroup :: Parser ([ValueExpr] -> [Name] -> ValueExpr) > withinGroup :: Parser ([ScalarExpr] -> [Name] -> ScalarExpr)
> withinGroup = > withinGroup =
> (keywords_ ["within", "group"] *> parens orderBy) <$$$> AggregateAppGroup > (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 TODO: add window support for other aggregate variations, needs some
changes to the syntax also changes to the syntax also
> window :: Parser ([ValueExpr] -> [Name] -> ValueExpr) > window :: Parser ([ScalarExpr] -> [Name] -> ScalarExpr)
> window = > window =
> keyword_ "over" *> openParen *> option [] partitionBy > keyword_ "over" *> openParen *> option [] partitionBy
> <**> (option [] orderBy > <**> (option [] orderBy
> <**> (((optionMaybe frameClause) <* closeParen) <$$$$$> WindowApp)) > <**> (((optionMaybe frameClause) <* closeParen) <$$$$$> WindowApp))
> where > where
> partitionBy = keywords_ ["partition","by"] *> commaSep1 valueExpr > partitionBy = keywords_ ["partition","by"] *> commaSep1 scalarExpr
> frameClause = > frameClause =
> frameRowsRange -- TODO: this 'and' could be an issue > frameRowsRange -- TODO: this 'and' could be an issue
> <**> (choice [(keyword_ "between" *> frameLimit True) > <**> (choice [(keyword_ "between" *> frameLimit True)
@ -984,14 +984,14 @@ changes to the syntax also
> ,keyword_ "unbounded" *> > ,keyword_ "unbounded" *>
> choice [UnboundedPreceding <$ keyword_ "preceding" > choice [UnboundedPreceding <$ keyword_ "preceding"
> ,UnboundedFollowing <$ keyword_ "following"] > ,UnboundedFollowing <$ keyword_ "following"]
> ,(if useB then valueExprB else valueExpr) > ,(if useB then scalarExprB else scalarExpr)
> <**> (Preceding <$ keyword_ "preceding" > <**> (Preceding <$ keyword_ "preceding"
> <|> Following <$ keyword_ "following") > <|> Following <$ keyword_ "following")
> ] > ]
== suffixes == suffixes
These are all generic suffixes on any value expr These are all generic suffixes on any scalar expr
=== in === in
@ -999,12 +999,12 @@ in: two variations:
a in (expr0, expr1, ...) a in (expr0, expr1, ...)
a in (queryexpr) a in (queryexpr)
> inSuffix :: Parser (ValueExpr -> ValueExpr) > inSuffix :: Parser (ScalarExpr -> ScalarExpr)
> inSuffix = > inSuffix =
> mkIn <$> inty > mkIn <$> inty
> <*> parens (choice > <*> parens (choice
> [InQueryExpr <$> queryExpr > [InQueryExpr <$> queryExpr
> ,InList <$> commaSep1 valueExpr]) > ,InList <$> commaSep1 scalarExpr])
> where > where
> inty = choice [True <$ keyword_ "in" > inty = choice [True <$ keyword_ "in"
> ,False <$ keywords_ ["not","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, postgres does, which might be standard across SQL implementations,
which is that you can't have a binary and operator in the middle 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 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 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 = > betweenSuffix =
> makeOp <$> Name Nothing <$> opName > makeOp <$> Name Nothing <$> opName
> <*> valueExprB > <*> scalarExprB
> <*> (keyword_ "and" *> valueExprB) > <*> (keyword_ "and" *> scalarExprB)
> where > where
> opName = choice > opName = choice
> ["between" <$ keyword_ "between" > ["between" <$ keyword_ "between"
@ -1040,7 +1040,7 @@ and operator. This is the call to valueExprB.
a = any (select * from t) a = any (select * from t)
> quantifiedComparisonSuffix :: Parser (ValueExpr -> ValueExpr) > quantifiedComparisonSuffix :: Parser (ScalarExpr -> ScalarExpr)
> quantifiedComparisonSuffix = do > quantifiedComparisonSuffix = do
> c <- comp > c <- comp
> cq <- compQuan > cq <- compQuan
@ -1058,7 +1058,7 @@ a = any (select * from t)
a match (select a from t) a match (select a from t)
> matchPredicateSuffix :: Parser (ValueExpr -> ValueExpr) > matchPredicateSuffix :: Parser (ScalarExpr -> ScalarExpr)
> matchPredicateSuffix = do > matchPredicateSuffix = do
> keyword_ "match" > keyword_ "match"
> u <- option False (True <$ keyword_ "unique") > u <- option False (True <$ keyword_ "unique")
@ -1067,9 +1067,9 @@ a match (select a from t)
=== array subscript === array subscript
> arraySuffix :: Parser (ValueExpr -> ValueExpr) > arraySuffix :: Parser (ScalarExpr -> ScalarExpr)
> arraySuffix = do > arraySuffix = do
> es <- brackets (commaSep valueExpr) > es <- brackets (commaSep scalarExpr)
> pure $ \v -> Array v es > pure $ \v -> Array v es
=== escape === 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 TODO: this needs fixing. Escape is only part of other nodes, and not a
separate suffix. separate suffix.
> {-escapeSuffix :: Parser (ValueExpr -> ValueExpr) > {-escapeSuffix :: Parser (ScalarExpr -> ScalarExpr)
> escapeSuffix = do > escapeSuffix = do
> ctor <- choice > ctor <- choice
> [Escape <$ keyword_ "escape" > [Escape <$ keyword_ "escape"
@ -1098,7 +1098,7 @@ separate suffix.
=== collate === collate
> collateSuffix:: Parser (ValueExpr -> ValueExpr) > collateSuffix:: Parser (ScalarExpr -> ScalarExpr)
> collateSuffix = do > collateSuffix = do
> keyword_ "collate" > keyword_ "collate"
> i <- names > 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) scalar expressions (the other is a variation on joins)
> odbcExpr :: Parser ValueExpr > odbcExpr :: Parser ScalarExpr
> odbcExpr = between (symbol "{") (symbol "}") > odbcExpr = between (symbol "{") (symbol "}")
> (odbcTimeLit <|> odbcFunc) > (odbcTimeLit <|> odbcFunc)
> where > where
@ -1122,7 +1122,7 @@ scalar expressions (the other is a variation on joins)
> -- todo: this parser is too general, the expr part > -- todo: this parser is too general, the expr part
> -- should be only a function call (from a whitelist of functions) > -- should be only a function call (from a whitelist of functions)
> -- or the extract operator > -- or the extract operator
> odbcFunc = OdbcFunc <$> (keyword "fn" *> valueExpr) > odbcFunc = OdbcFunc <$> (keyword "fn" *> scalarExpr)
== operators == 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 wanted to avoid extensibility and to not be concerned with parse error
messages, but both of these are too important. 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 = > opTable bExpr =
> [-- parse match and quantified comparisons as postfix ops > [-- parse match and quantified comparisons as postfix ops
> -- todo: left factor the quantified comparison with regular > -- 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 (.) > prefix' p = E.Prefix . chainl1 p $ pure (.)
> postfix' p = E.Postfix . chainl1 p $ pure (flip (.)) > 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 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 fragile and could at least do with some heavy explanation. Update: the
'try's have migrated into the individual parsers, they still need 'try's have migrated into the individual parsers, they still need
documenting/fixing. documenting/fixing.
> valueExpr :: Parser ValueExpr > scalarExpr :: Parser ScalarExpr
> valueExpr = E.buildExpressionParser (opTable False) term > scalarExpr = E.buildExpressionParser (opTable False) term
> term :: Parser ValueExpr > term :: Parser ScalarExpr
> term = choice [simpleLiteral > term = choice [simpleLiteral
> ,parameter > ,parameter
> ,positionalArg > ,positionalArg
@ -1275,12 +1275,12 @@ documenting/fixing.
> ,specialOpKs > ,specialOpKs
> ,idenExpr > ,idenExpr
> ,odbcExpr] > ,odbcExpr]
> <?> "value expression" > <?> "scalar expression"
expose the b expression for window frame clause range between expose the b expression for window frame clause range between
> valueExprB :: Parser ValueExpr > scalarExprB :: Parser ScalarExpr
> valueExprB = E.buildExpressionParser (opTable True) term > scalarExprB = E.buildExpressionParser (opTable True) term
== helper parsers == helper parsers
@ -1306,7 +1306,7 @@ use a data type for the datetime field?
> ,"hour","minute","second"]) > ,"hour","minute","second"])
> <?> "datetime field" > <?> "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). and set operations (query expr).
> duplicates :: Parser SetQuantifier > duplicates :: Parser SetQuantifier
@ -1320,11 +1320,11 @@ and set operations (query expr).
== select lists == select lists
> selectItem :: Parser (ValueExpr,Maybe Name) > selectItem :: Parser (ScalarExpr,Maybe Name)
> selectItem = (,) <$> valueExpr <*> optionMaybe als > selectItem = (,) <$> scalarExpr <*> optionMaybe als
> where als = optional (keyword_ "as") *> name > where als = optional (keyword_ "as") *> name
> selectList :: Parser [(ValueExpr,Maybe Name)] > selectList :: Parser [(ScalarExpr,Maybe Name)]
> selectList = commaSep1 selectItem > selectList = commaSep1 selectItem
== from == from
@ -1355,7 +1355,7 @@ aliases.
> ,do > ,do
> n <- names > n <- names
> choice [TRFunction n > choice [TRFunction n
> <$> parens (commaSep valueExpr) > <$> parens (commaSep scalarExpr)
> ,pure $ TRSimple n] > ,pure $ TRSimple n]
> -- todo: I think you can only have outer joins inside the oj, > -- todo: I think you can only have outer joins inside the oj,
> -- not sure. > -- not sure.
@ -1389,7 +1389,7 @@ it more readable)
> joinCondition :: Parser JoinCondition > joinCondition :: Parser JoinCondition
> joinCondition = choice > joinCondition = choice
> [keyword_ "on" >> JoinOn <$> valueExpr > [keyword_ "on" >> JoinOn <$> scalarExpr
> ,keyword_ "using" >> JoinUsing <$> parens (commaSep1 name)] > ,keyword_ "using" >> JoinUsing <$> parens (commaSep1 name)]
> fromAlias :: Parser Alias > fromAlias :: Parser Alias
@ -1403,8 +1403,8 @@ it more readable)
Parsers for where, group by, having, order by and limit, which are Parsers for where, group by, having, order by and limit, which are
pretty trivial. pretty trivial.
> whereClause :: Parser ValueExpr > whereClause :: Parser ScalarExpr
> whereClause = keyword_ "where" *> valueExpr > whereClause = keyword_ "where" *> scalarExpr
> groupByClause :: Parser [GroupingExpr] > groupByClause :: Parser [GroupingExpr]
> groupByClause = keywords_ ["group","by"] *> commaSep1 groupingExpression > groupByClause = keywords_ ["group","by"] *> commaSep1 groupingExpression
@ -1417,17 +1417,17 @@ pretty trivial.
> ,GroupingParens <$> parens (commaSep groupingExpression) > ,GroupingParens <$> parens (commaSep groupingExpression)
> ,keywords_ ["grouping", "sets"] >> > ,keywords_ ["grouping", "sets"] >>
> GroupingSets <$> parens (commaSep groupingExpression) > GroupingSets <$> parens (commaSep groupingExpression)
> ,SimpleGroup <$> valueExpr > ,SimpleGroup <$> scalarExpr
> ] > ]
> having :: Parser ValueExpr > having :: Parser ScalarExpr
> having = keyword_ "having" *> valueExpr > having = keyword_ "having" *> scalarExpr
> orderBy :: Parser [SortSpec] > orderBy :: Parser [SortSpec]
> orderBy = keywords_ ["order","by"] *> commaSep1 ob > orderBy = keywords_ ["order","by"] *> commaSep1 ob
> where > where
> ob = SortSpec > ob = SortSpec
> <$> valueExpr > <$> scalarExpr
> <*> option DirDefault (choice [Asc <$ keyword_ "asc" > <*> option DirDefault (choice [Asc <$ keyword_ "asc"
> ,Desc <$ keyword_ "desc"]) > ,Desc <$ keyword_ "desc"])
> <*> option NullsOrderDefault > <*> option NullsOrderDefault
@ -1439,25 +1439,25 @@ pretty trivial.
allows offset and fetch in either order allows offset and fetch in either order
+ postgresql offset without row(s) and limit instead of fetch also + 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) > offsetFetch = permute ((,) <$?> (Nothing, Just <$> offset)
> <|?> (Nothing, Just <$> fetch)) > <|?> (Nothing, Just <$> fetch))
> offset :: Parser ValueExpr > offset :: Parser ScalarExpr
> offset = keyword_ "offset" *> valueExpr > offset = keyword_ "offset" *> scalarExpr
> <* option () (choice [keyword_ "rows" > <* option () (choice [keyword_ "rows"
> ,keyword_ "row"]) > ,keyword_ "row"])
> fetch :: Parser ValueExpr > fetch :: Parser ScalarExpr
> fetch = fetchFirst <|> limit > fetch = fetchFirst <|> limit
> where > where
> fetchFirst = guardDialect [ANSI2011] > fetchFirst = guardDialect [ANSI2011]
> *> fs *> valueExpr <* ro > *> fs *> scalarExpr <* ro
> fs = makeKeywordTree ["fetch first", "fetch next"] > fs = makeKeywordTree ["fetch first", "fetch next"]
> ro = makeKeywordTree ["rows only", "row only"] > ro = makeKeywordTree ["rows only", "row only"]
> -- todo: not in ansi sql dialect > -- todo: not in ansi sql dialect
> limit = guardDialect [MySQL] *> > limit = guardDialect [MySQL] *>
> keyword_ "limit" *> valueExpr > keyword_ "limit" *> scalarExpr
== common table expressions == common table expressions
@ -1489,7 +1489,7 @@ and union, etc..
> mkSelect d sl (Just (TableExpression f w g h od ofs fe)) = > mkSelect d sl (Just (TableExpression f w g h od ofs fe)) =
> Select d sl f w g h od ofs fe > Select d sl f w g h od ofs fe
> values = keyword_ "values" > values = keyword_ "values"
> >> Values <$> commaSep (parens (commaSep valueExpr)) > >> Values <$> commaSep (parens (commaSep scalarExpr))
> table = keyword_ "table" >> Table <$> names > table = keyword_ "table" >> Table <$> names
local data type to help with parsing the bit after the select list, local data type to help with parsing the bit after the select list,
@ -1499,12 +1499,12 @@ be in the public syntax?
> data TableExpression > data TableExpression
> = TableExpression > = TableExpression
> {_teFrom :: [TableRef] > {_teFrom :: [TableRef]
> ,_teWhere :: Maybe ValueExpr > ,_teWhere :: Maybe ScalarExpr
> ,_teGroupBy :: [GroupingExpr] > ,_teGroupBy :: [GroupingExpr]
> ,_teHaving :: Maybe ValueExpr > ,_teHaving :: Maybe ScalarExpr
> ,_teOrderBy :: [SortSpec] > ,_teOrderBy :: [SortSpec]
> ,_teOffset :: Maybe ValueExpr > ,_teOffset :: Maybe ScalarExpr
> ,_teFetchFirst :: Maybe ValueExpr} > ,_teFetchFirst :: Maybe ScalarExpr}
> tableExpression :: Parser TableExpression > tableExpression :: Parser TableExpression
> tableExpression = mkTe <$> from > tableExpression = mkTe <$> from
@ -1597,10 +1597,10 @@ TODO: change style
> where > where
> defaultClause = choice [ > defaultClause = choice [
> keyword_ "default" >> > keyword_ "default" >>
> DefaultClause <$> valueExpr > DefaultClause <$> scalarExpr
> -- todo: left factor > -- todo: left factor
> ,try (keywords_ ["generated","always","as"] >> > ,try (keywords_ ["generated","always","as"] >>
> GenerationClause <$> parens valueExpr) > GenerationClause <$> parens scalarExpr)
> ,keyword_ "generated" >> > ,keyword_ "generated" >>
> IdentityColumnSpec > IdentityColumnSpec
> <$> (GeneratedAlways <$ keyword_ "always" > <$> (GeneratedAlways <$ keyword_ "always"
@ -1619,7 +1619,7 @@ TODO: change style
> TableUniqueConstraint <$> parens (commaSep1 name) > TableUniqueConstraint <$> parens (commaSep1 name)
> primaryKey = keywords_ ["primary", "key"] >> > primaryKey = keywords_ ["primary", "key"] >>
> TablePrimaryKeyConstraint <$> parens (commaSep1 name) > TablePrimaryKeyConstraint <$> parens (commaSep1 name)
> check = keyword_ "check" >> TableCheckConstraint <$> parens valueExpr > check = keyword_ "check" >> TableCheckConstraint <$> parens scalarExpr
> references = keywords_ ["foreign", "key"] >> > references = keywords_ ["foreign", "key"] >>
> (\cs ft ftcs m (u,d) -> TableReferencesConstraint cs ft ftcs m u d) > (\cs ft ftcs m (u,d) -> TableReferencesConstraint cs ft ftcs m u d)
> <$> parens (commaSep1 name) > <$> parens (commaSep1 name)
@ -1658,7 +1658,7 @@ TODO: change style
> notNull = ColNotNullConstraint <$ keywords_ ["not", "null"] > notNull = ColNotNullConstraint <$ keywords_ ["not", "null"]
> unique = ColUniqueConstraint <$ keyword_ "unique" > unique = ColUniqueConstraint <$ keyword_ "unique"
> primaryKey = ColPrimaryKeyConstraint <$ keywords_ ["primary", "key"] > primaryKey = ColPrimaryKeyConstraint <$ keywords_ ["primary", "key"]
> check = keyword_ "check" >> ColCheckConstraint <$> parens valueExpr > check = keyword_ "check" >> ColCheckConstraint <$> parens scalarExpr
> references = keyword_ "references" >> > references = keyword_ "references" >>
> (\t c m (ou,od) -> ColReferencesConstraint t c m ou od) > (\t c m (ou,od) -> ColReferencesConstraint t c m ou od)
> <$> names > <$> names
@ -1733,7 +1733,7 @@ slightly hacky parser for signed integers
> setDefault :: Parser (Name -> AlterTableAction) > setDefault :: Parser (Name -> AlterTableAction)
> -- todo: left factor > -- todo: left factor
> setDefault = try (keywords_ ["set","default"]) >> > setDefault = try (keywords_ ["set","default"]) >>
> valueExpr <$$> AlterColumnSetDefault > scalarExpr <$$> AlterColumnSetDefault
> dropDefault = AlterColumnDropDefault <$ try (keywords_ ["drop","default"]) > dropDefault = AlterColumnDropDefault <$ try (keywords_ ["drop","default"])
> setNotNull = AlterColumnSetNotNull <$ try (keywords_ ["set","not","null"]) > setNotNull = AlterColumnSetNotNull <$ try (keywords_ ["set","not","null"])
> dropNotNull = AlterColumnDropNotNull <$ try (keywords_ ["drop","not","null"]) > dropNotNull = AlterColumnDropNotNull <$ try (keywords_ ["drop","not","null"])
@ -1779,11 +1779,11 @@ slightly hacky parser for signed integers
> CreateDomain > CreateDomain
> <$> names > <$> names
> <*> (optional (keyword_ "as") *> typeName) > <*> (optional (keyword_ "as") *> typeName)
> <*> optionMaybe (keyword_ "default" *> valueExpr) > <*> optionMaybe (keyword_ "default" *> scalarExpr)
> <*> many con > <*> many con
> where > where
> con = (,) <$> optionMaybe (keyword_ "constraint" *> names) > con = (,) <$> optionMaybe (keyword_ "constraint" *> names)
> <*> (keyword_ "check" *> parens valueExpr) > <*> (keyword_ "check" *> parens scalarExpr)
> alterDomain :: Parser Statement > alterDomain :: Parser Statement
> alterDomain = keyword_ "domain" >> > alterDomain = keyword_ "domain" >>
@ -1792,11 +1792,11 @@ slightly hacky parser for signed integers
> <*> (setDefault <|> constraint > <*> (setDefault <|> constraint
> <|> (keyword_ "drop" *> (dropDefault <|> dropConstraint))) > <|> (keyword_ "drop" *> (dropDefault <|> dropConstraint)))
> where > where
> setDefault = keywords_ ["set", "default"] >> ADSetDefault <$> valueExpr > setDefault = keywords_ ["set", "default"] >> ADSetDefault <$> scalarExpr
> constraint = keyword_ "add" >> > constraint = keyword_ "add" >>
> ADAddConstraint > ADAddConstraint
> <$> optionMaybe (keyword_ "constraint" *> names) > <$> optionMaybe (keyword_ "constraint" *> names)
> <*> (keyword_ "check" *> parens valueExpr) > <*> (keyword_ "check" *> parens scalarExpr)
> dropDefault = ADDropDefault <$ keyword_ "default" > dropDefault = ADDropDefault <$ keyword_ "default"
> dropConstraint = keyword_ "constraint" >> ADDropConstraint <$> names > dropConstraint = keyword_ "constraint" >> ADDropConstraint <$> names
@ -1824,7 +1824,7 @@ slightly hacky parser for signed integers
> createAssertion = keyword_ "assertion" >> > createAssertion = keyword_ "assertion" >>
> CreateAssertion > CreateAssertion
> <$> names > <$> names
> <*> (keyword_ "check" *> parens valueExpr) > <*> (keyword_ "check" *> parens scalarExpr)
> dropAssertion :: Parser Statement > dropAssertion :: Parser Statement
@ -1840,7 +1840,7 @@ slightly hacky parser for signed integers
> Delete > Delete
> <$> names > <$> names
> <*> optionMaybe (optional (keyword_ "as") *> name) > <*> optionMaybe (optional (keyword_ "as") *> name)
> <*> optionMaybe (keyword_ "where" *> valueExpr) > <*> optionMaybe (keyword_ "where" *> scalarExpr)
> truncateSt :: Parser Statement > truncateSt :: Parser Statement
> truncateSt = keywords_ ["truncate", "table"] >> > truncateSt = keywords_ ["truncate", "table"] >>
@ -1864,15 +1864,15 @@ slightly hacky parser for signed integers
> <$> names > <$> names
> <*> optionMaybe (optional (keyword_ "as") *> name) > <*> optionMaybe (optional (keyword_ "as") *> name)
> <*> (keyword_ "set" *> commaSep1 setClause) > <*> (keyword_ "set" *> commaSep1 setClause)
> <*> optionMaybe (keyword_ "where" *> valueExpr) > <*> optionMaybe (keyword_ "where" *> scalarExpr)
> where > where
> setClause = multipleSet <|> singleSet > setClause = multipleSet <|> singleSet
> multipleSet = SetMultiple > multipleSet = SetMultiple
> <$> parens (commaSep1 names) > <$> parens (commaSep1 names)
> <*> (symbol "=" *> parens (commaSep1 valueExpr)) > <*> (symbol "=" *> parens (commaSep1 scalarExpr))
> singleSet = Set > singleSet = Set
> <$> names > <$> names
> <*> (symbol "=" *> valueExpr) > <*> (symbol "=" *> scalarExpr)
> dropBehaviour :: Parser DropBehaviour > dropBehaviour :: Parser DropBehaviour
> dropBehaviour = > dropBehaviour =

View file

@ -4,7 +4,7 @@
> -- readable way. > -- readable way.
> module Language.SQL.SimpleSQL.Pretty > module Language.SQL.SimpleSQL.Pretty
> (prettyQueryExpr > (prettyQueryExpr
> ,prettyValueExpr > ,prettyScalarExpr
> ,prettyStatement > ,prettyStatement
> ,prettyStatements > ,prettyStatements
> ) where > ) where
@ -25,8 +25,8 @@ which have been changed to try to improve the layout of the output.
> prettyQueryExpr d = render . queryExpr d > prettyQueryExpr d = render . queryExpr d
> -- | Convert a value expr ast to concrete syntax. > -- | Convert a value expr ast to concrete syntax.
> prettyValueExpr :: Dialect -> ValueExpr -> String > prettyScalarExpr :: Dialect -> ScalarExpr -> String
> prettyValueExpr d = render . valueExpr d > prettyScalarExpr d = render . scalarExpr d
> -- | Convert a statement ast to concrete syntax. > -- | Convert a statement ast to concrete syntax.
> prettyStatement :: Dialect -> Statement -> String > 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 :: Dialect -> [Statement] -> String
> prettyStatements d = render . vcat . map ((<> text ";\n") . statement d) > prettyStatements d = render . vcat . map ((<> text ";\n") . statement d)
= value expressions = scalar expressions
> valueExpr :: Dialect -> ValueExpr -> Doc > scalarExpr :: Dialect -> ScalarExpr -> Doc
> valueExpr _ (StringLit s e t) = text s <> text t <> text e > scalarExpr _ (StringLit s e t) = text s <> text t <> text e
> valueExpr _ (NumLit s) = text s > scalarExpr _ (NumLit s) = text s
> valueExpr _ (IntervalLit s v f t) = > scalarExpr _ (IntervalLit s v f t) =
> text "interval" > text "interval"
> <+> me (\x -> if x then text "+" else text "-") s > <+> me (\x -> if x then text "+" else text "-") s
> <+> quotes (text v) > <+> quotes (text v)
> <+> intervalTypeField f > <+> intervalTypeField f
> <+> me (\x -> text "to" <+> intervalTypeField x) t > <+> me (\x -> text "to" <+> intervalTypeField x) t
> valueExpr _ (Iden i) = names i > scalarExpr _ (Iden i) = names i
> valueExpr _ Star = text "*" > scalarExpr _ Star = text "*"
> valueExpr _ Parameter = text "?" > scalarExpr _ Parameter = text "?"
> valueExpr _ (PositionalArg n) = text $ "$" ++ show n > scalarExpr _ (PositionalArg n) = text $ "$" ++ show n
> valueExpr _ (HostParameter p i) = > scalarExpr _ (HostParameter p i) =
> text p > text p
> <+> me (\i' -> text "indicator" <+> text i') i > <+> 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 > names f
> <> parens ((case d of > <> parens ((case d of
> Distinct -> text "distinct" > Distinct -> text "distinct"
> All -> text "all" > All -> text "all"
> SQDefault -> empty) > SQDefault -> empty)
> <+> commaSep (map (valueExpr dia) es) > <+> commaSep (map (scalarExpr dia) es)
> <+> orderBy dia od) > <+> orderBy dia od)
> <+> me (\x -> text "filter" > <+> 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 > names f
> <> parens (commaSep (map (valueExpr d) es)) > <> parens (commaSep (map (scalarExpr d) es))
> <+> if null od > <+> if null od
> then empty > then empty
> else text "within group" <+> parens (orderBy d od) > else text "within group" <+> parens (orderBy d od)
> valueExpr d (WindowApp f es pb od fr) = > scalarExpr d (WindowApp f es pb od fr) =
> names f <> parens (commaSep $ map (valueExpr d) es) > names f <> parens (commaSep $ map (scalarExpr d) es)
> <+> text "over" > <+> text "over"
> <+> parens ((case pb of > <+> parens ((case pb of
> [] -> empty > [] -> empty
> _ -> text "partition by" > _ -> text "partition by"
> <+> nest 13 (commaSep $ map (valueExpr d) pb)) > <+> nest 13 (commaSep $ map (scalarExpr d) pb))
> <+> orderBy d od > <+> orderBy d od
> <+> me frd fr) > <+> me frd fr)
> where > where
@ -97,73 +97,73 @@ which have been changed to try to improve the layout of the output.
> fpd UnboundedPreceding = text "unbounded preceding" > fpd UnboundedPreceding = text "unbounded preceding"
> fpd UnboundedFollowing = text "unbounded following" > fpd UnboundedFollowing = text "unbounded following"
> fpd Current = text "current row" > fpd Current = text "current row"
> fpd (Preceding e) = valueExpr d e <+> text "preceding" > fpd (Preceding e) = scalarExpr d e <+> text "preceding"
> fpd (Following e) = valueExpr d e <+> text "following" > 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"]] = > ,[Name Nothing "not between"]] =
> sep [valueExpr dia a > sep [scalarExpr dia a
> ,names nm <+> valueExpr dia b > ,names nm <+> scalarExpr dia b
> ,nest (length (unnames nm) + 1) $ text "and" <+> valueExpr dia c] > ,nest (length (unnames nm) + 1) $ text "and" <+> scalarExpr dia c]
> valueExpr d (SpecialOp [Name Nothing "rowctor"] as) = > scalarExpr d (SpecialOp [Name Nothing "rowctor"] as) =
> parens $ commaSep $ map (valueExpr d) as > parens $ commaSep $ map (scalarExpr d) as
> valueExpr d (SpecialOp nm es) = > scalarExpr d (SpecialOp nm es) =
> names nm <+> parens (commaSep $ map (valueExpr d) 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 > names nm <> parens (sep $ catMaybes
> (fmap (valueExpr d) fs > (fmap (scalarExpr d) fs
> : map (\(n,e) -> Just (text n <+> valueExpr d e)) as)) > : map (\(n,e) -> Just (text n <+> scalarExpr d e)) as))
> valueExpr d (PrefixOp f e) = names f <+> valueExpr d e > scalarExpr d (PrefixOp f e) = names f <+> scalarExpr d e
> valueExpr d (PostfixOp f e) = valueExpr d e <+> names f > scalarExpr d (PostfixOp f e) = scalarExpr d e <+> names f
> valueExpr d e@(BinOp _ op _) | op `elem` [[Name Nothing "and"] > scalarExpr d e@(BinOp _ op _) | op `elem` [[Name Nothing "and"]
> ,[Name Nothing "or"]] = > ,[Name Nothing "or"]] =
> -- special case for and, or, get all the ands so we can vcat them > -- special case for and, or, get all the ands so we can vcat them
> -- nicely > -- nicely
> case ands e of > case ands e of
> (e':es) -> vcat (valueExpr d e' > (e':es) -> vcat (scalarExpr d e'
> : map ((names op <+>) . valueExpr d) es) > : map ((names op <+>) . scalarExpr d) es)
> [] -> empty -- shouldn't be possible > [] -> empty -- shouldn't be possible
> where > where
> ands (BinOp a op' b) | op == op' = ands a ++ ands b > ands (BinOp a op' b) | op == op' = ands a ++ ands b
> ands x = [x] > ands x = [x]
> -- special case for . we don't use whitespace > -- special case for . we don't use whitespace
> valueExpr d (BinOp e0 [Name Nothing "."] e1) = > scalarExpr d (BinOp e0 [Name Nothing "."] e1) =
> valueExpr d e0 <> text "." <> valueExpr d e1 > scalarExpr d e0 <> text "." <> scalarExpr d e1
> valueExpr d (BinOp e0 f e1) = > scalarExpr d (BinOp e0 f e1) =
> valueExpr d e0 <+> names f <+> valueExpr d e1 > scalarExpr d e0 <+> names f <+> scalarExpr d e1
> valueExpr dia (Case t ws els) = > scalarExpr dia (Case t ws els) =
> sep $ [text "case" <+> me (valueExpr dia) t] > sep $ [text "case" <+> me (scalarExpr dia) t]
> ++ map w ws > ++ map w ws
> ++ maybeToList (fmap e els) > ++ maybeToList (fmap e els)
> ++ [text "end"] > ++ [text "end"]
> where > where
> w (t0,t1) = > w (t0,t1) =
> text "when" <+> nest 5 (commaSep $ map (valueExpr dia) t0) > text "when" <+> nest 5 (commaSep $ map (scalarExpr dia) t0)
> <+> text "then" <+> nest 5 (valueExpr dia t1) > <+> text "then" <+> nest 5 (scalarExpr dia t1)
> e el = text "else" <+> nest 5 (valueExpr dia el) > e el = text "else" <+> nest 5 (scalarExpr dia el)
> valueExpr d (Parens e) = parens $ valueExpr d e > scalarExpr d (Parens e) = parens $ scalarExpr d e
> valueExpr d (Cast e tn) = > scalarExpr d (Cast e tn) =
> text "cast" <> parens (sep [valueExpr d e > text "cast" <> parens (sep [scalarExpr d e
> ,text "as" > ,text "as"
> ,typeName tn]) > ,typeName tn])
> valueExpr _ (TypedLit tn s) = > scalarExpr _ (TypedLit tn s) =
> typeName tn <+> quotes (text s) > typeName tn <+> quotes (text s)
> valueExpr d (SubQueryExpr ty qe) = > scalarExpr d (SubQueryExpr ty qe) =
> (case ty of > (case ty of
> SqSq -> empty > SqSq -> empty
> SqExists -> text "exists" > SqExists -> text "exists"
> SqUnique -> text "unique" > SqUnique -> text "unique"
> ) <+> parens (queryExpr d qe) > ) <+> parens (queryExpr d qe)
> valueExpr d (QuantifiedComparison v c cp sq) = > scalarExpr d (QuantifiedComparison v c cp sq) =
> valueExpr d v > scalarExpr d v
> <+> names c > <+> names c
> <+> (text $ case cp of > <+> (text $ case cp of
> CPAny -> "any" > CPAny -> "any"
@ -171,36 +171,36 @@ which have been changed to try to improve the layout of the output.
> CPAll -> "all") > CPAll -> "all")
> <+> parens (queryExpr d sq) > <+> parens (queryExpr d sq)
> valueExpr d (Match v u sq) = > scalarExpr d (Match v u sq) =
> valueExpr d v > scalarExpr d v
> <+> text "match" > <+> text "match"
> <+> (if u then text "unique" else empty) > <+> (if u then text "unique" else empty)
> <+> parens (queryExpr d sq) > <+> parens (queryExpr d sq)
> valueExpr d (In b se x) = > scalarExpr d (In b se x) =
> valueExpr d se <+> > scalarExpr d se <+>
> (if b then empty else text "not") > (if b then empty else text "not")
> <+> text "in" > <+> text "in"
> <+> parens (nest (if b then 3 else 7) $ > <+> parens (nest (if b then 3 else 7) $
> case x of > case x of
> InList es -> commaSep $ map (valueExpr d) es > InList es -> commaSep $ map (scalarExpr d) es
> InQueryExpr qe -> queryExpr d qe) > InQueryExpr qe -> queryExpr d qe)
> valueExpr d (Array v es) = > scalarExpr d (Array v es) =
> valueExpr d v <> brackets (commaSep $ map (valueExpr d) es) > scalarExpr d v <> brackets (commaSep $ map (scalarExpr d) es)
> valueExpr d (ArrayCtor q) = > scalarExpr d (ArrayCtor q) =
> text "array" <> parens (queryExpr d q) > text "array" <> parens (queryExpr d q)
> valueExpr d (MultisetCtor es) = > scalarExpr d (MultisetCtor es) =
> text "multiset" <> brackets (commaSep $ map (valueExpr d) es) > text "multiset" <> brackets (commaSep $ map (scalarExpr d) es)
> valueExpr d (MultisetQueryCtor q) = > scalarExpr d (MultisetQueryCtor q) =
> text "multiset" <> parens (queryExpr d q) > text "multiset" <> parens (queryExpr d q)
> valueExpr d (MultisetBinOp a c q b) = > scalarExpr d (MultisetBinOp a c q b) =
> sep > sep
> [valueExpr d a > [scalarExpr d a
> ,text "multiset" > ,text "multiset"
> ,text $ case c of > ,text $ case c of
> Union -> "union" > Union -> "union"
@ -210,32 +210,32 @@ which have been changed to try to improve the layout of the output.
> SQDefault -> empty > SQDefault -> empty
> All -> text "all" > All -> text "all"
> Distinct -> text "distinct" > Distinct -> text "distinct"
> ,valueExpr d b] > ,scalarExpr d b]
> {-valueExpr d (Escape v e) = > {-scalarExpr d (Escape v e) =
> valueExpr d v <+> text "escape" <+> text [e] > scalarExpr d v <+> text "escape" <+> text [e]
> valueExpr d (UEscape v e) = > scalarExpr d (UEscape v e) =
> valueExpr d v <+> text "uescape" <+> text [e]-} > scalarExpr d v <+> text "uescape" <+> text [e]-}
> valueExpr d (Collate v c) = > scalarExpr d (Collate v c) =
> valueExpr d v <+> text "collate" <+> names c > scalarExpr d v <+> text "collate" <+> names c
> valueExpr _ (NextValueFor ns) = > scalarExpr _ (NextValueFor ns) =
> text "next value for" <+> names ns > text "next value for" <+> names ns
> valueExpr d (VEComment cmt v) = > scalarExpr d (VEComment cmt v) =
> vcat $ map comment cmt ++ [valueExpr d v] > vcat $ map comment cmt ++ [scalarExpr d v]
> valueExpr _ (OdbcLiteral t s) = > scalarExpr _ (OdbcLiteral t s) =
> text "{" <> lt t <+> quotes (text s) <> text "}" > text "{" <> lt t <+> quotes (text s) <> text "}"
> where > where
> lt OLDate = text "d" > lt OLDate = text "d"
> lt OLTime = text "t" > lt OLTime = text "t"
> lt OLTimestamp = text "ts" > lt OLTimestamp = text "ts"
> valueExpr d (OdbcFunc e) = > scalarExpr d (OdbcFunc e) =
> text "{fn" <+> valueExpr d e <> text "}" > text "{fn" <+> scalarExpr d e <> text "}"
> unname :: Name -> String > unname :: Name -> String
> unname (Name Nothing n) = n > 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" > Distinct -> text "distinct"
> ,nest 7 $ sep [selectList dia sl] > ,nest 7 $ sep [selectList dia sl]
> ,from dia fr > ,from dia fr
> ,maybeValueExpr dia "where" wh > ,maybeScalarExpr dia "where" wh
> ,grpBy dia gb > ,grpBy dia gb
> ,maybeValueExpr dia "having" hv > ,maybeScalarExpr dia "having" hv
> ,orderBy dia od > ,orderBy dia od
> ,me (\e -> text "offset" <+> valueExpr dia e <+> text "rows") off > ,me (\e -> text "offset" <+> scalarExpr dia e <+> text "rows") off
> ,fetchFirst > ,fetchFirst
> ] > ]
> where > where
> fetchFirst = > fetchFirst =
> me (\e -> if diSyntaxFlavour dia == MySQL > me (\e -> if diSyntaxFlavour dia == MySQL
> then text "limit" <+> valueExpr dia e > then text "limit" <+> scalarExpr dia e
> else text "fetch first" <+> valueExpr dia e > else text "fetch first" <+> scalarExpr dia e
> <+> text "rows only") fe > <+> text "rows only") fe
> queryExpr dia (CombineQueryExpr q1 ct d c q2) = > 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 qe]
> queryExpr d (Values vs) = > queryExpr d (Values vs) =
> text "values" > 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 _ (Table t) = text "table" <+> names t
> queryExpr d (QEComment cmt v) = > queryExpr d (QEComment cmt v) =
> vcat $ map comment cmt ++ [queryExpr d 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 > text "as" <+> name nm
> <+> me (parens . commaSep . map name) cols > <+> 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 > selectList d is = commaSep $ map si is
> where > 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 > als al = text "as" <+> name al
> from :: Dialect -> [TableRef] -> Doc > 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 (TRSimple t) = names t
> tr (TRLateral t) = text "lateral" <+> tr t > tr (TRLateral t) = text "lateral" <+> tr t
> tr (TRFunction f as) = > 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 (TRAlias t a) = sep [tr t, alias a]
> tr (TRParens t) = parens $ tr t > tr (TRParens t) = parens $ tr t
> tr (TRQueryExpr q) = parens $ queryExpr d q > 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" > JFull -> text "full"
> JCross -> text "cross" > JCross -> text "cross"
> ,text "join"] > ,text "join"]
> joinCond (Just (JoinOn e)) = text "on" <+> valueExpr d e > joinCond (Just (JoinOn e)) = text "on" <+> scalarExpr d e
> joinCond (Just (JoinUsing es)) = > joinCond (Just (JoinUsing es)) =
> text "using" <+> parens (commaSep $ map name es) > text "using" <+> parens (commaSep $ map name es)
> joinCond Nothing = empty > joinCond Nothing = empty
> maybeValueExpr :: Dialect -> String -> Maybe ValueExpr -> Doc > maybeScalarExpr :: Dialect -> String -> Maybe ScalarExpr -> Doc
> maybeValueExpr d k = me > maybeScalarExpr d k = me
> (\e -> sep [text k > (\e -> sep [text k
> ,nest (length k + 1) $ valueExpr d e]) > ,nest (length k + 1) $ scalarExpr d e])
> grpBy :: Dialect -> [GroupingExpr] -> Doc > grpBy :: Dialect -> [GroupingExpr] -> Doc
> grpBy _ [] = empty > grpBy _ [] = empty
> grpBy d gs = sep [text "group by" > grpBy d gs = sep [text "group by"
> ,nest 9 $ commaSep $ map ge gs] > ,nest 9 $ commaSep $ map ge gs]
> where > where
> ge (SimpleGroup e) = valueExpr d e > ge (SimpleGroup e) = scalarExpr d e
> ge (GroupingParens g) = parens (commaSep $ map ge g) > ge (GroupingParens g) = parens (commaSep $ map ge g)
> ge (Cube es) = text "cube" <> parens (commaSep $ map ge es) > ge (Cube es) = text "cube" <> parens (commaSep $ map ge es)
> ge (Rollup es) = text "rollup" <> 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] > ,nest 9 $ commaSep $ map f os]
> where > where
> f (SortSpec e d n) = > f (SortSpec e d n) =
> valueExpr dia e > scalarExpr dia e
> <+> (case d of > <+> (case d of
> Asc -> text "asc" > Asc -> text "asc"
> Desc -> text "desc" > 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) = > statement d (CreateDomain nm ty def cs) =
> text "create" <+> text "domain" <+> names nm > text "create" <+> text "domain" <+> names nm
> <+> typeName ty > <+> typeName ty
> <+> maybe empty (\def' -> text "default" <+> valueExpr d def') def > <+> maybe empty (\def' -> text "default" <+> scalarExpr d def') def
> <+> sep (map con cs) > <+> sep (map con cs)
> where > where
> con (cn, e) = > con (cn, e) =
> maybe empty (\cn' -> text "constraint" <+> names cn') cn > 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) = > statement d (AlterDomain nm act) =
> texts ["alter","domain"] > texts ["alter","domain"]
> <+> names nm > <+> names nm
> <+> a act > <+> a act
> where > 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 (ADDropDefault) = texts ["drop","default"]
> a (ADAddConstraint cnm e) = > a (ADAddConstraint cnm e) =
> text "add" > text "add"
> <+> maybe empty (\cnm' -> text "constraint" <+> names cnm') cnm > <+> 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"] > a (ADDropConstraint cnm) = texts ["drop", "constraint"]
> <+> names cnm > <+> names cnm
@ -504,7 +504,7 @@ which have been changed to try to improve the layout of the output.
> statement d (CreateAssertion nm ex) = > statement d (CreateAssertion nm ex) =
> texts ["create","assertion"] <+> names nm > texts ["create","assertion"] <+> names nm
> <+> text "check" <+> parens (valueExpr d ex) > <+> text "check" <+> parens (scalarExpr d ex)
> statement _ (DropAssertion nm db) = > statement _ (DropAssertion nm db) =
> text "drop" <+> text "assertion" <+> names nm <+> dropBehav 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) = > statement d (Delete t a w) =
> text "delete" <+> text "from" > text "delete" <+> text "from"
> <+> names t <+> maybe empty (\x -> text "as" <+> name x) a > <+> names t <+> maybe empty (\x -> text "as" <+> name x) a
> <+> maybeValueExpr d "where" w > <+> maybeScalarExpr d "where" w
> statement _ (Truncate t ir) = > statement _ (Truncate t ir) =
> text "truncate" <+> text "table" <+> names t > 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 > text "update" <+> names t
> <+> maybe empty (\x -> text "as" <+> name x) a > <+> maybe empty (\x -> text "as" <+> name x) a
> <+> text "set" <+> commaSep (map sc sts) > <+> text "set" <+> commaSep (map sc sts)
> <+> maybeValueExpr d "where" whr > <+> maybeScalarExpr d "where" whr
> where > 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 "=" > 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) = > statement _ (DropTable n b) =
> text "drop" <+> text "table" <+> names n <+> dropBehav 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 > <+> case mdef of
> Nothing -> empty > Nothing -> empty
> Just (DefaultClause def) -> > Just (DefaultClause def) ->
> text "default" <+> valueExpr d def > text "default" <+> scalarExpr d def
> Just (GenerationClause e) -> > Just (GenerationClause e) ->
> texts ["generated","always","as"] <+> parens (valueExpr d e) > texts ["generated","always","as"] <+> parens (scalarExpr d e)
> Just (IdentityColumnSpec w o) -> > Just (IdentityColumnSpec w o) ->
> text "generated" > text "generated"
> <+> (case w of > <+> (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 ColNotNullConstraint = texts ["not","null"]
> pcon ColUniqueConstraint = text "unique" > pcon ColUniqueConstraint = text "unique"
> pcon ColPrimaryKeyConstraint = texts ["primary","key"] > 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) = > pcon (ColReferencesConstraint tb c m u del) =
> text "references" > text "references"
> <+> names tb > <+> names tb
@ -709,7 +709,7 @@ which have been changed to try to improve the layout of the output.
> alterTableAction d (AlterColumnSetDefault n v) = > alterTableAction d (AlterColumnSetDefault n v) =
> texts ["alter", "column"] > texts ["alter", "column"]
> <+> name n > <+> name n
> <+> texts ["set","default"] <+> valueExpr d v > <+> texts ["set","default"] <+> scalarExpr d v
> alterTableAction _ (AlterColumnDropDefault n) = > alterTableAction _ (AlterColumnDropDefault n) =
> texts ["alter", "column"] > texts ["alter", "column"]
> <+> name n > <+> name n
@ -761,7 +761,7 @@ which have been changed to try to improve the layout of the output.
> <+> refMatch m > <+> refMatch m
> <+> refAct "update" u > <+> refAct "update" u
> <+> refAct "delete" del > <+> 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 > privAct :: PrivilegeAction -> Doc

View file

@ -2,8 +2,8 @@
> -- | The AST for SQL. > -- | The AST for SQL.
> {-# LANGUAGE DeriveDataTypeable #-} > {-# LANGUAGE DeriveDataTypeable #-}
> module Language.SQL.SimpleSQL.Syntax > module Language.SQL.SimpleSQL.Syntax
> (-- * Value expressions > (-- * Scalar expressions
> ValueExpr(..) > ScalarExpr(..)
> ,Name(..) > ,Name(..)
> ,TypeName(..) > ,TypeName(..)
> ,IntervalTypeField(..) > ,IntervalTypeField(..)
@ -73,7 +73,7 @@
> -- | Represents a value expression. This is used for the expressions > -- | Represents a value expression. This is used for the expressions
> -- in select lists. It is also used for expressions in where, group > -- in select lists. It is also used for expressions in where, group
> -- by, having, order by and so on. > -- by, having, order by and so on.
> data ValueExpr > data ScalarExpr
> = -- | a numeric literal optional decimal point, e+- > = -- | a numeric literal optional decimal point, e+-
> -- integral exponent, e.g > -- integral exponent, e.g
> -- > --
@ -121,21 +121,21 @@
> -- | Infix binary operators. This is used for symbol operators > -- | Infix binary operators. This is used for symbol operators
> -- (a + b), keyword operators (a and b) and multiple keyword > -- (a + b), keyword operators (a and b) and multiple keyword
> -- operators (a is similar to b) > -- operators (a is similar to b)
> | BinOp ValueExpr [Name] ValueExpr > | BinOp ScalarExpr [Name] ScalarExpr
> -- | Prefix unary operators. This is used for symbol > -- | Prefix unary operators. This is used for symbol
> -- operators, keyword operators and multiple keyword operators. > -- operators, keyword operators and multiple keyword operators.
> | PrefixOp [Name] ValueExpr > | PrefixOp [Name] ScalarExpr
> -- | Postfix unary operators. This is used for symbol > -- | Postfix unary operators. This is used for symbol
> -- operators, keyword operators and multiple keyword operators. > -- operators, keyword operators and multiple keyword operators.
> | PostfixOp [Name] ValueExpr > | PostfixOp [Name] ScalarExpr
> -- | Used for ternary, mixfix and other non orthodox > -- | Used for ternary, mixfix and other non orthodox
> -- operators. Currently used for row constructors, and for > -- operators. Currently used for row constructors, and for
> -- between. > -- between.
> | SpecialOp [Name] [ValueExpr] > | SpecialOp [Name] [ScalarExpr]
> -- | function application (anything that looks like c style > -- | function application (anything that looks like c style
> -- function application syntactically) > -- function application syntactically)
> | App [Name] [ValueExpr] > | App [Name] [ScalarExpr]
> -- | aggregate application, which adds distinct or all, and > -- | aggregate application, which adds distinct or all, and
@ -143,14 +143,14 @@
> | AggregateApp > | AggregateApp
> {aggName :: [Name] -- ^ aggregate function name > {aggName :: [Name] -- ^ aggregate function name
> ,aggDistinct :: SetQuantifier -- ^ distinct > ,aggDistinct :: SetQuantifier -- ^ distinct
> ,aggArgs :: [ValueExpr]-- ^ args > ,aggArgs :: [ScalarExpr]-- ^ args
> ,aggOrderBy :: [SortSpec] -- ^ order by > ,aggOrderBy :: [SortSpec] -- ^ order by
> ,aggFilter :: Maybe ValueExpr -- ^ filter > ,aggFilter :: Maybe ScalarExpr -- ^ filter
> } > }
> -- | aggregates with within group > -- | aggregates with within group
> | AggregateAppGroup > | AggregateAppGroup
> {aggName :: [Name] -- ^ aggregate function name > {aggName :: [Name] -- ^ aggregate function name
> ,aggArgs :: [ValueExpr] -- ^ args > ,aggArgs :: [ScalarExpr] -- ^ args
> ,aggGroup :: [SortSpec] -- ^ within group > ,aggGroup :: [SortSpec] -- ^ within group
> } > }
> -- | window application, which adds over (partition by a order > -- | window application, which adds over (partition by a order
@ -158,8 +158,8 @@
> -- not currently supported > -- not currently supported
> | WindowApp > | WindowApp
> {wnName :: [Name] -- ^ window function name > {wnName :: [Name] -- ^ window function name
> ,wnArgs :: [ValueExpr] -- ^ args > ,wnArgs :: [ScalarExpr] -- ^ args
> ,wnPartition :: [ValueExpr] -- ^ partition by > ,wnPartition :: [ScalarExpr] -- ^ partition by
> ,wnOrderBy :: [SortSpec] -- ^ order by > ,wnOrderBy :: [SortSpec] -- ^ order by
> ,wnFrame :: Maybe Frame -- ^ frame clause > ,wnFrame :: Maybe Frame -- ^ frame clause
> } > }
@ -169,56 +169,56 @@
> -- of commas. The maybe is for the first unnamed argument > -- of commas. The maybe is for the first unnamed argument
> -- if it is present, and the list is for the keyword argument > -- if it is present, and the list is for the keyword argument
> -- pairs. > -- pairs.
> | SpecialOpK [Name] (Maybe ValueExpr) [(String,ValueExpr)] > | SpecialOpK [Name] (Maybe ScalarExpr) [(String,ScalarExpr)]
> -- | cast(a as typename) > -- | cast(a as typename)
> | Cast ValueExpr TypeName > | Cast ScalarExpr TypeName
> -- | case expression. both flavours supported > -- | case expression. both flavours supported
> | Case > | Case
> {caseTest :: Maybe ValueExpr -- ^ test value > {caseTest :: Maybe ScalarExpr -- ^ test value
> ,caseWhens :: [([ValueExpr],ValueExpr)] -- ^ when branches > ,caseWhens :: [([ScalarExpr],ScalarExpr)] -- ^ when branches
> ,caseElse :: Maybe ValueExpr -- ^ else value > ,caseElse :: Maybe ScalarExpr -- ^ else value
> } > }
> | Parens ValueExpr > | Parens ScalarExpr
> -- | in list literal and in subquery, if the bool is false it > -- | in list literal and in subquery, if the bool is false it
> -- means not in was used ('a not in (1,2)') > -- means not in was used ('a not in (1,2)')
> | In Bool ValueExpr InPredValue > | In Bool ScalarExpr InPredValue
> -- | exists, all, any, some subqueries > -- | exists, all, any, some subqueries
> | SubQueryExpr SubQueryExprType QueryExpr > | SubQueryExpr SubQueryExprType QueryExpr
> | QuantifiedComparison > | QuantifiedComparison
> ValueExpr > ScalarExpr
> [Name] -- operator > [Name] -- operator
> CompPredQuantifier > CompPredQuantifier
> QueryExpr > QueryExpr
> | Match ValueExpr Bool -- true if unique > | Match ScalarExpr Bool -- true if unique
> QueryExpr > QueryExpr
> | Array ValueExpr [ValueExpr] -- ^ represents an array > | Array ScalarExpr [ScalarExpr] -- ^ represents an array
> -- access expression, or an array ctor > -- access expression, or an array ctor
> -- e.g. a[3]. The first > -- e.g. a[3]. The first
> -- valueExpr is the array, the > -- scalarExpr is the array, the
> -- second is the subscripts/ctor args > -- 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) > | 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 todo: special syntax for like, similar with escape - escape cannot go
in other places in other places
> -- | Escape ValueExpr Char > -- | Escape ScalarExpr Char
> -- | UEscape ValueExpr Char > -- | UEscape ScalarExpr Char
> | Collate ValueExpr [Name] > | Collate ScalarExpr [Name]
> | MultisetBinOp ValueExpr CombineOp SetQuantifier ValueExpr > | MultisetBinOp ScalarExpr CombineOp SetQuantifier ScalarExpr
> | MultisetCtor [ValueExpr] > | MultisetCtor [ScalarExpr]
> | MultisetQueryCtor QueryExpr > | MultisetQueryCtor QueryExpr
> | NextValueFor [Name] > | NextValueFor [Name]
> | VEComment [Comment] ValueExpr > | VEComment [Comment] ScalarExpr
> | OdbcLiteral OdbcLiteralType String > | OdbcLiteral OdbcLiteralType String
> -- ^ an odbc literal e.g. {d '2000-01-01'} > -- ^ an odbc literal e.g. {d '2000-01-01'}
> | OdbcFunc ValueExpr > | OdbcFunc ScalarExpr
> -- ^ an odbc function call e.g. {fn CHARACTER_LENGTH('test')} > -- ^ an odbc function call e.g. {fn CHARACTER_LENGTH('test')}
> deriving (Eq,Show,Read,Data,Typeable) > deriving (Eq,Show,Read,Data,Typeable)
@ -256,15 +256,15 @@ in other places
> | PrecOctets > | PrecOctets
> deriving (Eq,Show,Read,Data,Typeable) > 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. > -- (subquery)' syntax.
> data InPredValue = InList [ValueExpr] > data InPredValue = InList [ScalarExpr]
> | InQueryExpr QueryExpr > | InQueryExpr QueryExpr
> deriving (Eq,Show,Read,Data,Typeable) > deriving (Eq,Show,Read,Data,Typeable)
not sure if scalar subquery, exists and unique should be represented like this 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 > data SubQueryExprType
> = -- | exists (query expr) > = -- | exists (query expr)
> SqExists > SqExists
@ -281,7 +281,7 @@ not sure if scalar subquery, exists and unique should be represented like this
> deriving (Eq,Show,Read,Data,Typeable) > deriving (Eq,Show,Read,Data,Typeable)
> -- | Represents one field in an order by list. > -- | 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) > deriving (Eq,Show,Read,Data,Typeable)
> -- | Represents 'nulls first' or 'nulls last' in an order by clause. > -- | 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 > -- | represents the start or end of a frame
> data FramePos = UnboundedPreceding > data FramePos = UnboundedPreceding
> | Preceding ValueExpr > | Preceding ScalarExpr
> | Current > | Current
> | Following ValueExpr > | Following ScalarExpr
> | UnboundedFollowing > | UnboundedFollowing
> deriving (Eq,Show,Read,Data,Typeable) > 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 > data QueryExpr
> = Select > = Select
> {qeSetQuantifier :: SetQuantifier > {qeSetQuantifier :: SetQuantifier
> ,qeSelectList :: [(ValueExpr,Maybe Name)] > ,qeSelectList :: [(ScalarExpr,Maybe Name)]
> -- ^ the expressions and the column aliases > -- ^ the expressions and the column aliases
TODO: consider breaking this up. The SQL grammar has 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? This would make some things a bit cleaner?
> ,qeFrom :: [TableRef] > ,qeFrom :: [TableRef]
> ,qeWhere :: Maybe ValueExpr > ,qeWhere :: Maybe ScalarExpr
> ,qeGroupBy :: [GroupingExpr] > ,qeGroupBy :: [GroupingExpr]
> ,qeHaving :: Maybe ValueExpr > ,qeHaving :: Maybe ScalarExpr
> ,qeOrderBy :: [SortSpec] > ,qeOrderBy :: [SortSpec]
> ,qeOffset :: Maybe ValueExpr > ,qeOffset :: Maybe ScalarExpr
> ,qeFetchFirst :: Maybe ValueExpr > ,qeFetchFirst :: Maybe ScalarExpr
> } > }
> | CombineQueryExpr > | CombineQueryExpr
> {qe0 :: QueryExpr > {qe0 :: QueryExpr
@ -360,7 +360,7 @@ This would make some things a bit cleaner?
> {qeWithRecursive :: Bool > {qeWithRecursive :: Bool
> ,qeViews :: [(Alias,QueryExpr)] > ,qeViews :: [(Alias,QueryExpr)]
> ,qeQueryExpression :: QueryExpr} > ,qeQueryExpression :: QueryExpr}
> | Values [[ValueExpr]] > | Values [[ScalarExpr]]
> | Table [Name] > | Table [Name]
> | QEComment [Comment] QueryExpr > | QEComment [Comment] QueryExpr
> deriving (Eq,Show,Read,Data,Typeable) > deriving (Eq,Show,Read,Data,Typeable)
@ -412,7 +412,7 @@ I'm not sure if this is valid syntax or not.
> | Cube [GroupingExpr] > | Cube [GroupingExpr]
> | Rollup [GroupingExpr] > | Rollup [GroupingExpr]
> | GroupingSets [GroupingExpr] > | GroupingSets [GroupingExpr]
> | SimpleGroup ValueExpr > | SimpleGroup ScalarExpr
> deriving (Eq,Show,Read,Data,Typeable) > deriving (Eq,Show,Read,Data,Typeable)
> -- | Represents a entry in the csv of tables in the from clause. > -- | 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) > -- | from (query expr)
> | TRQueryExpr QueryExpr > | TRQueryExpr QueryExpr
> -- | from function(args) > -- | from function(args)
> | TRFunction [Name] [ValueExpr] > | TRFunction [Name] [ScalarExpr]
> -- | from lateral t > -- | from lateral t
> | TRLateral TableRef > | TRLateral TableRef
> -- | ODBC {oj t1 left outer join t2 on expr} syntax > -- | 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) > deriving (Eq,Show,Read,Data,Typeable)
> -- | The join condition. > -- | The join condition.
> data JoinCondition = JoinOn ValueExpr -- ^ on expr > data JoinCondition = JoinOn ScalarExpr -- ^ on expr
> | JoinUsing [Name] -- ^ using (column list) > | JoinUsing [Name] -- ^ using (column list)
> deriving (Eq,Show,Read,Data,Typeable) > 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]) > | CreateView Bool [Name] (Maybe [Name])
> QueryExpr (Maybe CheckOption) > QueryExpr (Maybe CheckOption)
> | DropView [Name] DropBehaviour > | DropView [Name] DropBehaviour
> | CreateDomain [Name] TypeName (Maybe ValueExpr) > | CreateDomain [Name] TypeName (Maybe ScalarExpr)
> [(Maybe [Name], ValueExpr)] > [(Maybe [Name], ScalarExpr)]
> | AlterDomain [Name] AlterDomainAction > | AlterDomain [Name] AlterDomainAction
> | DropDomain [Name] DropBehaviour > | DropDomain [Name] DropBehaviour
@ -475,7 +475,7 @@ I'm not sure if this is valid syntax or not.
> | DropCollation > | DropCollation
> | CreateTranslation > | CreateTranslation
> | DropTranslation -} > | DropTranslation -}
> | CreateAssertion [Name] ValueExpr > | CreateAssertion [Name] ScalarExpr
> | DropAssertion [Name] DropBehaviour > | DropAssertion [Name] DropBehaviour
> {- | CreateTrigger > {- | CreateTrigger
> | DropTrigger > | DropTrigger
@ -499,11 +499,11 @@ I'm not sure if this is valid syntax or not.
> | CloseCursor > | CloseCursor
> | SelectInto -} > | SelectInto -}
> -- | DeletePositioned > -- | DeletePositioned
> | Delete [Name] (Maybe Name) (Maybe ValueExpr) > | Delete [Name] (Maybe Name) (Maybe ScalarExpr)
> | Truncate [Name] IdentityRestart > | Truncate [Name] IdentityRestart
> | Insert [Name] (Maybe [Name]) InsertSource > | Insert [Name] (Maybe [Name]) InsertSource
> -- | Merge > -- | Merge
> | Update [Name] (Maybe Name) [SetClause] (Maybe ValueExpr) > | Update [Name] (Maybe Name) [SetClause] (Maybe ScalarExpr)
> {- | TemporaryTable > {- | TemporaryTable
> | FreeLocator > | FreeLocator
> | HoldLocator -} > | HoldLocator -}
@ -553,8 +553,8 @@ I'm not sure if this is valid syntax or not.
> deriving (Eq,Show,Read,Data,Typeable) > deriving (Eq,Show,Read,Data,Typeable)
> data SetClause = > data SetClause =
> Set [Name] ValueExpr > Set [Name] ScalarExpr
> | SetMultiple [[Name]] [ValueExpr] > | SetMultiple [[Name]] [ScalarExpr]
> deriving (Eq,Show,Read,Data,Typeable) > deriving (Eq,Show,Read,Data,Typeable)
> data TableElement = > data TableElement =
@ -581,7 +581,7 @@ I'm not sure if this is valid syntax or not.
> ReferenceMatch > ReferenceMatch
> ReferentialAction > ReferentialAction
> ReferentialAction > ReferentialAction
> | ColCheckConstraint ValueExpr > | ColCheckConstraint ScalarExpr
> deriving (Eq,Show,Read,Data,Typeable) > deriving (Eq,Show,Read,Data,Typeable)
> data TableConstraint = > data TableConstraint =
@ -591,7 +591,7 @@ I'm not sure if this is valid syntax or not.
> ReferenceMatch > ReferenceMatch
> ReferentialAction > ReferentialAction
> ReferentialAction > ReferentialAction
> | TableCheckConstraint ValueExpr > | TableCheckConstraint ScalarExpr
> deriving (Eq,Show,Read,Data,Typeable) > deriving (Eq,Show,Read,Data,Typeable)
@ -613,7 +613,7 @@ I'm not sure if this is valid syntax or not.
> data AlterTableAction = > data AlterTableAction =
> AddColumnDef ColumnDef > AddColumnDef ColumnDef
> | AlterColumnSetDefault Name ValueExpr > | AlterColumnSetDefault Name ScalarExpr
> | AlterColumnDropDefault Name > | AlterColumnDropDefault Name
> | AlterColumnSetNotNull Name > | AlterColumnSetNotNull Name
> | AlterColumnDropNotNull Name > | AlterColumnDropNotNull Name
@ -656,9 +656,9 @@ I'm not sure if this is valid syntax or not.
> deriving (Eq,Show,Read,Data,Typeable) -} > deriving (Eq,Show,Read,Data,Typeable) -}
> data DefaultClause = > data DefaultClause =
> DefaultClause ValueExpr > DefaultClause ScalarExpr
> | IdentityColumnSpec IdentityWhen [SequenceGeneratorOption] > | IdentityColumnSpec IdentityWhen [SequenceGeneratorOption]
> | GenerationClause ValueExpr > | GenerationClause ScalarExpr
> deriving (Eq,Show,Read,Data,Typeable) > deriving (Eq,Show,Read,Data,Typeable)
> data IdentityWhen = > data IdentityWhen =
@ -686,9 +686,9 @@ I'm not sure if this is valid syntax or not.
> deriving (Eq,Show,Read,Data,Typeable) > deriving (Eq,Show,Read,Data,Typeable)
> data AlterDomainAction = > data AlterDomainAction =
> ADSetDefault ValueExpr > ADSetDefault ScalarExpr
> | ADDropDefault > | ADDropDefault
> | ADAddConstraint (Maybe [Name]) ValueExpr > | ADAddConstraint (Maybe [Name]) ScalarExpr
> | ADDropConstraint [Name] > | ADDropConstraint [Name]
> deriving (Eq,Show,Read,Data,Typeable) > deriving (Eq,Show,Read,Data,Typeable)

17
TODO
View file

@ -1,21 +1,24 @@
medium tasks next release 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 rename combinequeryexpr
add comment to statements? add comment to statements?
review simple enums to make sure they have default review simple enums to make sure they have default
use enum in sign in interval literal 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 / work on better dialect design: more basic customizability and rule /
callback driven callback driven
review/fix documentation and website review/fix documentation and website
fix the groups for generated tests fix the groups for generated tests
check the .cabal file module lists
medium tasks next release + 1 medium tasks next release + 1
add annotation add annotation
@ -87,7 +90,7 @@ compare every so often to catch regressions and approve improvements
start with tpch, and then add some others start with tpch, and then add some others
same with invalid statements to see the error messages 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) stuff (either tokens, whitespace or junk strings)
semi-systematically added and/or removed semi-systematically added and/or removed

View file

@ -30,6 +30,8 @@
fix parsing of functions whose name is a keyword (e.g. abs) fix parsing of functions whose name is a keyword (e.g. abs)
add basic support for parsing odbc syntax ({d 'literals'} {fn add basic support for parsing odbc syntax ({d 'literals'} {fn
app(something)} and {oj t1 left outer join ... } app(something)} and {oj t1 left outer join ... }
rename ValueExpr -> ScalarExpr (I think scalar expression is
slightly less incorrect)
0.4.1 (commit c156c5c34e91e1f7ef449d2c1ea14e282104fd90) 0.4.1 (commit c156c5c34e91e1f7ef449d2c1ea14e282104fd90)
tested with ghc 7.4.2, 7.6.3, 7.8.4,7.10.0.20150123 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 simple demonstration of how dialects could be handled internally

View file

@ -83,7 +83,7 @@ Test-Suite Tests
Language.SQL.SimpleSQL.TestTypes, Language.SQL.SimpleSQL.TestTypes,
Language.SQL.SimpleSQL.Tests, Language.SQL.SimpleSQL.Tests,
Language.SQL.SimpleSQL.Tpch, Language.SQL.SimpleSQL.Tpch,
Language.SQL.SimpleSQL.ValueExprs, Language.SQL.SimpleSQL.ScalarExprs,
Language.SQL.SimpleSQL.LexerTests Language.SQL.SimpleSQL.LexerTests
other-extensions: TupleSections,DeriveDataTypeable other-extensions: TupleSections,DeriveDataTypeable

View file

@ -18,10 +18,10 @@ limit syntax
[LIMIT {[offset,] row_count | row_count OFFSET offset}] [LIMIT {[offset,] row_count | row_count OFFSET offset}]
> backtickQuotes :: TestItem > backtickQuotes :: TestItem
> backtickQuotes = Group "backtickQuotes" (map (uncurry (TestValueExpr mysql)) > backtickQuotes = Group "backtickQuotes" (map (uncurry (TestScalarExpr mysql))
> [("`test`", Iden [Name (Just ("`","`")) "test"]) > [("`test`", Iden [Name (Just ("`","`")) "test"])
> ] > ]
> ++ [ParseValueExprFails ansi2011 "`test`"] > ++ [ParseScalarExprFails ansi2011 "`test`"]
> ) > )
> limit :: TestItem > limit :: TestItem

View file

@ -45,7 +45,7 @@
> ,qeFrom = [TRSimple [Name Nothing "t"]]}] > ,qeFrom = [TRSimple [Name Nothing "t"]]}]
> ] > ]
> where > where
> e = TestValueExpr ansi2011 {allowOdbc = True} > e = TestScalarExpr ansi2011 {allowOdbc = True}
> --tsql = ParseProcSql defaultParseFlags {pfDialect=sqlServerDialect} > --tsql = ParseProcSql defaultParseFlags {pfDialect=sqlServerDialect}
> ap n = App [Name Nothing n] > ap n = App [Name Nothing n]
> iden n = Iden [Name Nothing n] > iden n = Iden [Name Nothing n]

View file

@ -504,7 +504,7 @@ Specify a non-null value.
> characterStringLiterals :: TestItem > characterStringLiterals :: TestItem
> characterStringLiterals = Group "character string literals" > characterStringLiterals = Group "character string literals"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [("'a regular string literal'" > [("'a regular string literal'"
> ,StringLit "'" "'" "a regular string literal") > ,StringLit "'" "'" "a regular string literal")
> ,("'something' ' some more' 'and more'" > ,("'something' ' some more' 'and more'"
@ -532,7 +532,7 @@ character set allows them.
> nationalCharacterStringLiterals :: TestItem > nationalCharacterStringLiterals :: TestItem
> nationalCharacterStringLiterals = Group "national character string literals" > nationalCharacterStringLiterals = Group "national character string literals"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [("N'something'", StringLit "N'" "'" "something") > [("N'something'", StringLit "N'" "'" "something")
> ,("n'something'", StringLit "n'" "'" "something") > ,("n'something'", StringLit "n'" "'" "something")
> ] > ]
@ -549,7 +549,7 @@ character set allows them.
> unicodeCharacterStringLiterals :: TestItem > unicodeCharacterStringLiterals :: TestItem
> unicodeCharacterStringLiterals = Group "unicode character string literals" > unicodeCharacterStringLiterals = Group "unicode character string literals"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [("U&'something'", StringLit "U&'" "'" "something") > [("U&'something'", StringLit "U&'" "'" "something")
> {-,("u&'something' escape =" > {-,("u&'something' escape ="
> ,Escape (StringLit "u&'" "'" "something") '=') > ,Escape (StringLit "u&'" "'" "something") '=')
@ -568,7 +568,7 @@ TODO: unicode escape
> binaryStringLiterals :: TestItem > binaryStringLiterals :: TestItem
> binaryStringLiterals = Group "binary string literals" > binaryStringLiterals = Group "binary string literals"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [--("B'101010'", CSStringLit "B" "101010") > [--("B'101010'", CSStringLit "B" "101010")
> ("X'7f7f7f'", StringLit "X'" "'" "7f7f7f") > ("X'7f7f7f'", StringLit "X'" "'" "7f7f7f")
> --,("X'7f7f7f' escape z", Escape (StringLit "X'" "'" "7f7f7f") 'z') > --,("X'7f7f7f' escape z", Escape (StringLit "X'" "'" "7f7f7f") 'z')
@ -598,7 +598,7 @@ TODO: unicode escape
> numericLiterals :: TestItem > numericLiterals :: TestItem
> numericLiterals = Group "numeric literals" > numericLiterals = Group "numeric literals"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [("11", NumLit "11") > [("11", NumLit "11")
> ,("11.11", NumLit "11.11") > ,("11.11", NumLit "11.11")
@ -704,7 +704,7 @@ TODO: unicode escape
> intervalLiterals :: TestItem > intervalLiterals :: TestItem
> intervalLiterals = Group "intervalLiterals literals" > intervalLiterals = Group "intervalLiterals literals"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [("interval '1'", TypedLit (TypeName [Name Nothing "interval"]) "1") > [("interval '1'", TypedLit (TypeName [Name Nothing "interval"]) "1")
> ,("interval '1' day" > ,("interval '1' day"
> ,IntervalLit Nothing "1" (Itf "day" Nothing) Nothing) > ,IntervalLit Nothing "1" (Itf "day" Nothing) Nothing)
@ -727,7 +727,7 @@ TODO: unicode escape
> booleanLiterals :: TestItem > booleanLiterals :: TestItem
> booleanLiterals = Group "boolean literals" > booleanLiterals = Group "boolean literals"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [("true", Iden [Name Nothing "true"]) > [("true", Iden [Name Nothing "true"])
> ,("false", Iden [Name Nothing "false"]) > ,("false", Iden [Name Nothing "false"])
> ,("unknown", Iden [Name Nothing "unknown"]) > ,("unknown", Iden [Name Nothing "unknown"])
@ -747,7 +747,7 @@ Specify names.
> identifiers :: TestItem > identifiers :: TestItem
> identifiers = Group "identifiers" > identifiers = Group "identifiers"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [("test",Iden [Name Nothing "test"]) > [("test",Iden [Name Nothing "test"])
> ,("_test",Iden [Name Nothing "_test"]) > ,("_test",Iden [Name Nothing "_test"])
> ,("t1",Iden [Name Nothing "t1"]) > ,("t1",Iden [Name Nothing "t1"])
@ -1188,11 +1188,11 @@ expression
> typeNameTests :: TestItem > typeNameTests :: TestItem
> typeNameTests = Group "type names" > typeNameTests = Group "type names"
> [Group "type names" $ map (uncurry (TestValueExpr ansi2011)) > [Group "type names" $ map (uncurry (TestScalarExpr ansi2011))
> $ concatMap makeSimpleTests $ fst typeNames > $ concatMap makeSimpleTests $ fst typeNames
> ,Group "generated casts" $ map (uncurry (TestValueExpr ansi2011)) > ,Group "generated casts" $ map (uncurry (TestScalarExpr ansi2011))
> $ concatMap makeCastTests $ fst typeNames > $ concatMap makeCastTests $ fst typeNames
> ,Group "generated typename" $ map (uncurry (TestValueExpr ansi2011)) > ,Group "generated typename" $ map (uncurry (TestScalarExpr ansi2011))
> $ concatMap makeTests $ snd typeNames] > $ concatMap makeTests $ snd typeNames]
> where > where
> makeSimpleTests (ctn, stn) = > makeSimpleTests (ctn, stn) =
@ -1213,7 +1213,7 @@ Define a field of a row type.
> fieldDefinition :: TestItem > fieldDefinition :: TestItem
> fieldDefinition = Group "field definition" > fieldDefinition = Group "field definition"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [("cast('(1,2)' as row(a int,b char))" > [("cast('(1,2)' as row(a int,b char))"
> ,Cast (StringLit "'" "'" "(1,2)") > ,Cast (StringLit "'" "'" "(1,2)")
> $ RowTypeName [(Name Nothing "a", TypeName [Name Nothing "int"]) > $ RowTypeName [(Name Nothing "a", TypeName [Name Nothing "int"])
@ -1269,31 +1269,31 @@ Specify a value that is syntactically self-delimited.
> ,nestedWindowFunction > ,nestedWindowFunction
> ,caseExpression > ,caseExpression
> ,castSpecification > ,castSpecification
> ,nextValueExpression > ,nextScalarExpression
> ,fieldReference > ,fieldReference
> ,arrayElementReference > ,arrayElementReference
> ,multisetElementReference > ,multisetElementReference
> ,numericValueExpression > ,numericScalarExpression
> ,numericValueFunction > ,numericValueFunction
> ,stringValueExpression > ,stringScalarExpression
> ,stringValueFunction > ,stringValueFunction
> ,datetimeValueExpression > ,datetimeScalarExpression
> ,datetimeValueFunction > ,datetimeValueFunction
> ,intervalValueExpression > ,intervalScalarExpression
> ,intervalValueFunction > ,intervalValueFunction
> ,booleanValueExpression > ,booleanScalarExpression
> ,arrayValueExpression > ,arrayScalarExpression
> ,arrayValueFunction > ,arrayValueFunction
> ,arrayValueConstructor > ,arrayValueConstructor
> ,multisetValueExpression > ,multisetScalarExpression
> ,multisetValueFunction > ,multisetValueFunction
> ,multisetValueConstructor > ,multisetValueConstructor
> ,parenthesizedValueExpression > ,parenthesizedScalarExpression
> ] > ]
> parenthesizedValueExpression :: TestItem > parenthesizedScalarExpression :: TestItem
> parenthesizedValueExpression = Group "parenthesized value expression" > parenthesizedScalarExpression = Group "parenthesized value expression"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [("(3)", Parens (NumLit "3")) > [("(3)", Parens (NumLit "3"))
> ,("((3))", Parens $ 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 :: TestItem
> generalValueSpecification = Group "general value specification" > generalValueSpecification = Group "general value specification"
> $ map (uncurry (TestValueExpr ansi2011)) $ > $ map (uncurry (TestScalarExpr ansi2011)) $
> map mkIden ["CURRENT_DEFAULT_TRANSFORM_GROUP" > map mkIden ["CURRENT_DEFAULT_TRANSFORM_GROUP"
> ,"CURRENT_PATH" > ,"CURRENT_PATH"
> ,"CURRENT_ROLE" > ,"CURRENT_ROLE"
@ -1383,7 +1383,7 @@ TODO: add the missing bits
> parameterSpecification :: TestItem > parameterSpecification :: TestItem
> parameterSpecification = Group "parameter specification" > parameterSpecification = Group "parameter specification"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [(":hostparam", HostParameter ":hostparam" Nothing) > [(":hostparam", HostParameter ":hostparam" Nothing)
> ,(":hostparam indicator :another_host_param" > ,(":hostparam indicator :another_host_param"
> ,HostParameter ":hostparam" $ Just ":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 :: TestItem
> contextuallyTypedValueSpecification = > contextuallyTypedValueSpecification =
> Group "contextually typed value specification" > Group "contextually typed value specification"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [("null", Iden [Name Nothing "null"]) > [("null", Iden [Name Nothing "null"])
> ,("array[]", Array (Iden [Name Nothing "array"]) []) > ,("array[]", Array (Iden [Name Nothing "array"]) [])
> ,("multiset[]", MultisetCtor []) > ,("multiset[]", MultisetCtor [])
@ -1438,7 +1438,7 @@ Disambiguate a <period>-separated chain of identifiers.
> identifierChain :: TestItem > identifierChain :: TestItem
> identifierChain = Group "identifier chain" > identifierChain = Group "identifier chain"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [("a.b", Iden [Name Nothing "a",Name Nothing "b"])] > [("a.b", Iden [Name Nothing "a",Name Nothing "b"])]
== 6.7 <column reference> == 6.7 <column reference>
@ -1452,7 +1452,7 @@ Reference a column.
> columnReference :: TestItem > columnReference :: TestItem
> columnReference = Group "column reference" > 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"])] > [("module.a.b", Iden [Name Nothing "module",Name Nothing "a",Name Nothing "b"])]
== 6.8 <SQL parameter reference> == 6.8 <SQL parameter reference>
@ -1676,7 +1676,7 @@ Specify a data conversion.
> castSpecification :: TestItem > castSpecification :: TestItem
> castSpecification = Group "cast specification" > castSpecification = Group "cast specification"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [("cast(a as int)" > [("cast(a as int)"
> ,Cast (Iden [Name Nothing "a"]) (TypeName [Name Nothing "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> <next value expression> ::= NEXT VALUE FOR <sequence generator name>
> nextValueExpression :: TestItem > nextScalarExpression :: TestItem
> nextValueExpression = Group "next value expression" > nextScalarExpression = Group "next value expression"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [("next value for a.b", NextValueFor [Name Nothing "a", Name Nothing "b"]) > [("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 :: TestItem
> fieldReference = Group "field reference" > fieldReference = Group "field reference"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [("f(something).a" > [("f(something).a"
> ,BinOp (App [Name Nothing "f"] [Iden [Name Nothing "something"]]) > ,BinOp (App [Name Nothing "f"] [Iden [Name Nothing "something"]])
> [Name Nothing "."] > [Name Nothing "."]
@ -1827,7 +1827,7 @@ Return an element of an array.
> arrayElementReference :: TestItem > arrayElementReference :: TestItem
> arrayElementReference = Group "array element reference" > arrayElementReference = Group "array element reference"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [("something[3]" > [("something[3]"
> ,Array (Iden [Name Nothing "something"]) [NumLit "3"]) > ,Array (Iden [Name Nothing "something"]) [NumLit "3"])
> ,("(something(a))[x]" > ,("(something(a))[x]"
@ -1850,7 +1850,7 @@ Return the sole element of a multiset of one element.
> multisetElementReference :: TestItem > multisetElementReference :: TestItem
> multisetElementReference = Group "multisetElementReference" > multisetElementReference = Group "multisetElementReference"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [("element(something)" > [("element(something)"
> ,App [Name Nothing "element"] [Iden [Name Nothing "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> <numeric primary> ::= <value expression primary> | <numeric value function>
> numericValueExpression :: TestItem > numericScalarExpression :: TestItem
> numericValueExpression = Group "numeric value expression" > numericScalarExpression = Group "numeric value expression"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [("a + b", binOp "+") > [("a + b", binOp "+")
> ,("a - b", binOp "-") > ,("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 concatenation> ::=
<binary value expression> <concatenation operator> <binary factor> <binary value expression> <concatenation operator> <binary factor>
> stringValueExpression :: TestItem > stringScalarExpression :: TestItem
> stringValueExpression = Group "string value expression" > stringScalarExpression = Group "string value expression"
> [-- todo: 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> <plus sign> <interval term>
| <datetime value expression> <minus sign> <interval term> | <datetime value expression> <minus sign> <interval term>
> datetimeValueExpression :: TestItem > datetimeScalarExpression :: TestItem
> datetimeValueExpression = Group "datetime value expression" > datetimeScalarExpression = Group "datetime value expression"
> [-- todo: datetime value expression > [-- todo: datetime value expression
> datetimeValueFunction > datetimeValueFunction
> ] > ]
@ -2288,8 +2288,8 @@ Specify an interval value.
| <left paren> <datetime value expression> <minus sign> <datetime term> <right paren> | <left paren> <datetime value expression> <minus sign> <datetime term> <right paren>
<interval qualifier> <interval qualifier>
> intervalValueExpression :: TestItem > intervalScalarExpression :: TestItem
> intervalValueExpression = Group "interval value expression" > intervalScalarExpression = Group "interval value expression"
> [-- todo: interval value expression > [-- todo: interval value expression
> ] > ]
@ -2355,9 +2355,9 @@ Specify a boolean value.
<left paren> <boolean value expression> <right paren> <left paren> <boolean value expression> <right paren>
> booleanValueExpression :: TestItem > booleanScalarExpression :: TestItem
> booleanValueExpression = Group "booleab value expression" > booleanScalarExpression = Group "booleab value expression"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [("a or b", BinOp a [Name Nothing "or"] b) > [("a or b", BinOp a [Name Nothing "or"] b)
> ,("a and b", BinOp a [Name Nothing "and"] b) > ,("a and b", BinOp a [Name Nothing "and"] b)
> ,("not a", PrefixOp [Name Nothing "not"] a) > ,("not a", PrefixOp [Name Nothing "not"] a)
@ -2391,8 +2391,8 @@ Specify an array value.
<array primary> ::= <array value function> | <value expression primary> <array primary> ::= <array value function> | <value expression primary>
> arrayValueExpression :: TestItem > arrayScalarExpression :: TestItem
> arrayValueExpression = Group "array value expression" > arrayScalarExpression = Group "array value expression"
> [-- todo: array value expression > [-- todo: array value expression
> ] > ]
@ -2432,7 +2432,7 @@ Specify construction of an array.
> arrayValueConstructor :: TestItem > arrayValueConstructor :: TestItem
> arrayValueConstructor = Group "array value constructor" > arrayValueConstructor = Group "array value constructor"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [("array[1,2,3]" > [("array[1,2,3]"
> ,Array (Iden [Name Nothing "array"]) > ,Array (Iden [Name Nothing "array"])
> [NumLit "1", NumLit "2", NumLit "3"]) > [NumLit "1", NumLit "2", NumLit "3"])
@ -2468,9 +2468,9 @@ Specify a multiset value.
<multiset primary> ::= <multiset value function> | <value expression primary> <multiset primary> ::= <multiset value function> | <value expression primary>
> multisetValueExpression :: TestItem > multisetScalarExpression :: TestItem
> multisetValueExpression = Group "multiset value expression" > multisetScalarExpression = Group "multiset value expression"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [("a multiset union b" > [("a multiset union b"
> ,MultisetBinOp (Iden [Name Nothing "a"]) Union SQDefault (Iden [Name Nothing "b"])) > ,MultisetBinOp (Iden [Name Nothing "a"]) Union SQDefault (Iden [Name Nothing "b"]))
> ,("a multiset union all b" > ,("a multiset union all b"
@ -2500,7 +2500,7 @@ special case term.
> multisetValueFunction :: TestItem > multisetValueFunction :: TestItem
> multisetValueFunction = Group "multiset value function" > multisetValueFunction = Group "multiset value function"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [("set(a)", App [Name Nothing "set"] [Iden [Name Nothing "a"]]) > [("set(a)", App [Name Nothing "set"] [Iden [Name Nothing "a"]])
> ] > ]
@ -2528,7 +2528,7 @@ Specify construction of a multiset.
> multisetValueConstructor :: TestItem > multisetValueConstructor :: TestItem
> multisetValueConstructor = Group "multiset value constructor" > multisetValueConstructor = Group "multiset value constructor"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [("multiset[a,b,c]", MultisetCtor[Iden [Name Nothing "a"] > [("multiset[a,b,c]", MultisetCtor[Iden [Name Nothing "a"]
> ,Iden [Name Nothing "b"], Iden [Name Nothing "c"]]) > ,Iden [Name Nothing "b"], Iden [Name Nothing "c"]])
> ,("multiset(select * from t)", MultisetQueryCtor qe) > ,("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 :: TestItem
> rowValueConstructor = Group "row value constructor" > rowValueConstructor = Group "row value constructor"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [("(a,b)" > [("(a,b)"
> ,SpecialOp [Name Nothing "rowctor"] [Iden [Name Nothing "a"], Iden [Name Nothing "b"]]) > ,SpecialOp [Name Nothing "rowctor"] [Iden [Name Nothing "a"], Iden [Name Nothing "b"]])
> ,("row(1)",App [Name Nothing "row"] [NumLit "1"]) > ,("row(1)",App [Name Nothing "row"] [NumLit "1"])
@ -3460,7 +3460,7 @@ Specify a comparison of two row values.
> comparisonPredicates :: TestItem > comparisonPredicates :: TestItem
> comparisonPredicates = Group "comparison predicates" > comparisonPredicates = Group "comparison predicates"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> $ map mkOp ["=", "<>", "<", ">", "<=", ">="] > $ map mkOp ["=", "<>", "<", ">", "<=", ">="]
> ++ [("ROW(a) = ROW(b)" > ++ [("ROW(a) = ROW(b)"
> ,BinOp (App [Name Nothing "ROW"] [a]) > ,BinOp (App [Name Nothing "ROW"] [a])
@ -3664,7 +3664,7 @@ Specify a quantified comparison.
> quantifiedComparisonPredicate :: TestItem > quantifiedComparisonPredicate :: TestItem
> quantifiedComparisonPredicate = Group "quantified comparison predicate" > quantifiedComparisonPredicate = Group "quantified comparison predicate"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [("a = any (select * from t)" > [("a = any (select * from t)"
> ,QuantifiedComparison (Iden [Name Nothing "a"]) [Name Nothing "="] CPAny qe) > ,QuantifiedComparison (Iden [Name Nothing "a"]) [Name Nothing "="] CPAny qe)
@ -3691,7 +3691,7 @@ Specify a test for a non-empty set.
> existsPredicate :: TestItem > existsPredicate :: TestItem
> existsPredicate = Group "exists predicate" > existsPredicate = Group "exists predicate"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [("exists(select * from t where a = 4)" > [("exists(select * from t where a = 4)"
> ,SubQueryExpr SqExists > ,SubQueryExpr SqExists
> $ makeSelect > $ makeSelect
@ -3710,7 +3710,7 @@ Specify a test for the absence of duplicate rows.
> uniquePredicate :: TestItem > uniquePredicate :: TestItem
> uniquePredicate = Group "unique predicate" > uniquePredicate = Group "unique predicate"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [("unique(select * from t where a = 4)" > [("unique(select * from t where a = 4)"
> ,SubQueryExpr SqUnique > ,SubQueryExpr SqUnique
> $ makeSelect > $ makeSelect
@ -3746,7 +3746,7 @@ Specify a test for matching rows.
> matchPredicate :: TestItem > matchPredicate :: TestItem
> matchPredicate = Group "match predicate" > matchPredicate = Group "match predicate"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [("a match (select a from t)" > [("a match (select a from t)"
> ,Match (Iden [Name Nothing "a"]) False qe) > ,Match (Iden [Name Nothing "a"]) False qe)
> ,("(a,b) match (select a,b from t)" > ,("(a,b) match (select a,b from t)"
@ -4098,7 +4098,7 @@ Specify a default collation.
> collateClause :: TestItem > collateClause :: TestItem
> collateClause = Group "collate clause" > collateClause = Group "collate clause"
> $ map (uncurry (TestValueExpr ansi2011)) > $ map (uncurry (TestScalarExpr ansi2011))
> [("a collate my_collation" > [("a collate my_collation"
> ,Collate (Iden [Name Nothing "a"]) [Name Nothing "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 :: TestItem
> aggregateFunction = Group "aggregate function" > aggregateFunction = Group "aggregate function"
> $ map (uncurry (TestValueExpr ansi2011)) $ > $ map (uncurry (TestScalarExpr ansi2011)) $
> [("count(*)",App [Name Nothing "count"] [Star]) > [("count(*)",App [Name Nothing "count"] [Star])
> ,("count(*) filter (where something > 5)" > ,("count(*) filter (where something > 5)"
> ,AggregateApp [Name Nothing "count"] SQDefault [Star] [] fil) > ,AggregateApp [Name Nothing "count"] SQDefault [Star] [] fil)

View file

@ -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.TestTypes
> import Language.SQL.SimpleSQL.Syntax > import Language.SQL.SimpleSQL.Syntax
> valueExprTests :: TestItem > scalarExprTests :: TestItem
> valueExprTests = Group "valueExprTests" > scalarExprTests = Group "scalarExprTests"
> [literals > [literals
> ,identifiers > ,identifiers
> ,star > ,star
@ -24,7 +24,7 @@ Tests for parsing value expressions
> ] > ]
> literals :: TestItem > literals :: TestItem
> literals = Group "literals" $ map (uncurry (TestValueExpr ansi2011)) > literals = Group "literals" $ map (uncurry (TestScalarExpr ansi2011))
> [("3", NumLit "3") > [("3", NumLit "3")
> ,("3.", NumLit "3.") > ,("3.", NumLit "3.")
> ,("3.3", NumLit "3.3") > ,("3.3", NumLit "3.3")
@ -46,14 +46,14 @@ Tests for parsing value expressions
> ] > ]
> identifiers :: TestItem > identifiers :: TestItem
> identifiers = Group "identifiers" $ map (uncurry (TestValueExpr ansi2011)) > identifiers = Group "identifiers" $ map (uncurry (TestScalarExpr ansi2011))
> [("iden1", Iden [Name Nothing "iden1"]) > [("iden1", Iden [Name Nothing "iden1"])
> --,("t.a", Iden2 "t" "a") > --,("t.a", Iden2 "t" "a")
> ,("\"quoted identifier\"", Iden [Name (Just ("\"","\"")) "quoted identifier"]) > ,("\"quoted identifier\"", Iden [Name (Just ("\"","\"")) "quoted identifier"])
> ] > ]
> star :: TestItem > star :: TestItem
> star = Group "star" $ map (uncurry (TestValueExpr ansi2011)) > star = Group "star" $ map (uncurry (TestScalarExpr ansi2011))
> [("*", Star) > [("*", Star)
> --,("t.*", Star2 "t") > --,("t.*", Star2 "t")
> --,("ROW(t.*,42)", App "ROW" [Star2 "t", NumLit "42"]) > --,("ROW(t.*,42)", App "ROW" [Star2 "t", NumLit "42"])
@ -61,12 +61,12 @@ Tests for parsing value expressions
> parameter :: TestItem > parameter :: TestItem
> parameter = Group "parameter" > parameter = Group "parameter"
> [TestValueExpr ansi2011 "?" Parameter > [TestScalarExpr ansi2011 "?" Parameter
> ,TestValueExpr postgres "$13" $ PositionalArg 13] > ,TestScalarExpr postgres "$13" $ PositionalArg 13]
> dots :: TestItem > 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.a", Iden [Name Nothing "t",Name Nothing "a"])
> ,("t.*", BinOp (Iden [Name Nothing "t"]) [Name Nothing "."] Star) > ,("t.*", BinOp (Iden [Name Nothing "t"]) [Name Nothing "."] Star)
> ,("a.b.c", Iden [Name Nothing "a",Name Nothing "b",Name Nothing "c"]) > ,("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 :: TestItem
> app = Group "app" $ map (uncurry (TestValueExpr ansi2011)) > app = Group "app" $ map (uncurry (TestScalarExpr ansi2011))
> [("f()", App [Name Nothing "f"] []) > [("f()", App [Name Nothing "f"] [])
> ,("f(a)", App [Name Nothing "f"] [Iden [Name Nothing "a"]]) > ,("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"]]) > ,("f(a,b)", App [Name Nothing "f"] [Iden [Name Nothing "a"], Iden [Name Nothing "b"]])
> ] > ]
> caseexp :: TestItem > caseexp :: TestItem
> caseexp = Group "caseexp" $ map (uncurry (TestValueExpr ansi2011)) > caseexp = Group "caseexp" $ map (uncurry (TestScalarExpr ansi2011))
> [("case a when 1 then 2 end" > [("case a when 1 then 2 end"
> ,Case (Just $ Iden [Name Nothing "a"]) [([NumLit "1"] > ,Case (Just $ Iden [Name Nothing "a"]) [([NumLit "1"]
> ,NumLit "2")] Nothing) > ,NumLit "2")] Nothing)
@ -117,7 +117,7 @@ Tests for parsing value expressions
> ,miscOps] > ,miscOps]
> binaryOperators :: TestItem > 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"])) > [("a + b", BinOp (Iden [Name Nothing "a"]) [Name Nothing "+"] (Iden [Name Nothing "b"]))
> -- sanity check fixities > -- sanity check fixities
> -- todo: add more fixity checking > -- todo: add more fixity checking
@ -132,7 +132,7 @@ Tests for parsing value expressions
> ] > ]
> unaryOperators :: TestItem > 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 a", PrefixOp [Name Nothing "not"] $ Iden [Name Nothing "a"])
> ,("not not a", PrefixOp [Name Nothing "not"] $ 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"]) > ,("+a", PrefixOp [Name Nothing "+"] $ Iden [Name Nothing "a"])
@ -141,7 +141,7 @@ Tests for parsing value expressions
> casts :: TestItem > casts :: TestItem
> casts = Group "operators" $ map (uncurry (TestValueExpr ansi2011)) > casts = Group "operators" $ map (uncurry (TestScalarExpr ansi2011))
> [("cast('1' as int)" > [("cast('1' as int)"
> ,Cast (StringLit "'" "'" "1") $ TypeName [Name Nothing "int"]) > ,Cast (StringLit "'" "'" "1") $ TypeName [Name Nothing "int"])
@ -163,7 +163,7 @@ Tests for parsing value expressions
> ] > ]
> subqueries :: TestItem > subqueries :: TestItem
> subqueries = Group "unaryOperators" $ map (uncurry (TestValueExpr ansi2011)) > subqueries = Group "unaryOperators" $ map (uncurry (TestScalarExpr ansi2011))
> [("exists (select a from t)", SubQueryExpr SqExists ms) > [("exists (select a from t)", SubQueryExpr SqExists ms)
> ,("(select a from t)", SubQueryExpr SqSq ms) > ,("(select a from t)", SubQueryExpr SqSq ms)
@ -189,7 +189,7 @@ Tests for parsing value expressions
> } > }
> miscOps :: TestItem > miscOps :: TestItem
> miscOps = Group "unaryOperators" $ map (uncurry (TestValueExpr ansi2011)) > miscOps = Group "unaryOperators" $ map (uncurry (TestScalarExpr ansi2011))
> [("a in (1,2,3)" > [("a in (1,2,3)"
> ,In True (Iden [Name Nothing "a"]) $ InList $ map NumLit ["1","2","3"]) > ,In True (Iden [Name Nothing "a"]) $ InList $ map NumLit ["1","2","3"])
@ -327,7 +327,7 @@ target_string
> ] > ]
> aggregates :: TestItem > aggregates :: TestItem
> aggregates = Group "aggregates" $ map (uncurry (TestValueExpr ansi2011)) > aggregates = Group "aggregates" $ map (uncurry (TestScalarExpr ansi2011))
> [("count(*)",App [Name Nothing "count"] [Star]) > [("count(*)",App [Name Nothing "count"] [Star])
> ,("sum(a order by a)" > ,("sum(a order by a)"
@ -342,7 +342,7 @@ target_string
> ] > ]
> windowFunctions :: TestItem > 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) > [("max(a) over ()", WindowApp [Name Nothing "max"] [Iden [Name Nothing "a"]] [] [] Nothing)
> ,("count(*) over ()", WindowApp [Name Nothing "count"] [Star] [] [] Nothing) > ,("count(*) over ()", WindowApp [Name Nothing "count"] [Star] [] [] Nothing)
@ -401,7 +401,7 @@ target_string
> ] > ]
> parens :: TestItem > parens :: TestItem
> parens = Group "parens" $ map (uncurry (TestValueExpr ansi2011)) > parens = Group "parens" $ map (uncurry (TestScalarExpr ansi2011))
> [("(a)", Parens (Iden [Name Nothing "a"])) > [("(a)", Parens (Iden [Name Nothing "a"]))
> ,("(a + b)", Parens (BinOp (Iden [Name Nothing "a"]) [Name Nothing "+"] (Iden [Name Nothing "b"]))) > ,("(a + b)", Parens (BinOp (Iden [Name Nothing "a"]) [Name Nothing "+"] (Iden [Name Nothing "b"])))
> ] > ]
@ -412,4 +412,4 @@ target_string
> ,"char_length" > ,"char_length"
> ] > ]
> where > 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"]]

View file

@ -16,7 +16,7 @@ mentioned give a parse error. Not sure if this will be too awkward due
to lots of tricky exceptions/variationsx. to lots of tricky exceptions/variationsx.
> data TestItem = Group String [TestItem] > data TestItem = Group String [TestItem]
> | TestValueExpr Dialect String ValueExpr > | TestScalarExpr Dialect String ScalarExpr
> | TestQueryExpr Dialect String QueryExpr > | TestQueryExpr Dialect String QueryExpr
> | TestStatement Dialect String Statement > | TestStatement Dialect String Statement
> | TestStatements 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 check that the string given fails to parse
> | ParseQueryExprFails Dialect String > | ParseQueryExprFails Dialect String
> | ParseValueExprFails Dialect String > | ParseScalarExprFails Dialect String
> | LexTest Dialect String [Token] > | LexTest Dialect String [Token]
> | LexFails Dialect String > | LexFails Dialect String
> deriving (Eq,Show) > deriving (Eq,Show)

View file

@ -25,7 +25,7 @@ test data to the Test.Framework tests.
> import Language.SQL.SimpleSQL.QueryExprComponents > import Language.SQL.SimpleSQL.QueryExprComponents
> import Language.SQL.SimpleSQL.QueryExprs > import Language.SQL.SimpleSQL.QueryExprs
> import Language.SQL.SimpleSQL.TableRefs > import Language.SQL.SimpleSQL.TableRefs
> import Language.SQL.SimpleSQL.ValueExprs > import Language.SQL.SimpleSQL.ScalarExprs
> import Language.SQL.SimpleSQL.Odbc > import Language.SQL.SimpleSQL.Odbc
> import Language.SQL.SimpleSQL.Tpch > import Language.SQL.SimpleSQL.Tpch
> import Language.SQL.SimpleSQL.LexerTests > import Language.SQL.SimpleSQL.LexerTests
@ -45,7 +45,7 @@ order on the generated documentation.
> testData = > testData =
> Group "parserTest" > Group "parserTest"
> [lexerTests > [lexerTests
> ,valueExprTests > ,scalarExprTests
> ,odbcTests > ,odbcTests
> ,queryExprComponentTests > ,queryExprComponentTests
> ,queryExprsTests > ,queryExprsTests
@ -71,8 +71,8 @@ order on the generated documentation.
> itemToTest :: TestItem -> T.TestTree > itemToTest :: TestItem -> T.TestTree
> itemToTest (Group nm ts) = > itemToTest (Group nm ts) =
> T.testGroup nm $ map itemToTest ts > T.testGroup nm $ map itemToTest ts
> itemToTest (TestValueExpr d str expected) = > itemToTest (TestScalarExpr d str expected) =
> toTest parseValueExpr prettyValueExpr d str expected > toTest parseScalarExpr prettyScalarExpr d str expected
> itemToTest (TestQueryExpr d str expected) = > itemToTest (TestQueryExpr d str expected) =
> toTest parseQueryExpr prettyQueryExpr d str expected > toTest parseQueryExpr prettyQueryExpr d str expected
> itemToTest (TestStatement d str expected) = > itemToTest (TestStatement d str expected) =
@ -85,8 +85,8 @@ order on the generated documentation.
> itemToTest (ParseQueryExprFails d str) = > itemToTest (ParseQueryExprFails d str) =
> toFTest parseQueryExpr prettyQueryExpr d str > toFTest parseQueryExpr prettyQueryExpr d str
> itemToTest (ParseValueExprFails d str) = > itemToTest (ParseScalarExprFails d str) =
> toFTest parseValueExpr prettyValueExpr d str > toFTest parseScalarExpr prettyScalarExpr d str
> itemToTest (LexTest d s ts) = makeLexerTest d s ts > itemToTest (LexTest d s ts) = makeLexerTest d s ts
> itemToTest (LexFails d s) = makeLexingFailsTest d s > itemToTest (LexFails d s) = makeLexingFailsTest d s

View file

@ -17,7 +17,7 @@ Converts the test data to asciidoc
> doc n (Group nm is) = > doc n (Group nm is) =
> Heading n nm > Heading n nm
> : concatMap (doc (n + 1)) is > : concatMap (doc (n + 1)) is
> doc _ (TestValueExpr _ str e) = > doc _ (TestScalarExpr _ str e) =
> [Row str (ppShow e)] > [Row str (ppShow e)]
> doc _ (TestQueryExpr _ str e) = > doc _ (TestQueryExpr _ str e) =
> [Row str (ppShow e)] > [Row str (ppShow e)]
@ -29,8 +29,8 @@ Converts the test data to asciidoc
> [Row str (ppShow $ parseQueryExpr d "" Nothing str)] > [Row str (ppShow $ parseQueryExpr d "" Nothing str)]
> doc _ (ParseQueryExprFails d str) = > doc _ (ParseQueryExprFails d str) =
> [Row str (ppShow $ parseQueryExpr d "" Nothing str)] > [Row str (ppShow $ parseQueryExpr d "" Nothing str)]
> doc _ (ParseValueExprFails d str) = > doc _ (ParseScalarExprFails d str) =
> [Row str (ppShow $ parseValueExpr d "" Nothing str)] > [Row str (ppShow $ parseScalarExpr d "" Nothing str)]
> doc _ (LexTest d str t) = > doc _ (LexTest d str t) =
> [Row str (ppShow $ lexSQL d "" Nothing str)] > [Row str (ppShow $ lexSQL d "" Nothing str)]

View file

@ -56,7 +56,7 @@ link:https://github.com/JakeWheat/intro_to_parsing/blob/master/SimpleSQLQueryPar
** offset and fetch ** offset and fetch
** set operators ** set operators
** common table expressions ** common table expressions
** wide range of value expressions ** wide range of scalar expressions
* DDL * DDL
** TODO ** TODO
* non-query DML * non-query DML

View file

@ -28,7 +28,7 @@ get the best parser error messages possible.
=== Select lists === 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. 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 === 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. parentheses and grouping sets with nested grouping expressions.
=== Order by clause === Order by clause
Supports value expressions, asc/desc and nulls first/last. Supports scalar expressions, asc/desc and nulls first/last.
=== Offset and fetch === 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'. 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: including:
* select lists; * select lists;
@ -91,7 +91,7 @@ including:
This doesn't exactly follow the ANSI Standards, which have separate This doesn't exactly follow the ANSI Standards, which have separate
grammars for most of these. grammars for most of these.
The supported value expressions include: The supported scalar expressions include:
* basic string literals in single quotes * basic string literals in single quotes
* number literals: digits.digitse+-exp * number literals: digits.digitse+-exp