generalize . to a binary operator
This commit is contained in:
parent
8adc169b38
commit
8093498f2d
|
@ -81,9 +81,7 @@ the fixity code.
|
||||||
> App n es -> HSE.App (var ('f':name n)) $ ltoh es
|
> App n es -> HSE.App (var ('f':name n)) $ ltoh es
|
||||||
> Parens e0 -> HSE.Paren $ toHaskell e0
|
> Parens e0 -> HSE.Paren $ toHaskell e0
|
||||||
> IntervalLit {} -> str ('v':show e)
|
> IntervalLit {} -> str ('v':show e)
|
||||||
> Iden2 {} -> str ('v':show e)
|
|
||||||
> Star -> str ('v':show e)
|
> Star -> str ('v':show e)
|
||||||
> Star2 {} -> str ('v':show e)
|
|
||||||
> AggregateApp nm d es od ->
|
> AggregateApp nm d es od ->
|
||||||
> HSE.App (var ('a':name nm))
|
> HSE.App (var ('a':name nm))
|
||||||
> $ HSE.List [str $ show (d,map snd od)
|
> $ HSE.List [str $ show (d,map snd od)
|
||||||
|
|
|
@ -125,20 +125,15 @@ identifiers.
|
||||||
> identifier :: P ScalarExpr
|
> identifier :: P ScalarExpr
|
||||||
> identifier = Iden <$> name
|
> identifier = Iden <$> name
|
||||||
|
|
||||||
Identifier with one dot in it. This should be extended to any amount
|
|
||||||
of dots.
|
|
||||||
|
|
||||||
> dottedIden :: P ScalarExpr
|
|
||||||
> dottedIden = Iden2 <$> name <*> (symbol "." *> name)
|
|
||||||
|
|
||||||
== star
|
== star
|
||||||
|
|
||||||
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.
|
places as well. Because it is quite general, the parser doesn't
|
||||||
|
attempt to check that the star is in a valid context, it parses it ok
|
||||||
|
in any scalar expression context.
|
||||||
|
|
||||||
> star :: P ScalarExpr
|
> star :: P ScalarExpr
|
||||||
> star = choice [Star <$ symbol "*"
|
> star = Star <$ symbol "*"
|
||||||
> ,Star2 <$> (name <* symbol "." <* symbol "*")]
|
|
||||||
|
|
||||||
== function application, aggregates and windows
|
== function application, aggregates and windows
|
||||||
|
|
||||||
|
@ -327,7 +322,7 @@ keyword.
|
||||||
> binOpSymbolNames =
|
> binOpSymbolNames =
|
||||||
> ["=", "<=", ">=", "!=", "<>", "<", ">"
|
> ["=", "<=", ">=", "!=", "<>", "<", ">"
|
||||||
> ,"*", "/", "+", "-"
|
> ,"*", "/", "+", "-"
|
||||||
> ,"||"]
|
> ,"||", "."]
|
||||||
|
|
||||||
> binOpKeywordNames :: [String]
|
> binOpKeywordNames :: [String]
|
||||||
> binOpKeywordNames = ["and", "or", "like", "overlaps"]
|
> binOpKeywordNames = ["and", "or", "like", "overlaps"]
|
||||||
|
@ -411,7 +406,8 @@ associativity. This is fixed with a separate pass over the AST.
|
||||||
> ++ prefixUnOpKeywordNames ++ prefixUnOpSymbolNames
|
> ++ prefixUnOpKeywordNames ++ prefixUnOpSymbolNames
|
||||||
> ++ postfixOpKeywords
|
> ++ postfixOpKeywords
|
||||||
> -- these are the ops with the highest precedence in order
|
> -- these are the ops with the highest precedence in order
|
||||||
> highPrec = [infixl_ ["*","/"]
|
> highPrec = [infixl_ ["."]
|
||||||
|
> ,infixl_ ["*","/"]
|
||||||
> ,infixl_ ["+", "-"]
|
> ,infixl_ ["+", "-"]
|
||||||
> ,infixl_ ["<=",">=","!=","<>","||","like"]
|
> ,infixl_ ["<=",">=","!=","<>","||","like"]
|
||||||
> ]
|
> ]
|
||||||
|
@ -451,7 +447,6 @@ could at least do with some heavy explanation.
|
||||||
> ,subquery
|
> ,subquery
|
||||||
> ,prefixUnaryOp
|
> ,prefixUnaryOp
|
||||||
> ,try app
|
> ,try app
|
||||||
> ,try dottedIden
|
|
||||||
> ,try star
|
> ,try star
|
||||||
> ,identifier
|
> ,identifier
|
||||||
> ,sparens]
|
> ,sparens]
|
||||||
|
|
|
@ -39,9 +39,7 @@
|
||||||
> <+> text u
|
> <+> text u
|
||||||
> <+> maybe empty (parens . text . show ) p
|
> <+> maybe empty (parens . text . show ) p
|
||||||
> scalarExpr (Iden i) = name i
|
> scalarExpr (Iden i) = name i
|
||||||
> scalarExpr (Iden2 q i) = name q <> text "." <> name i
|
|
||||||
> scalarExpr Star = text "*"
|
> scalarExpr Star = text "*"
|
||||||
> scalarExpr (Star2 q) = name q <> text "." <> text "*"
|
|
||||||
|
|
||||||
> scalarExpr (App f es) = name f <> parens (commaSep (map scalarExpr es))
|
> scalarExpr (App f es) = name f <> parens (commaSep (map scalarExpr es))
|
||||||
|
|
||||||
|
@ -97,6 +95,9 @@
|
||||||
> 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
|
||||||
|
> scalarExpr (BinOp e0 (Name ".") e1) =
|
||||||
|
> scalarExpr e0 <> text "." <> scalarExpr e1
|
||||||
> scalarExpr (BinOp e0 f e1) =
|
> scalarExpr (BinOp e0 f e1) =
|
||||||
> scalarExpr e0 <+> name f <+> scalarExpr e1
|
> scalarExpr e0 <+> name f <+> scalarExpr e1
|
||||||
|
|
||||||
|
|
|
@ -47,12 +47,8 @@
|
||||||
> | IntervalLit String String (Maybe Int)
|
> | IntervalLit String String (Maybe Int)
|
||||||
> -- | identifier without dots
|
> -- | identifier without dots
|
||||||
> | Iden Name
|
> | Iden Name
|
||||||
> -- | identifier with one dot
|
> -- | star, as in select *, t.*, count(*)
|
||||||
> | Iden2 Name Name
|
|
||||||
> -- | star
|
|
||||||
> | Star
|
> | Star
|
||||||
> -- | star with qualifier, e.g t.*
|
|
||||||
> | Star2 Name
|
|
||||||
> -- | function application (anything that looks like c style
|
> -- | function application (anything that looks like c style
|
||||||
> -- function application syntactically)
|
> -- function application syntactically)
|
||||||
> | App Name [ScalarExpr]
|
> | App Name [ScalarExpr]
|
||||||
|
|
5
TODO
5
TODO
|
@ -1,8 +1,6 @@
|
||||||
|
|
||||||
next release:
|
next release:
|
||||||
|
|
||||||
escapes in string literals
|
|
||||||
|
|
||||||
ansi standard versions of limit and offset
|
ansi standard versions of limit and offset
|
||||||
|
|
||||||
OFFSET start { ROW | ROWS }
|
OFFSET start { ROW | ROWS }
|
||||||
|
@ -76,6 +74,9 @@ review abstract syntax (e.g. combine App with SpecialOp?)
|
||||||
|
|
||||||
Later general tasks:
|
Later general tasks:
|
||||||
|
|
||||||
|
extended string literals, escapes and other flavours (like pg and
|
||||||
|
oracle custom delimiters)
|
||||||
|
|
||||||
run through other manuals for example queries and features: sql in a
|
run through other manuals for example queries and features: sql in a
|
||||||
nutshell, sql guide, sql reference guide, sql standard, sql server
|
nutshell, sql guide, sql reference guide, sql standard, sql server
|
||||||
manual, oracle manual, teradata manual + re-through postgresql
|
manual, oracle manual, teradata manual + re-through postgresql
|
||||||
|
|
|
@ -12,6 +12,7 @@ Tests for parsing scalar expressions
|
||||||
> [literals
|
> [literals
|
||||||
> ,identifiers
|
> ,identifiers
|
||||||
> ,star
|
> ,star
|
||||||
|
> ,dots
|
||||||
> ,app
|
> ,app
|
||||||
> ,caseexp
|
> ,caseexp
|
||||||
> ,operators
|
> ,operators
|
||||||
|
@ -44,15 +45,23 @@ Tests for parsing scalar expressions
|
||||||
> identifiers :: TestItem
|
> identifiers :: TestItem
|
||||||
> identifiers = Group "identifiers" $ map (uncurry TestScalarExpr)
|
> identifiers = Group "identifiers" $ map (uncurry TestScalarExpr)
|
||||||
> [("iden1", Iden "iden1")
|
> [("iden1", Iden "iden1")
|
||||||
> ,("t.a", Iden2 "t" "a")
|
> --,("t.a", Iden2 "t" "a")
|
||||||
> ,("\"quoted identifier\"", Iden $ QName "quoted identifier")
|
> ,("\"quoted identifier\"", Iden $ QName "quoted identifier")
|
||||||
> ]
|
> ]
|
||||||
|
|
||||||
> star :: TestItem
|
> star :: TestItem
|
||||||
> star = Group "star" $ map (uncurry TestScalarExpr)
|
> star = Group "star" $ map (uncurry TestScalarExpr)
|
||||||
> [("*", 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"])
|
||||||
|
> ]
|
||||||
|
|
||||||
|
> dots :: TestItem
|
||||||
|
> dots = Group "dot" $ map (uncurry TestScalarExpr)
|
||||||
|
> [("t.a", BinOp (Iden "t") "." (Iden "a"))
|
||||||
|
> ,("t.*", BinOp (Iden "t") "." Star)
|
||||||
|
> ,("a.b.c", BinOp (BinOp (Iden "a") "." (Iden "b")) "." (Iden "c"))
|
||||||
|
> ,("ROW(t.*,42)", App "ROW" [BinOp (Iden "t") "." Star, NumLit "42"])
|
||||||
> ]
|
> ]
|
||||||
|
|
||||||
> app :: TestItem
|
> app :: TestItem
|
||||||
|
|
Loading…
Reference in a new issue