1
Fork 0

generalize . to a binary operator

This commit is contained in:
Jake Wheat 2013-12-17 15:21:43 +02:00
parent 8adc169b38
commit 8093498f2d
6 changed files with 26 additions and 26 deletions

View file

@ -81,9 +81,7 @@ the fixity code.
> App n es -> HSE.App (var ('f':name n)) $ ltoh es
> Parens e0 -> HSE.Paren $ toHaskell e0
> IntervalLit {} -> str ('v':show e)
> Iden2 {} -> str ('v':show e)
> Star -> str ('v':show e)
> Star2 {} -> str ('v':show e)
> AggregateApp nm d es od ->
> HSE.App (var ('a':name nm))
> $ HSE.List [str $ show (d,map snd od)

View file

@ -125,20 +125,15 @@ identifiers.
> identifier :: P ScalarExpr
> 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
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 = choice [Star <$ symbol "*"
> ,Star2 <$> (name <* symbol "." <* symbol "*")]
> star = Star <$ symbol "*"
== function application, aggregates and windows
@ -327,7 +322,7 @@ keyword.
> binOpSymbolNames =
> ["=", "<=", ">=", "!=", "<>", "<", ">"
> ,"*", "/", "+", "-"
> ,"||"]
> ,"||", "."]
> binOpKeywordNames :: [String]
> binOpKeywordNames = ["and", "or", "like", "overlaps"]
@ -411,7 +406,8 @@ associativity. This is fixed with a separate pass over the AST.
> ++ prefixUnOpKeywordNames ++ prefixUnOpSymbolNames
> ++ postfixOpKeywords
> -- these are the ops with the highest precedence in order
> highPrec = [infixl_ ["*","/"]
> highPrec = [infixl_ ["."]
> ,infixl_ ["*","/"]
> ,infixl_ ["+", "-"]
> ,infixl_ ["<=",">=","!=","<>","||","like"]
> ]
@ -451,7 +447,6 @@ could at least do with some heavy explanation.
> ,subquery
> ,prefixUnaryOp
> ,try app
> ,try dottedIden
> ,try star
> ,identifier
> ,sparens]

View file

@ -39,9 +39,7 @@
> <+> text u
> <+> maybe empty (parens . text . show ) p
> scalarExpr (Iden i) = name i
> scalarExpr (Iden2 q i) = name q <> text "." <> name i
> scalarExpr Star = text "*"
> scalarExpr (Star2 q) = name q <> text "." <> text "*"
> scalarExpr (App f es) = name f <> parens (commaSep (map scalarExpr es))
@ -97,6 +95,9 @@
> where
> ands (BinOp a op' b) | op == op' = ands a ++ ands b
> 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 e0 <+> name f <+> scalarExpr e1

View file

@ -47,12 +47,8 @@
> | IntervalLit String String (Maybe Int)
> -- | identifier without dots
> | Iden Name
> -- | identifier with one dot
> | Iden2 Name Name
> -- | star
> -- | star, as in select *, t.*, count(*)
> | Star
> -- | star with qualifier, e.g t.*
> | Star2 Name
> -- | function application (anything that looks like c style
> -- function application syntactically)
> | App Name [ScalarExpr]

5
TODO
View file

@ -1,8 +1,6 @@
next release:
escapes in string literals
ansi standard versions of limit and offset
OFFSET start { ROW | ROWS }
@ -76,6 +74,9 @@ review abstract syntax (e.g. combine App with SpecialOp?)
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
nutshell, sql guide, sql reference guide, sql standard, sql server
manual, oracle manual, teradata manual + re-through postgresql

View file

@ -12,6 +12,7 @@ Tests for parsing scalar expressions
> [literals
> ,identifiers
> ,star
> ,dots
> ,app
> ,caseexp
> ,operators
@ -44,15 +45,23 @@ Tests for parsing scalar expressions
> identifiers :: TestItem
> identifiers = Group "identifiers" $ map (uncurry TestScalarExpr)
> [("iden1", Iden "iden1")
> ,("t.a", Iden2 "t" "a")
> --,("t.a", Iden2 "t" "a")
> ,("\"quoted identifier\"", Iden $ QName "quoted identifier")
> ]
> star :: TestItem
> star = Group "star" $ map (uncurry TestScalarExpr)
> [("*", Star)
> ,("t.*", Star2 "t")
> ,("ROW(t.*,42)", App "ROW" [Star2 "t", NumLit "42"])
> --,("t.*", Star2 "t")
> --,("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