1
Fork 0

swap order in select lists so the expression comes first then the alias to match the order in the concrete syntax

This commit is contained in:
Jake Wheat 2013-12-31 11:31:00 +02:00
parent 552d3f5383
commit 7cf5275615
9 changed files with 43 additions and 46 deletions

View file

@ -1,7 +1,3 @@
TODO:
P -> P.Parser
swap order in select items
> {-# LANGUAGE TupleSections #-}
> -- | This is the module with the parser functions.
> module Language.SQL.SimpleSQL.Parser
@ -573,11 +569,11 @@ expose the b expression for window frame clause range between
== select lists
> selectItem :: Parser (Maybe Name, ValueExpr)
> selectItem = flip (,) <$> valueExpr <*> optionMaybe (try als)
> selectItem :: Parser (ValueExpr,Maybe Name)
> selectItem = (,) <$> valueExpr <*> optionMaybe (try als)
> where als = optional (try (keyword_ "as")) *> name
> selectList :: Parser [(Maybe Name,ValueExpr)]
> selectList :: Parser [(ValueExpr,Maybe Name)]
> selectList = commaSep1 selectItem
== from

View file

@ -213,10 +213,10 @@
> text "as" <+> name nm
> <+> maybe empty (parens . commaSep . map name) cols
> selectList :: [(Maybe Name, ValueExpr)] -> Doc
> selectList :: [(ValueExpr,Maybe Name)] -> Doc
> selectList is = commaSep $ map si is
> where
> si (al,e) = valueExpr e <+> maybe empty als al
> si (e,al) = valueExpr e <+> maybe empty als al
> als al = text "as" <+> name al
> from :: [TableRef] -> Doc

View file

@ -196,8 +196,8 @@
> data QueryExpr
> = Select
> {qeSetQuantifier :: SetQuantifier
> ,qeSelectList :: [(Maybe Name,ValueExpr)]
> -- ^ the column aliases and the expressions
> ,qeSelectList :: [(ValueExpr,Maybe Name)]
> -- ^ the expressions and the column aliases
TODO: consider breaking this up. The SQL grammar has
queryexpr = select <select list> [<table expression>]

View file

@ -12,7 +12,7 @@ Some tests for parsing full queries.
> fullQueriesTests = Group "queries" $ map (uncurry TestQueryExpr)
> [("select count(*) from t"
> ,makeSelect
> {qeSelectList = [(Nothing, App "count" [Star])]
> {qeSelectList = [(App "count" [Star], Nothing)]
> ,qeFrom = [TRSimple "t"]
> }
> )
@ -24,10 +24,10 @@ Some tests for parsing full queries.
> \ having count(1) > 5\n\
> \ order by s"
> ,makeSelect
> {qeSelectList = [(Nothing, Iden "a")
> ,(Just "s"
> ,App "sum" [BinOp (Iden "c")
> "+" (Iden "d")])]
> {qeSelectList = [(Iden "a", Nothing)
> ,(App "sum" [BinOp (Iden "c")
> "+" (Iden "d")]
> ,Just "s")]
> ,qeFrom = [TRSimple "t", TRSimple "u"]
> ,qeWhere = Just $ BinOp (Iden "a") ">" (NumLit "5")
> ,qeGroupBy = [SimpleGroup $ Iden "a"]

View file

@ -18,16 +18,16 @@ Here are the tests for the group by component of query exprs
> simpleGroupBy :: TestItem
> simpleGroupBy = Group "simpleGroupBy" $ map (uncurry TestQueryExpr)
> [("select a,sum(b) from t group by a"
> ,makeSelect {qeSelectList = [(Nothing, Iden "a")
> ,(Nothing, App "sum" [Iden "b"])]
> ,makeSelect {qeSelectList = [(Iden "a",Nothing)
> ,(App "sum" [Iden "b"],Nothing)]
> ,qeFrom = [TRSimple "t"]
> ,qeGroupBy = [SimpleGroup $ Iden "a"]
> })
> ,("select a,b,sum(c) from t group by a,b"
> ,makeSelect {qeSelectList = [(Nothing, Iden "a")
> ,(Nothing, Iden "b")
> ,(Nothing, App "sum" [Iden "c"])]
> ,makeSelect {qeSelectList = [(Iden "a",Nothing)
> ,(Iden "b",Nothing)
> ,(App "sum" [Iden "c"],Nothing)]
> ,qeFrom = [TRSimple "t"]
> ,qeGroupBy = [SimpleGroup $ Iden "a"
> ,SimpleGroup $ Iden "b"]
@ -49,7 +49,7 @@ sure which sql version they were introduced, 1999 or 2003 I think).
> ,ms [Rollup [SimpleGroup $ Iden "a", SimpleGroup $ Iden "b"]])
> ]
> where
> ms g = makeSelect {qeSelectList = [(Nothing,Star)]
> ms g = makeSelect {qeSelectList = [(Star,Nothing)]
> ,qeFrom = [TRSimple "t"]
> ,qeGroupBy = g}

View file

@ -37,45 +37,46 @@ These are a few misc tests which don't fit anywhere else.
> where
> ms d = makeSelect
> {qeSetQuantifier = d
> ,qeSelectList = [(Nothing,Iden "a")]
> ,qeSelectList = [(Iden "a",Nothing)]
> ,qeFrom = [TRSimple "t"]}
> selectLists :: TestItem
> selectLists = Group "selectLists" $ map (uncurry TestQueryExpr)
> [("select 1",
> makeSelect {qeSelectList = [(Nothing,NumLit "1")]})
> makeSelect {qeSelectList = [(NumLit "1",Nothing)]})
> ,("select a"
> ,makeSelect {qeSelectList = [(Nothing,Iden "a")]})
> ,makeSelect {qeSelectList = [(Iden "a",Nothing)]})
> ,("select a,b"
> ,makeSelect {qeSelectList = [(Nothing,Iden "a")
> ,(Nothing,Iden "b")]})
> ,makeSelect {qeSelectList = [(Iden "a",Nothing)
> ,(Iden "b",Nothing)]})
> ,("select 1+2,3+4"
> ,makeSelect {qeSelectList =
> [(Nothing,BinOp (NumLit "1") "+" (NumLit "2"))
> ,(Nothing,BinOp (NumLit "3") "+" (NumLit "4"))]})
> [(BinOp (NumLit "1") "+" (NumLit "2"),Nothing)
> ,(BinOp (NumLit "3") "+" (NumLit "4"),Nothing)]})
> ,("select a as a, /*comment*/ b as b"
> ,makeSelect {qeSelectList = [(Just "a", Iden "a")
> ,(Just "b", Iden "b")]})
> ,makeSelect {qeSelectList = [(Iden "a", Just "a")
> ,(Iden "b", Just "b")]})
> ,("select a a, b b"
> ,makeSelect {qeSelectList = [(Just "a", Iden "a")
> ,(Just "b", Iden "b")]})
> ,makeSelect {qeSelectList = [(Iden "a", Just "a")
> ,(Iden "b", Just "b")]})
> ,("select a + b * c"
> ,makeSelect {qeSelectList =
> [(Nothing,BinOp (Iden (Name "a")) (Name "+")
> (BinOp (Iden (Name "b")) (Name "*") (Iden (Name "c"))))]})
> [(BinOp (Iden (Name "a")) (Name "+")
> (BinOp (Iden (Name "b")) (Name "*") (Iden (Name "c")))
> ,Nothing)]})
> ]
> whereClause :: TestItem
> whereClause = Group "whereClause" $ map (uncurry TestQueryExpr)
> [("select a from t where a = 5"
> ,makeSelect {qeSelectList = [(Nothing,Iden "a")]
> ,makeSelect {qeSelectList = [(Iden "a",Nothing)]
> ,qeFrom = [TRSimple "t"]
> ,qeWhere = Just $ BinOp (Iden "a") "=" (NumLit "5")})
> ]
@ -83,8 +84,8 @@ These are a few misc tests which don't fit anywhere else.
> having :: TestItem
> having = Group "having" $ map (uncurry TestQueryExpr)
> [("select a,sum(b) from t group by a having sum(b) > 5"
> ,makeSelect {qeSelectList = [(Nothing, Iden "a")
> ,(Nothing, App "sum" [Iden "b"])]
> ,makeSelect {qeSelectList = [(Iden "a",Nothing)
> ,(App "sum" [Iden "b"],Nothing)]
> ,qeFrom = [TRSimple "t"]
> ,qeGroupBy = [SimpleGroup $ Iden "a"]
> ,qeHaving = Just $ BinOp (App "sum" [Iden "b"])
@ -114,7 +115,7 @@ These are a few misc tests which don't fit anywhere else.
> ]
> where
> ms o = makeSelect {qeSelectList = [(Nothing,Iden "a")]
> ms o = makeSelect {qeSelectList = [(Iden "a",Nothing)]
> ,qeFrom = [TRSimple "t"]
> ,qeOrderBy = o}
@ -135,7 +136,7 @@ These are a few misc tests which don't fit anywhere else.
> ]
> where
> ms o l = makeSelect
> {qeSelectList = [(Nothing,Iden "a")]
> {qeSelectList = [(Iden "a",Nothing)]
> ,qeFrom = [TRSimple "t"]
> ,qeOffset = o
> ,qeFetchFirst = l}
@ -164,10 +165,10 @@ These are a few misc tests which don't fit anywhere else.
> ]
> where
> ms1 = makeSelect
> {qeSelectList = [(Nothing,Iden "a")]
> {qeSelectList = [(Iden "a",Nothing)]
> ,qeFrom = [TRSimple "t"]}
> ms2 = makeSelect
> {qeSelectList = [(Nothing,Iden "b")]
> {qeSelectList = [(Iden "b",Nothing)]
> ,qeFrom = [TRSimple "u"]}
@ -189,7 +190,7 @@ These are a few misc tests which don't fit anywhere else.
> ]
> where
> ms c t = makeSelect
> {qeSelectList = [(Nothing,Iden c)]
> {qeSelectList = [(Iden c,Nothing)]
> ,qeFrom = [TRSimple t]}
> ms1 = ms "a" "t"
> ms2 = ms "a" "u"

View file

@ -15,4 +15,4 @@ query expressions from one string.
> ,(" select 1;select 1; ",[ms,ms])
> ]
> where
> ms = makeSelect {qeSelectList = [(Nothing,NumLit "1")]}
> ms = makeSelect {qeSelectList = [(NumLit "1",Nothing)]}

View file

@ -100,5 +100,5 @@ these lateral queries make no sense but the syntax is valid
> JCross (TRSimple "v") Nothing])
> ]
> where
> ms f = makeSelect {qeSelectList = [(Nothing,Iden "a")]
> ms f = makeSelect {qeSelectList = [(Iden "a",Nothing)]
> ,qeFrom = f}

View file

@ -183,7 +183,7 @@ Tests for parsing value expressions
> ]
> where
> ms = makeSelect
> {qeSelectList = [(Nothing,Iden "a")]
> {qeSelectList = [(Iden "a",Nothing)]
> ,qeFrom = [TRSimple "t"]
> }