1
Fork 0

change set quantifier and sort direction to represent default separately

This commit is contained in:
Jake Wheat 2014-04-18 11:18:21 +03:00
parent c814cc9437
commit 3df87a3cf9
8 changed files with 55 additions and 49 deletions

View file

@ -184,11 +184,11 @@ aggregate([all|distinct] args [order by orderitems])
> aggOrApp :: Name -> Parser ValueExpr > aggOrApp :: Name -> Parser ValueExpr
> aggOrApp n = > aggOrApp n =
> makeApp n > makeApp n
> <$> parens ((,,) <$> duplicates > <$> parens ((,,) <$> (fromMaybe SQDefault <$> duplicates)
> <*> choice [commaSep valueExpr] > <*> choice [commaSep valueExpr]
> <*> (optionMaybe orderBy)) > <*> (optionMaybe orderBy))
> where > where
> makeApp i (Nothing,es,Nothing) = App i es > makeApp i (SQDefault,es,Nothing) = App i es
> makeApp i (d,es,od) = AggregateApp i d es (fromMaybe [] od) > makeApp i (d,es,od) = AggregateApp i d es (fromMaybe [] od)
> duplicates :: Parser (Maybe SetQuantifier) > duplicates :: Parser (Maybe SetQuantifier)
@ -602,7 +602,7 @@ TODO: carefully review the precedences and associativities.
> ,"is unknown" > ,"is unknown"
> ,"is not unknown"] > ,"is not unknown"]
> -- have to use try with inSuffix because of a conflict > -- have to use try with inSuffix because of a conflict
> -- with 'in' in position function > -- with 'in' in position function, and not between
> -- between also has a try in it to deal with 'not' > -- between also has a try in it to deal with 'not'
> -- ambiguity > -- ambiguity
> ++ [E.Postfix $ try inSuffix,E.Postfix betweenSuffix] > ++ [E.Postfix $ try inSuffix,E.Postfix betweenSuffix]
@ -780,8 +780,8 @@ pretty trivial.
> where > where
> ob = SortSpec > ob = SortSpec
> <$> valueExpr > <$> valueExpr
> <*> option Asc (choice [Asc <$ keyword_ "asc" > <*> option DirDefault (choice [Asc <$ keyword_ "asc"
> ,Desc <$ keyword_ "desc"]) > ,Desc <$ keyword_ "desc"])
> <*> option NullsOrderDefault > <*> option NullsOrderDefault
> (keyword_ "nulls" >> > (keyword_ "nulls" >>
> choice [NullsFirst <$ keyword "first" > choice [NullsFirst <$ keyword "first"
@ -833,7 +833,7 @@ and union, etc..
> where > where
> select = keyword_ "select" >> > select = keyword_ "select" >>
> mkSelect > mkSelect
> <$> (fromMaybe All <$> duplicates) > <$> (fromMaybe SQDefault <$> duplicates)
> <*> selectList > <*> selectList
> <*> optionMaybe tableExpression > <*> optionMaybe tableExpression
> mkSelect d sl Nothing = > mkSelect d sl Nothing =
@ -877,7 +877,7 @@ be in the public syntax?
> [Union <$ keyword_ "union" > [Union <$ keyword_ "union"
> ,Intersect <$ keyword_ "intersect" > ,Intersect <$ keyword_ "intersect"
> ,Except <$ keyword_ "except"] <?> "set operator") > ,Except <$ keyword_ "except"] <?> "set operator")
> <*> (fromMaybe Distinct <$> duplicates) > <*> (fromMaybe SQDefault <$> duplicates)
> <*> option Respectively > <*> option Respectively
> (Corresponding <$ keyword_ "corresponding") > (Corresponding <$ keyword_ "corresponding")
> <*> queryExpr) > <*> queryExpr)

View file

@ -54,9 +54,9 @@ which have been changed to try to improve the layout of the output.
> valueExpr (AggregateApp f d es od) = > valueExpr (AggregateApp f d es od) =
> name f > name f
> <> parens ((case d of > <> parens ((case d of
> Just Distinct -> text "distinct" > Distinct -> text "distinct"
> Just All -> text "all" > All -> text "all"
> Nothing -> empty) > SQDefault -> empty)
> <+> commaSep (map valueExpr es) > <+> commaSep (map valueExpr es)
> <+> orderBy od) > <+> orderBy od)
@ -214,7 +214,8 @@ which have been changed to try to improve the layout of the output.
> queryExpr (Select d sl fr wh gb hv od off fe) = > queryExpr (Select d sl fr wh gb hv od off fe) =
> sep [text "select" > sep [text "select"
> ,case d of > ,case d of
> All -> empty > SQDefault -> empty
> All -> text "all"
> Distinct -> text "distinct" > Distinct -> text "distinct"
> ,nest 7 $ sep [selectList sl] > ,nest 7 $ sep [selectList sl]
> ,from fr > ,from fr
@ -233,8 +234,9 @@ which have been changed to try to improve the layout of the output.
> Intersect -> "intersect" > Intersect -> "intersect"
> Except -> "except") > Except -> "except")
> <+> case d of > <+> case d of
> SQDefault -> empty
> All -> text "all" > All -> text "all"
> Distinct -> empty -- text "distinct" > Distinct -> text "distinct"
> <+> case c of > <+> case c of
> Corresponding -> text "corresponding" > Corresponding -> text "corresponding"
> Respectively -> empty > Respectively -> empty
@ -320,7 +322,10 @@ which have been changed to try to improve the layout of the output.
> where > where
> f (SortSpec e d n) = > f (SortSpec e d n) =
> valueExpr e > valueExpr e
> <+> (if d == Asc then empty else text "desc") > <+> (case d of
> Asc -> text "asc"
> Desc -> text "desc"
> DirDefault -> empty)
> <+> (case n of > <+> (case n of
> NullsOrderDefault -> empty > NullsOrderDefault -> empty
> NullsFirst -> text "nulls" <+> text "first" > NullsFirst -> text "nulls" <+> text "first"

View file

@ -71,7 +71,7 @@
> -- order by, to regular function application > -- order by, to regular function application
> | AggregateApp > | AggregateApp
> {aggName :: Name -- ^ aggregate function name > {aggName :: Name -- ^ aggregate function name
> ,aggDistinct :: Maybe SetQuantifier -- ^ distinct > ,aggDistinct :: SetQuantifier -- ^ distinct
> ,aggArgs :: [ValueExpr]-- ^ args > ,aggArgs :: [ValueExpr]-- ^ args
> ,aggOrderBy :: [SortSpec] -- ^ order by > ,aggOrderBy :: [SortSpec] -- ^ order by
> } > }
@ -265,7 +265,7 @@ I'm not sure if this is valid syntax or not.
> -- expr values a little easier. It is defined like this: > -- expr values a little easier. It is defined like this:
> -- > --
> -- > makeSelect :: QueryExpr > -- > makeSelect :: QueryExpr
> -- > makeSelect = Select {qeSetQuantifier = All > -- > makeSelect = Select {qeSetQuantifier = SQDefault
> -- > ,qeSelectList = [] > -- > ,qeSelectList = []
> -- > ,qeFrom = [] > -- > ,qeFrom = []
> -- > ,qeWhere = Nothing > -- > ,qeWhere = Nothing
@ -276,7 +276,7 @@ I'm not sure if this is valid syntax or not.
> -- > ,qeFetchFirst = Nothing} > -- > ,qeFetchFirst = Nothing}
> makeSelect :: QueryExpr > makeSelect :: QueryExpr
> makeSelect = Select {qeSetQuantifier = All > makeSelect = Select {qeSetQuantifier = SQDefault
> ,qeSelectList = [] > ,qeSelectList = []
> ,qeFrom = [] > ,qeFrom = []
> ,qeWhere = Nothing > ,qeWhere = Nothing
@ -290,10 +290,10 @@ I'm not sure if this is valid syntax or not.
> -- | Represents the Distinct or All keywords, which can be used > -- | Represents the Distinct or All keywords, which can be used
> -- before a select list, in an aggregate/window function > -- before a select list, in an aggregate/window function
> -- application, or in a query expression set operator. > -- application, or in a query expression set operator.
> data SetQuantifier = Distinct | All deriving (Eq,Show,Read,Data,Typeable) > data SetQuantifier = SQDefault | Distinct | All deriving (Eq,Show,Read,Data,Typeable)
> -- | The direction for a column in order by. > -- | The direction for a column in order by.
> data Direction = Asc | Desc deriving (Eq,Show,Read,Data,Typeable) > data Direction = DirDefault | Asc | Desc deriving (Eq,Show,Read,Data,Typeable)
> -- | Query expression set operators. > -- | Query expression set operators.
> data CombineOp = Union | Except | Intersect deriving (Eq,Show,Read,Data,Typeable) > data CombineOp = Union | Except | Intersect deriving (Eq,Show,Read,Data,Typeable)
> -- | Corresponding, an option for the set operators. > -- | Corresponding, an option for the set operators.

1
TODO
View file

@ -114,6 +114,7 @@ multi word type names: left factor
quantified comparison: left factor with normal comparison quantified comparison: left factor with normal comparison
multi word operator names in expressions multi word operator names in expressions
hardcode all the symbols in the symbol parser/split? hardcode all the symbols in the symbol parser/split?
left factor the not in 'not in' and 'not between', maybe others
future big feature summary: future big feature summary:

View file

@ -33,7 +33,7 @@ Some tests for parsing full queries.
> ,qeGroupBy = [SimpleGroup $ Iden "a"] > ,qeGroupBy = [SimpleGroup $ Iden "a"]
> ,qeHaving = Just $ BinOp (App "count" [NumLit "1"]) > ,qeHaving = Just $ BinOp (App "count" [NumLit "1"])
> ">" (NumLit "5") > ">" (NumLit "5")
> ,qeOrderBy = [SortSpec (Iden "s") Asc NullsOrderDefault] > ,qeOrderBy = [SortSpec (Iden "s") DirDefault NullsOrderDefault]
> } > }
> ) > )
> ] > ]

View file

@ -30,7 +30,7 @@ These are a few misc tests which don't fit anywhere else.
> duplicates :: TestItem > duplicates :: TestItem
> duplicates = Group "duplicates" $ map (uncurry TestQueryExpr) > duplicates = Group "duplicates" $ map (uncurry TestQueryExpr)
> [("select a from t" ,ms All) > [("select a from t" ,ms SQDefault)
> ,("select all a from t" ,ms All) > ,("select all a from t" ,ms All)
> ,("select distinct a from t", ms Distinct) > ,("select distinct a from t", ms Distinct)
> ] > ]
@ -96,11 +96,11 @@ These are a few misc tests which don't fit anywhere else.
> orderBy :: TestItem > orderBy :: TestItem
> orderBy = Group "orderBy" $ map (uncurry TestQueryExpr) > orderBy = Group "orderBy" $ map (uncurry TestQueryExpr)
> [("select a from t order by a" > [("select a from t order by a"
> ,ms [SortSpec (Iden "a") Asc NullsOrderDefault]) > ,ms [SortSpec (Iden "a") DirDefault NullsOrderDefault])
> ,("select a from t order by a, b" > ,("select a from t order by a, b"
> ,ms [SortSpec (Iden "a") Asc NullsOrderDefault > ,ms [SortSpec (Iden "a") DirDefault NullsOrderDefault
> ,SortSpec (Iden "b") Asc NullsOrderDefault]) > ,SortSpec (Iden "b") DirDefault NullsOrderDefault])
> ,("select a from t order by a asc" > ,("select a from t order by a asc"
> ,ms [SortSpec (Iden "a") Asc NullsOrderDefault]) > ,ms [SortSpec (Iden "a") Asc NullsOrderDefault])
@ -144,10 +144,10 @@ These are a few misc tests which don't fit anywhere else.
> combos :: TestItem > combos :: TestItem
> combos = Group "combos" $ map (uncurry TestQueryExpr) > combos = Group "combos" $ map (uncurry TestQueryExpr)
> [("select a from t union select b from u" > [("select a from t union select b from u"
> ,CombineQueryExpr ms1 Union Distinct Respectively ms2) > ,CombineQueryExpr ms1 Union SQDefault Respectively ms2)
> ,("select a from t intersect select b from u" > ,("select a from t intersect select b from u"
> ,CombineQueryExpr ms1 Intersect Distinct Respectively ms2) > ,CombineQueryExpr ms1 Intersect SQDefault Respectively ms2)
> ,("select a from t except all select b from u" > ,("select a from t except all select b from u"
> ,CombineQueryExpr ms1 Except All Respectively ms2) > ,CombineQueryExpr ms1 Except All Respectively ms2)
@ -160,8 +160,8 @@ These are a few misc tests which don't fit anywhere else.
> -- TODO: union should be left associative. I think the others also > -- TODO: union should be left associative. I think the others also
> -- so this needs to be fixed (new optionSuffix variation which > -- so this needs to be fixed (new optionSuffix variation which
> -- handles this) > -- handles this)
> ,CombineQueryExpr ms1 Union Distinct Respectively > ,CombineQueryExpr ms1 Union SQDefault Respectively
> (CombineQueryExpr ms1 Union Distinct Respectively ms1)) > (CombineQueryExpr ms1 Union SQDefault Respectively ms1))
> ] > ]
> where > where
> ms1 = makeSelect > ms1 = makeSelect

View file

@ -1794,7 +1794,7 @@ operator is ||, same as the string concatenation operator.
> ,ArrayCtor (makeSelect > ,ArrayCtor (makeSelect
> {qeSelectList = [(Star,Nothing)] > {qeSelectList = [(Star,Nothing)]
> ,qeFrom = [TRSimple "t"] > ,qeFrom = [TRSimple "t"]
> ,qeOrderBy = [SortSpec (Iden "a") Asc NullsOrderDefault] })) > ,qeOrderBy = [SortSpec (Iden "a") DirDefault NullsOrderDefault] }))
> ] > ]
== 6.37 <multiset value expression> (p286) == 6.37 <multiset value expression> (p286)
@ -2911,22 +2911,22 @@ TODO: review sort specifications
> sortSpecificationList :: TestItem > sortSpecificationList :: TestItem
> sortSpecificationList = Group "sort specification list" $ map (uncurry TestQueryExpr) > sortSpecificationList = Group "sort specification list" $ map (uncurry TestQueryExpr)
> [("select * from t order by a" > [("select * from t order by a"
> ,qe {qeOrderBy = [SortSpec (Iden "a") Asc NullsOrderDefault]}) > ,qe {qeOrderBy = [SortSpec (Iden "a") DirDefault NullsOrderDefault]})
> ,("select * from t order by a,b" > ,("select * from t order by a,b"
> ,qe {qeOrderBy = [SortSpec (Iden "a") Asc NullsOrderDefault > ,qe {qeOrderBy = [SortSpec (Iden "a") DirDefault NullsOrderDefault
> ,SortSpec (Iden "b") Asc NullsOrderDefault]}) > ,SortSpec (Iden "b") DirDefault NullsOrderDefault]})
> ,("select * from t order by a asc,b" > ,("select * from t order by a asc,b"
> ,qe {qeOrderBy = [SortSpec (Iden "a") Asc NullsOrderDefault > ,qe {qeOrderBy = [SortSpec (Iden "a") Asc NullsOrderDefault
> ,SortSpec (Iden "b") Asc NullsOrderDefault]}) > ,SortSpec (Iden "b") DirDefault NullsOrderDefault]})
> ,("select * from t order by a desc,b" > ,("select * from t order by a desc,b"
> ,qe {qeOrderBy = [SortSpec (Iden "a") Desc NullsOrderDefault > ,qe {qeOrderBy = [SortSpec (Iden "a") Desc NullsOrderDefault
> ,SortSpec (Iden "b") Asc NullsOrderDefault]}) > ,SortSpec (Iden "b") DirDefault NullsOrderDefault]})
> ,("select * from t order by a collate x desc,b" > ,("select * from t order by a collate x desc,b"
> ,qe {qeOrderBy = [SortSpec (Collate (Iden "a") "x") Desc NullsOrderDefault > ,qe {qeOrderBy = [SortSpec (Collate (Iden "a") "x") Desc NullsOrderDefault
> ,SortSpec (Iden "b") Asc NullsOrderDefault]}) > ,SortSpec (Iden "b") DirDefault NullsOrderDefault]})
> ,("select * from t order by 1,2" > ,("select * from t order by 1,2"
> ,qe {qeOrderBy = [SortSpec (NumLit "1") Asc NullsOrderDefault > ,qe {qeOrderBy = [SortSpec (NumLit "1") DirDefault NullsOrderDefault
> ,SortSpec (NumLit "2") Asc NullsOrderDefault]}) > ,SortSpec (NumLit "2") DirDefault NullsOrderDefault]})
> ] > ]
> where > where
> qe = makeSelect > qe = makeSelect

View file

@ -330,14 +330,14 @@ target_string
> [("count(*)",App "count" [Star]) > [("count(*)",App "count" [Star])
> ,("sum(a order by a)" > ,("sum(a order by a)"
> ,AggregateApp "sum" Nothing [Iden "a"] > ,AggregateApp "sum" SQDefault [Iden "a"]
> [SortSpec (Iden "a") Asc NullsOrderDefault]) > [SortSpec (Iden "a") DirDefault NullsOrderDefault])
> ,("sum(all a)" > ,("sum(all a)"
> ,AggregateApp "sum" (Just All) [Iden "a"] []) > ,AggregateApp "sum" All [Iden "a"] [])
> ,("count(distinct a)" > ,("count(distinct a)"
> ,AggregateApp "count" (Just Distinct) [Iden "a"] []) > ,AggregateApp "count" Distinct [Iden "a"] [])
> ] > ]
> windowFunctions :: TestItem > windowFunctions :: TestItem
@ -353,46 +353,46 @@ target_string
> ,("sum(a) over (order by b)" > ,("sum(a) over (order by b)"
> ,WindowApp "sum" [Iden "a"] [] > ,WindowApp "sum" [Iden "a"] []
> [SortSpec (Iden "b") Asc NullsOrderDefault] Nothing) > [SortSpec (Iden "b") DirDefault NullsOrderDefault] Nothing)
> ,("sum(a) over (order by b desc,c)" > ,("sum(a) over (order by b desc,c)"
> ,WindowApp "sum" [Iden "a"] [] > ,WindowApp "sum" [Iden "a"] []
> [SortSpec (Iden "b") Desc NullsOrderDefault > [SortSpec (Iden "b") Desc NullsOrderDefault
> ,SortSpec (Iden "c") Asc NullsOrderDefault] Nothing) > ,SortSpec (Iden "c") DirDefault NullsOrderDefault] Nothing)
> ,("sum(a) over (partition by b order by c)" > ,("sum(a) over (partition by b order by c)"
> ,WindowApp "sum" [Iden "a"] [Iden "b"] > ,WindowApp "sum" [Iden "a"] [Iden "b"]
> [SortSpec (Iden "c") Asc NullsOrderDefault] Nothing) > [SortSpec (Iden "c") DirDefault NullsOrderDefault] Nothing)
> ,("sum(a) over (partition by b order by c range unbounded preceding)" > ,("sum(a) over (partition by b order by c range unbounded preceding)"
> ,WindowApp "sum" [Iden "a"] [Iden "b"] > ,WindowApp "sum" [Iden "a"] [Iden "b"]
> [SortSpec (Iden "c") Asc NullsOrderDefault] > [SortSpec (Iden "c") DirDefault NullsOrderDefault]
> $ Just $ FrameFrom FrameRange UnboundedPreceding) > $ Just $ FrameFrom FrameRange UnboundedPreceding)
> ,("sum(a) over (partition by b order by c range 5 preceding)" > ,("sum(a) over (partition by b order by c range 5 preceding)"
> ,WindowApp "sum" [Iden "a"] [Iden "b"] > ,WindowApp "sum" [Iden "a"] [Iden "b"]
> [SortSpec (Iden "c") Asc NullsOrderDefault] > [SortSpec (Iden "c") DirDefault NullsOrderDefault]
> $ Just $ FrameFrom FrameRange $ Preceding (NumLit "5")) > $ Just $ FrameFrom FrameRange $ Preceding (NumLit "5"))
> ,("sum(a) over (partition by b order by c range current row)" > ,("sum(a) over (partition by b order by c range current row)"
> ,WindowApp "sum" [Iden "a"] [Iden "b"] > ,WindowApp "sum" [Iden "a"] [Iden "b"]
> [SortSpec (Iden "c") Asc NullsOrderDefault] > [SortSpec (Iden "c") DirDefault NullsOrderDefault]
> $ Just $ FrameFrom FrameRange Current) > $ Just $ FrameFrom FrameRange Current)
> ,("sum(a) over (partition by b order by c rows 5 following)" > ,("sum(a) over (partition by b order by c rows 5 following)"
> ,WindowApp "sum" [Iden "a"] [Iden "b"] > ,WindowApp "sum" [Iden "a"] [Iden "b"]
> [SortSpec (Iden "c") Asc NullsOrderDefault] > [SortSpec (Iden "c") DirDefault NullsOrderDefault]
> $ Just $ FrameFrom FrameRows $ Following (NumLit "5")) > $ Just $ FrameFrom FrameRows $ Following (NumLit "5"))
> ,("sum(a) over (partition by b order by c range unbounded following)" > ,("sum(a) over (partition by b order by c range unbounded following)"
> ,WindowApp "sum" [Iden "a"] [Iden "b"] > ,WindowApp "sum" [Iden "a"] [Iden "b"]
> [SortSpec (Iden "c") Asc NullsOrderDefault] > [SortSpec (Iden "c") DirDefault NullsOrderDefault]
> $ Just $ FrameFrom FrameRange UnboundedFollowing) > $ Just $ FrameFrom FrameRange UnboundedFollowing)
> ,("sum(a) over (partition by b order by c \n\ > ,("sum(a) over (partition by b order by c \n\
> \range between 5 preceding and 5 following)" > \range between 5 preceding and 5 following)"
> ,WindowApp "sum" [Iden "a"] [Iden "b"] > ,WindowApp "sum" [Iden "a"] [Iden "b"]
> [SortSpec (Iden "c") Asc NullsOrderDefault] > [SortSpec (Iden "c") DirDefault NullsOrderDefault]
> $ Just $ FrameBetween FrameRange > $ Just $ FrameBetween FrameRange
> (Preceding (NumLit "5")) > (Preceding (NumLit "5"))
> (Following (NumLit "5"))) > (Following (NumLit "5")))