1
Fork 0

adjust makeSelect helper to be new type, lib and tests now compile without any warnings

This commit is contained in:
Jake Wheat 2024-01-11 14:45:20 +00:00
parent a3d1ba7e5c
commit 858c7723b0
14 changed files with 274 additions and 243 deletions

View file

@ -235,7 +235,6 @@ import Language.SQL.SimpleSQL.Syntax
import Language.SQL.SimpleSQL.Dialect import Language.SQL.SimpleSQL.Dialect
import qualified Language.SQL.SimpleSQL.Lex as L import qualified Language.SQL.SimpleSQL.Lex as L
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
-- = Public API -- = Public API
@ -1522,7 +1521,7 @@ queryExpr = E.makeExprParser qeterm qeOpTable
<*> selectList <*> selectList
<*> (optional tableExpression) <?> "table expression" <*> (optional tableExpression) <?> "table expression"
mkSelect d sl Nothing = mkSelect d sl Nothing =
makeSelect{qeSetQuantifier = d, qeSelectList = sl} toQueryExpr $ makeSelect {msSetQuantifier = d, msSelectList = sl}
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"

View file

@ -23,7 +23,6 @@ module Language.SQL.SimpleSQL.Syntax
,OdbcLiteralType(..) ,OdbcLiteralType(..)
-- * Query expressions -- * Query expressions
,QueryExpr(..) ,QueryExpr(..)
,makeSelect
,SetOperatorName(..) ,SetOperatorName(..)
,Corresponding(..) ,Corresponding(..)
,Alias(..) ,Alias(..)
@ -60,6 +59,10 @@ module Language.SQL.SimpleSQL.Syntax
,GrantOptionFor(..) ,GrantOptionFor(..)
-- * Comment -- * Comment
,Comment(..) ,Comment(..)
,makeSelect
,toQueryExpr
,MakeSelect(..)
) where ) where
import Data.Text (Text) import Data.Text (Text)
@ -377,31 +380,6 @@ TODO: add queryexpr parens to deal with e.g.
I'm not sure if this is valid syntax or not. I'm not sure if this is valid syntax or not.
-} -}
-- | Helper/'default' value for query exprs to make creating query
-- expr values a little easier. It is defined like this:
--
-- > makeSelect :: QueryExpr
-- > makeSelect = Select {qeSetQuantifier = SQDefault
-- > ,qeSelectList = []
-- > ,qeFrom = []
-- > ,qeWhere = Nothing
-- > ,qeGroupBy = []
-- > ,qeHaving = Nothing
-- > ,qeOrderBy = []
-- > ,qeOffset = Nothing
-- > ,qeFetchFirst = Nothing}
makeSelect :: QueryExpr
makeSelect = Select {qeSetQuantifier = SQDefault
,qeSelectList = []
,qeFrom = []
,qeWhere = Nothing
,qeGroupBy = []
,qeHaving = Nothing
,qeOrderBy = []
,qeOffset = Nothing
,qeFetchFirst = Nothing}
-- | 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.
@ -744,3 +722,50 @@ data PrivilegeAction =
newtype Comment = BlockComment Text newtype Comment = BlockComment Text
deriving (Eq,Show,Read,Data,Typeable) deriving (Eq,Show,Read,Data,Typeable)
data MakeSelect
= MakeSelect
{msSetQuantifier :: SetQuantifier
,msSelectList :: [(ScalarExpr,Maybe Name)]
,msFrom :: [TableRef]
,msWhere :: Maybe ScalarExpr
,msGroupBy :: [GroupingExpr]
,msHaving :: Maybe ScalarExpr
,msOrderBy :: [SortSpec]
,msOffset :: Maybe ScalarExpr
,msFetchFirst :: Maybe ScalarExpr
}
-- | Helper/'default' value for query exprs to make creating query
-- expr values a little easier. It is defined like this:
--
-- > makeSelect :: MakeSelect
-- > makeSelect
-- > = MakeSelect
-- > {msSetQuantifier = SQDefault
-- > ,msSelectList = []
-- > ,msFrom = []
-- > ,msWhere = Nothing
-- > ,msGroupBy = []
-- > ,msHaving = Nothing
-- > ,msOrderBy = []
-- > ,msOffset = Nothing
-- > ,msFetchFirst = Nothing}
-- >
-- > Example, to create a select query expression with a select list 'sl':
-- > toQueryExpr $ makeSelect {msSelectList = sl}
makeSelect :: MakeSelect
makeSelect
= MakeSelect
{msSetQuantifier = SQDefault
,msSelectList = []
,msFrom = []
,msWhere = Nothing
,msGroupBy = []
,msHaving = Nothing
,msOrderBy = []
,msOffset = Nothing
,msFetchFirst = Nothing}
toQueryExpr :: MakeSelect -> QueryExpr
toQueryExpr (MakeSelect q sl f w g h o ff fetch) = Select q sl f w g h o ff fetch

View file

@ -9,6 +9,8 @@
parses from and pretty prints to strict Text parses from and pretty prints to strict Text
use strict Text instead of String everywhere use strict Text instead of String everywhere
tested with latest three main ghc releases (9.8.1, 9.6.4, and 9.4.8) and stack lts 22.5 tested with latest three main ghc releases (9.8.1, 9.6.4, and 9.4.8) and stack lts 22.5
the makeSelect helper is now a distinct type, code using it will need some trivial
tweaks, this is change so that code using makeSelect doesn't emit warnings
0.6.1 added odbc handling to sqlsqerver dialect 0.6.1 added odbc handling to sqlsqerver dialect
added sqlserver dialect case for convert function added sqlserver dialect case for convert function
0.6.0 0.6.0

View file

@ -11,9 +11,9 @@ import Language.SQL.SimpleSQL.Syntax
fullQueriesTests :: TestItem fullQueriesTests :: TestItem
fullQueriesTests = Group "queries" $ map (uncurry (TestQueryExpr ansi2011)) fullQueriesTests = Group "queries" $ map (uncurry (TestQueryExpr ansi2011))
[("select count(*) from t" [("select count(*) from t"
,makeSelect ,toQueryExpr $ makeSelect
{qeSelectList = [(App [Name Nothing "count"] [Star], Nothing)] {msSelectList = [(App [Name Nothing "count"] [Star], Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]] ,msFrom = [TRSimple [Name Nothing "t"]]
} }
) )
@ -23,18 +23,18 @@ fullQueriesTests = Group "queries" $ map (uncurry (TestQueryExpr ansi2011))
\ group by a\n\ \ group by a\n\
\ having count(1) > 5\n\ \ having count(1) > 5\n\
\ order by s" \ order by s"
,makeSelect ,toQueryExpr $ makeSelect
{qeSelectList = [(Iden [Name Nothing "a"], Nothing) {msSelectList = [(Iden [Name Nothing "a"], Nothing)
,(App [Name Nothing "sum"] ,(App [Name Nothing "sum"]
[BinOp (Iden [Name Nothing "c"]) [BinOp (Iden [Name Nothing "c"])
[Name Nothing "+"] (Iden [Name Nothing "d"])] [Name Nothing "+"] (Iden [Name Nothing "d"])]
,Just $ Name Nothing "s")] ,Just $ Name Nothing "s")]
,qeFrom = [TRSimple [Name Nothing "t"], TRSimple [Name Nothing "u"]] ,msFrom = [TRSimple [Name Nothing "t"], TRSimple [Name Nothing "u"]]
,qeWhere = Just $ BinOp (Iden [Name Nothing "a"]) [Name Nothing ">"] (NumLit "5") ,msWhere = Just $ BinOp (Iden [Name Nothing "a"]) [Name Nothing ">"] (NumLit "5")
,qeGroupBy = [SimpleGroup $ Iden [Name Nothing "a"]] ,msGroupBy = [SimpleGroup $ Iden [Name Nothing "a"]]
,qeHaving = Just $ BinOp (App [Name Nothing "count"] [NumLit "1"]) ,msHaving = Just $ BinOp (App [Name Nothing "count"] [NumLit "1"])
[Name Nothing ">"] (NumLit "5") [Name Nothing ">"] (NumLit "5")
,qeOrderBy = [SortSpec (Iden [Name Nothing "s"]) DirDefault NullsOrderDefault] ,msOrderBy = [SortSpec (Iden [Name Nothing "s"]) DirDefault NullsOrderDefault]
} }
) )
] ]

View file

@ -18,18 +18,18 @@ groupByTests = Group "groupByTests"
simpleGroupBy :: TestItem simpleGroupBy :: TestItem
simpleGroupBy = Group "simpleGroupBy" $ map (uncurry (TestQueryExpr ansi2011)) simpleGroupBy = Group "simpleGroupBy" $ map (uncurry (TestQueryExpr ansi2011))
[("select a,sum(b) from t group by a" [("select a,sum(b) from t group by a"
,makeSelect {qeSelectList = [(Iden [Name Nothing "a"],Nothing) ,toQueryExpr $ makeSelect {msSelectList = [(Iden [Name Nothing "a"],Nothing)
,(App [Name Nothing "sum"] [Iden [Name Nothing "b"]],Nothing)] ,(App [Name Nothing "sum"] [Iden [Name Nothing "b"]],Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]] ,msFrom = [TRSimple [Name Nothing "t"]]
,qeGroupBy = [SimpleGroup $ Iden [Name Nothing "a"]] ,msGroupBy = [SimpleGroup $ Iden [Name Nothing "a"]]
}) })
,("select a,b,sum(c) from t group by a,b" ,("select a,b,sum(c) from t group by a,b"
,makeSelect {qeSelectList = [(Iden [Name Nothing "a"],Nothing) ,toQueryExpr $ makeSelect {msSelectList = [(Iden [Name Nothing "a"],Nothing)
,(Iden [Name Nothing "b"],Nothing) ,(Iden [Name Nothing "b"],Nothing)
,(App [Name Nothing "sum"] [Iden [Name Nothing "c"]],Nothing)] ,(App [Name Nothing "sum"] [Iden [Name Nothing "c"]],Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]] ,msFrom = [TRSimple [Name Nothing "t"]]
,qeGroupBy = [SimpleGroup $ Iden [Name Nothing "a"] ,msGroupBy = [SimpleGroup $ Iden [Name Nothing "a"]
,SimpleGroup $ Iden [Name Nothing "b"]] ,SimpleGroup $ Iden [Name Nothing "b"]]
}) })
] ]
@ -51,9 +51,9 @@ newGroupBy = Group "newGroupBy" $ map (uncurry (TestQueryExpr ansi2011))
,ms [Rollup [SimpleGroup $ Iden [Name Nothing "a"], SimpleGroup $ Iden [Name Nothing "b"]]]) ,ms [Rollup [SimpleGroup $ Iden [Name Nothing "a"], SimpleGroup $ Iden [Name Nothing "b"]]])
] ]
where where
ms g = makeSelect {qeSelectList = [(Star,Nothing)] ms g = toQueryExpr $ makeSelect {msSelectList = [(Star,Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]] ,msFrom = [TRSimple [Name Nothing "t"]]
,qeGroupBy = g} ,msGroupBy = g}
randomGroupBy :: TestItem randomGroupBy :: TestItem
randomGroupBy = Group "randomGroupBy" $ map (ParseQueryExpr ansi2011) randomGroupBy = Group "randomGroupBy" $ map (ParseQueryExpr ansi2011)

View file

@ -30,7 +30,7 @@ backtickQuotes = Group "backtickQuotes" (map (uncurry (TestScalarExpr mysql))
limit :: TestItem limit :: TestItem
limit = Group "queries" ( map (uncurry (TestQueryExpr mysql)) limit = Group "queries" ( map (uncurry (TestQueryExpr mysql))
[("select * from t limit 5" [("select * from t limit 5"
,sel {qeFetchFirst = Just (NumLit "5")} ,toQueryExpr $ sel {msFetchFirst = Just (NumLit "5")}
) )
] ]
++ [ParseQueryExprFails mysql "select a from t fetch next 10 rows only;" ++ [ParseQueryExprFails mysql "select a from t fetch next 10 rows only;"
@ -38,6 +38,6 @@ limit = Group "queries" ( map (uncurry (TestQueryExpr mysql))
) )
where where
sel = makeSelect sel = makeSelect
{qeSelectList = [(Star, Nothing)] {msSelectList = [(Star, Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]] ,msFrom = [TRSimple [Name Nothing "t"]]
} }

View file

@ -32,18 +32,18 @@ odbcTests = Group "odbc" [
,Group "outer join" [ ,Group "outer join" [
TestQueryExpr ansi2011 {diOdbc=True} TestQueryExpr ansi2011 {diOdbc=True}
"select * from {oj t1 left outer join t2 on expr}" "select * from {oj t1 left outer join t2 on expr}"
$ makeSelect $ toQueryExpr $ makeSelect
{qeSelectList = [(Star,Nothing)] {msSelectList = [(Star,Nothing)]
,qeFrom = [TROdbc $ TRJoin (TRSimple [Name Nothing "t1"]) False JLeft (TRSimple [Name Nothing "t2"]) ,msFrom = [TROdbc $ TRJoin (TRSimple [Name Nothing "t1"]) False JLeft (TRSimple [Name Nothing "t2"])
(Just $ JoinOn $ Iden [Name Nothing "expr"])]}] (Just $ JoinOn $ Iden [Name Nothing "expr"])]}]
,Group "check parsing bugs" [ ,Group "check parsing bugs" [
TestQueryExpr ansi2011 {diOdbc=True} TestQueryExpr ansi2011 {diOdbc=True}
"select {fn CONVERT(cint,SQL_BIGINT)} from t;" "select {fn CONVERT(cint,SQL_BIGINT)} from t;"
$ makeSelect $ toQueryExpr $ makeSelect
{qeSelectList = [(OdbcFunc (ap "CONVERT" {msSelectList = [(OdbcFunc (ap "CONVERT"
[iden "cint" [iden "cint"
,iden "SQL_BIGINT"]), Nothing)] ,iden "SQL_BIGINT"]), Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]]}] ,msFrom = [TRSimple [Name Nothing "t"]]}]
] ]
where where
e = TestScalarExpr ansi2011 {diOdbc = True} e = TestScalarExpr ansi2011 {diOdbc = True}

View file

@ -37,38 +37,38 @@ duplicates = Group "duplicates" $ map (uncurry (TestQueryExpr ansi2011))
,("select distinct a from t", ms Distinct) ,("select distinct a from t", ms Distinct)
] ]
where where
ms d = makeSelect ms d = toQueryExpr $ makeSelect
{qeSetQuantifier = d {msSetQuantifier = d
,qeSelectList = [(Iden [Name Nothing "a"],Nothing)] ,msSelectList = [(Iden [Name Nothing "a"],Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]]} ,msFrom = [TRSimple [Name Nothing "t"]]}
selectLists :: TestItem selectLists :: TestItem
selectLists = Group "selectLists" $ map (uncurry (TestQueryExpr ansi2011)) selectLists = Group "selectLists" $ map (uncurry (TestQueryExpr ansi2011))
[("select 1", [("select 1",
makeSelect {qeSelectList = [(NumLit "1",Nothing)]}) toQueryExpr $ makeSelect {msSelectList = [(NumLit "1",Nothing)]})
,("select a" ,("select a"
,makeSelect {qeSelectList = [(Iden [Name Nothing "a"],Nothing)]}) ,toQueryExpr $ makeSelect {msSelectList = [(Iden [Name Nothing "a"],Nothing)]})
,("select a,b" ,("select a,b"
,makeSelect {qeSelectList = [(Iden [Name Nothing "a"],Nothing) ,toQueryExpr $ makeSelect {msSelectList = [(Iden [Name Nothing "a"],Nothing)
,(Iden [Name Nothing "b"],Nothing)]}) ,(Iden [Name Nothing "b"],Nothing)]})
,("select 1+2,3+4" ,("select 1+2,3+4"
,makeSelect {qeSelectList = ,toQueryExpr $ makeSelect {msSelectList =
[(BinOp (NumLit "1") [Name Nothing "+"] (NumLit "2"),Nothing) [(BinOp (NumLit "1") [Name Nothing "+"] (NumLit "2"),Nothing)
,(BinOp (NumLit "3") [Name Nothing "+"] (NumLit "4"),Nothing)]}) ,(BinOp (NumLit "3") [Name Nothing "+"] (NumLit "4"),Nothing)]})
,("select a as a, /*comment*/ b as b" ,("select a as a, /*comment*/ b as b"
,makeSelect {qeSelectList = [(Iden [Name Nothing "a"], Just $ Name Nothing "a") ,toQueryExpr $ makeSelect {msSelectList = [(Iden [Name Nothing "a"], Just $ Name Nothing "a")
,(Iden [Name Nothing "b"], Just $ Name Nothing "b")]}) ,(Iden [Name Nothing "b"], Just $ Name Nothing "b")]})
,("select a a, b b" ,("select a a, b b"
,makeSelect {qeSelectList = [(Iden [Name Nothing "a"], Just $ Name Nothing "a") ,toQueryExpr $ makeSelect {msSelectList = [(Iden [Name Nothing "a"], Just $ Name Nothing "a")
,(Iden [Name Nothing "b"], Just $ Name Nothing "b")]}) ,(Iden [Name Nothing "b"], Just $ Name Nothing "b")]})
,("select a + b * c" ,("select a + b * c"
,makeSelect {qeSelectList = ,toQueryExpr $ makeSelect {msSelectList =
[(BinOp (Iden [Name Nothing "a"]) [Name Nothing "+"] [(BinOp (Iden [Name Nothing "a"]) [Name Nothing "+"]
(BinOp (Iden [Name Nothing "b"]) [Name Nothing "*"] (Iden [Name Nothing "c"])) (BinOp (Iden [Name Nothing "b"]) [Name Nothing "*"] (Iden [Name Nothing "c"]))
,Nothing)]}) ,Nothing)]})
@ -78,19 +78,19 @@ selectLists = Group "selectLists" $ map (uncurry (TestQueryExpr ansi2011))
whereClause :: TestItem whereClause :: TestItem
whereClause = Group "whereClause" $ map (uncurry (TestQueryExpr ansi2011)) whereClause = Group "whereClause" $ map (uncurry (TestQueryExpr ansi2011))
[("select a from t where a = 5" [("select a from t where a = 5"
,makeSelect {qeSelectList = [(Iden [Name Nothing "a"],Nothing)] ,toQueryExpr $ makeSelect {msSelectList = [(Iden [Name Nothing "a"],Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]] ,msFrom = [TRSimple [Name Nothing "t"]]
,qeWhere = Just $ BinOp (Iden [Name Nothing "a"]) [Name Nothing "="] (NumLit "5")}) ,msWhere = Just $ BinOp (Iden [Name Nothing "a"]) [Name Nothing "="] (NumLit "5")})
] ]
having :: TestItem having :: TestItem
having = Group "having" $ map (uncurry (TestQueryExpr ansi2011)) having = Group "having" $ map (uncurry (TestQueryExpr ansi2011))
[("select a,sum(b) from t group by a having sum(b) > 5" [("select a,sum(b) from t group by a having sum(b) > 5"
,makeSelect {qeSelectList = [(Iden [Name Nothing "a"],Nothing) ,toQueryExpr $ makeSelect {msSelectList = [(Iden [Name Nothing "a"],Nothing)
,(App [Name Nothing "sum"] [Iden [Name Nothing "b"]],Nothing)] ,(App [Name Nothing "sum"] [Iden [Name Nothing "b"]],Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]] ,msFrom = [TRSimple [Name Nothing "t"]]
,qeGroupBy = [SimpleGroup $ Iden [Name Nothing "a"]] ,msGroupBy = [SimpleGroup $ Iden [Name Nothing "a"]]
,qeHaving = Just $ BinOp (App [Name Nothing "sum"] [Iden [Name Nothing "b"]]) ,msHaving = Just $ BinOp (App [Name Nothing "sum"] [Iden [Name Nothing "b"]])
[Name Nothing ">"] (NumLit "5") [Name Nothing ">"] (NumLit "5")
}) })
] ]
@ -117,9 +117,9 @@ orderBy = Group "orderBy" $ map (uncurry (TestQueryExpr ansi2011))
] ]
where where
ms o = makeSelect {qeSelectList = [(Iden [Name Nothing "a"],Nothing)] ms o = toQueryExpr $ makeSelect {msSelectList = [(Iden [Name Nothing "a"],Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]] ,msFrom = [TRSimple [Name Nothing "t"]]
,qeOrderBy = o} ,msOrderBy = o}
offsetFetch :: TestItem offsetFetch :: TestItem
offsetFetch = Group "offsetFetch" $ map (uncurry (TestQueryExpr ansi2011)) offsetFetch = Group "offsetFetch" $ map (uncurry (TestQueryExpr ansi2011))
@ -138,11 +138,11 @@ offsetFetch = Group "offsetFetch" $ map (uncurry (TestQueryExpr ansi2011))
-- ,ms (Just $ NumLit "5") (Just $ NumLit "10")) -- ,ms (Just $ NumLit "5") (Just $ NumLit "10"))
] ]
where where
ms o l = makeSelect ms o l = toQueryExpr $ makeSelect
{qeSelectList = [(Iden [Name Nothing "a"],Nothing)] {msSelectList = [(Iden [Name Nothing "a"],Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]] ,msFrom = [TRSimple [Name Nothing "t"]]
,qeOffset = o ,msOffset = o
,qeFetchFirst = l} ,msFetchFirst = l}
combos :: TestItem combos :: TestItem
combos = Group "combos" $ map (uncurry (TestQueryExpr ansi2011)) combos = Group "combos" $ map (uncurry (TestQueryExpr ansi2011))
@ -164,12 +164,12 @@ combos = Group "combos" $ map (uncurry (TestQueryExpr ansi2011))
Union SQDefault Respectively mst) Union SQDefault Respectively mst)
] ]
where where
mst = makeSelect mst = toQueryExpr $ makeSelect
{qeSelectList = [(Iden [Name Nothing "a"],Nothing)] {msSelectList = [(Iden [Name Nothing "a"],Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]]} ,msFrom = [TRSimple [Name Nothing "t"]]}
msu = makeSelect msu = toQueryExpr $ makeSelect
{qeSelectList = [(Iden [Name Nothing "b"],Nothing)] {msSelectList = [(Iden [Name Nothing "b"],Nothing)]
,qeFrom = [TRSimple [Name Nothing "u"]]} ,msFrom = [TRSimple [Name Nothing "u"]]}
withQueries :: TestItem withQueries :: TestItem
@ -189,9 +189,9 @@ withQueries = Group "with queries" $ map (uncurry (TestQueryExpr ansi2011))
,With True [(Alias (Name Nothing "u") Nothing, ms1)] ms2) ,With True [(Alias (Name Nothing "u") Nothing, ms1)] ms2)
] ]
where where
ms c t = makeSelect ms c t = toQueryExpr $ makeSelect
{qeSelectList = [(Iden [Name Nothing c],Nothing)] {msSelectList = [(Iden [Name Nothing c],Nothing)]
,qeFrom = [TRSimple [Name Nothing t]]} ,msFrom = [TRSimple [Name Nothing t]]}
ms1 = ms "a" "t" ms1 = ms "a" "t"
ms2 = ms "a" "u" ms2 = ms "a" "u"
ms3 = ms "a" "x" ms3 = ms "a" "x"

View file

@ -17,11 +17,11 @@ queryExprsTests = Group "query exprs" $ map (uncurry (TestStatements ansi2011))
,("select 1;select 1",[ms,ms]) ,("select 1;select 1",[ms,ms])
,(" select 1;select 1; ",[ms,ms]) ,(" select 1;select 1; ",[ms,ms])
,("SELECT CURRENT_TIMESTAMP;" ,("SELECT CURRENT_TIMESTAMP;"
,[SelectStatement $ makeSelect ,[SelectStatement $ toQueryExpr $ makeSelect
{qeSelectList = [(Iden [Name Nothing "CURRENT_TIMESTAMP"],Nothing)]}]) {msSelectList = [(Iden [Name Nothing "CURRENT_TIMESTAMP"],Nothing)]}])
,("SELECT \"CURRENT_TIMESTAMP\";" ,("SELECT \"CURRENT_TIMESTAMP\";"
,[SelectStatement $ makeSelect ,[SelectStatement $ toQueryExpr $ makeSelect
{qeSelectList = [(Iden [Name (Just ("\"","\"")) "CURRENT_TIMESTAMP"],Nothing)]}]) {msSelectList = [(Iden [Name (Just ("\"","\"")) "CURRENT_TIMESTAMP"],Nothing)]}])
] ]
where where
ms = SelectStatement $ makeSelect {qeSelectList = [(NumLit "1",Nothing)]} ms = SelectStatement $ toQueryExpr $ makeSelect {msSelectList = [(NumLit "1",Nothing)]}

View file

@ -184,15 +184,15 @@ sql2011DataManipulationTests = Group "sql 2011 data manipulation tests"
,(TestStatement ansi2011 "insert into t select * from u" ,(TestStatement ansi2011 "insert into t select * from u"
$ Insert [Name Nothing "t"] Nothing $ Insert [Name Nothing "t"] Nothing
$ InsertQuery makeSelect $ InsertQuery $ toQueryExpr $ makeSelect
{qeSelectList = [(Star, Nothing)] {msSelectList = [(Star, Nothing)]
,qeFrom = [TRSimple [Name Nothing "u"]]}) ,msFrom = [TRSimple [Name Nothing "u"]]})
,(TestStatement ansi2011 "insert into t(a,b,c) select * from u" ,(TestStatement ansi2011 "insert into t(a,b,c) select * from u"
$ Insert [Name Nothing "t"] (Just [Name Nothing "a", Name Nothing "b", Name Nothing "c"]) $ Insert [Name Nothing "t"] (Just [Name Nothing "a", Name Nothing "b", Name Nothing "c"])
$ InsertQuery makeSelect $ InsertQuery $ toQueryExpr $ makeSelect
{qeSelectList = [(Star, Nothing)] {msSelectList = [(Star, Nothing)]
,qeFrom = [TRSimple [Name Nothing "u"]]}) ,msFrom = [TRSimple [Name Nothing "u"]]})
,(TestStatement ansi2011 "insert into t default values" ,(TestStatement ansi2011 "insert into t default values"
$ Insert [Name Nothing "t"] Nothing DefaultInsertValues) $ Insert [Name Nothing "t"] Nothing DefaultInsertValues)

View file

@ -1528,14 +1528,14 @@ setFunctionSpecification = Group "set function specification"
\ GROUPING(SalesQuota) AS Grouping\n\ \ GROUPING(SalesQuota) AS Grouping\n\
\FROM Sales.SalesPerson\n\ \FROM Sales.SalesPerson\n\
\GROUP BY ROLLUP(SalesQuota);" \GROUP BY ROLLUP(SalesQuota);"
,makeSelect ,toQueryExpr $ makeSelect
{qeSelectList = [(Iden [Name Nothing "SalesQuota"],Nothing) {msSelectList = [(Iden [Name Nothing "SalesQuota"],Nothing)
,(App [Name Nothing "SUM"] [Iden [Name Nothing "SalesYTD"]] ,(App [Name Nothing "SUM"] [Iden [Name Nothing "SalesYTD"]]
,Just (Name Nothing "TotalSalesYTD")) ,Just (Name Nothing "TotalSalesYTD"))
,(App [Name Nothing "GROUPING"] [Iden [Name Nothing "SalesQuota"]] ,(App [Name Nothing "GROUPING"] [Iden [Name Nothing "SalesQuota"]]
,Just (Name Nothing "Grouping"))] ,Just (Name Nothing "Grouping"))]
,qeFrom = [TRSimple [Name Nothing "Sales",Name Nothing "SalesPerson"]] ,msFrom = [TRSimple [Name Nothing "Sales",Name Nothing "SalesPerson"]]
,qeGroupBy = [Rollup [SimpleGroup (Iden [Name Nothing "SalesQuota"])]]}) ,msGroupBy = [Rollup [SimpleGroup (Iden [Name Nothing "SalesQuota"])]]})
] ]
{- {-
@ -2528,14 +2528,14 @@ arrayValueConstructor = Group "array value constructor"
,Array (Iden [Name Nothing "array"]) ,Array (Iden [Name Nothing "array"])
[Iden [Name Nothing "a"], Iden [Name Nothing "b"], Iden [Name Nothing "c"]]) [Iden [Name Nothing "a"], Iden [Name Nothing "b"], Iden [Name Nothing "c"]])
,("array(select * from t)" ,("array(select * from t)"
,ArrayCtor (makeSelect ,ArrayCtor (toQueryExpr $ makeSelect
{qeSelectList = [(Star,Nothing)] {msSelectList = [(Star,Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]]})) ,msFrom = [TRSimple [Name Nothing "t"]]}))
,("array(select * from t order by a)" ,("array(select * from t order by a)"
,ArrayCtor (makeSelect ,ArrayCtor (toQueryExpr $ makeSelect
{qeSelectList = [(Star,Nothing)] {msSelectList = [(Star,Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]] ,msFrom = [TRSimple [Name Nothing "t"]]
,qeOrderBy = [SortSpec (Iden [Name Nothing "a"]) ,msOrderBy = [SortSpec (Iden [Name Nothing "a"])
DirDefault NullsOrderDefault]})) DirDefault NullsOrderDefault]}))
] ]
@ -2625,12 +2625,12 @@ multisetValueConstructor = Group "multiset value constructor"
$ map (uncurry (TestScalarExpr 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 ms)
,("table(select * from t)", MultisetQueryCtor qe) ,("table(select * from t)", MultisetQueryCtor ms)
] ]
where where
qe = makeSelect {qeSelectList = [(Star,Nothing)] ms = toQueryExpr $ makeSelect {msSelectList = [(Star,Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]]} ,msFrom = [TRSimple [Name Nothing "t"]]}
-- = 7 Query expressions -- = 7 Query expressions
@ -2761,9 +2761,9 @@ tableValueConstructor = Group "table value constructor"
,[BinOp (Iden [Name Nothing "a"]) [Name Nothing "+"] ,[BinOp (Iden [Name Nothing "a"]) [Name Nothing "+"]
(Iden [Name Nothing "b"]) (Iden [Name Nothing "b"])
,SubQueryExpr SqSq ,SubQueryExpr SqSq
(makeSelect (toQueryExpr $ makeSelect
{qeSelectList = [(App [Name Nothing "count"] [Star],Nothing)] {msSelectList = [(App [Name Nothing "count"] [Star],Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]]})]]) ,msFrom = [TRSimple [Name Nothing "t"]]})]])
] ]
{- {-
@ -2794,9 +2794,9 @@ fromClause :: TestItem
fromClause = Group "fromClause" fromClause = Group "fromClause"
$ map (uncurry (TestQueryExpr ansi2011)) $ map (uncurry (TestQueryExpr ansi2011))
[("select * from tbl1,tbl2" [("select * from tbl1,tbl2"
,makeSelect ,toQueryExpr $ makeSelect
{qeSelectList = [(Star, Nothing)] {msSelectList = [(Star, Nothing)]
,qeFrom = [TRSimple [Name Nothing "tbl1"], TRSimple [Name Nothing "tbl2"]] ,msFrom = [TRSimple [Name Nothing "tbl1"], TRSimple [Name Nothing "tbl2"]]
})] })]
@ -2810,7 +2810,7 @@ Reference a table.
tableReference :: TestItem tableReference :: TestItem
tableReference = Group "table reference" tableReference = Group "table reference"
$ map (uncurry (TestQueryExpr ansi2011)) $ map (uncurry (TestQueryExpr ansi2011))
[("select * from t", sel) [("select * from t", toQueryExpr sel)
{- {-
<table reference> ::= <table factor> | <joined table> <table reference> ::= <table factor> | <joined table>
@ -2901,16 +2901,16 @@ TODO: only
-- table or query name -- table or query name
,("select * from t u", a sel) ,("select * from t u", toQueryExpr $ a sel)
,("select * from t as u", a sel) ,("select * from t as u", toQueryExpr $ a sel)
,("select * from t u(a,b)", sel1 ) ,("select * from t u(a,b)", toQueryExpr sel1 )
,("select * from t as u(a,b)", sel1) ,("select * from t as u(a,b)", toQueryExpr sel1)
-- derived table TODO: realistic example -- derived table TODO: realistic example
,("select * from (select * from t) u" ,("select * from (select * from t) u"
,a $ sel {qeFrom = [TRQueryExpr sel]}) ,toQueryExpr $ a $ sel {msFrom = [TRQueryExpr $ toQueryExpr sel]})
-- lateral TODO: realistic example -- lateral TODO: realistic example
,("select * from lateral t" ,("select * from lateral t"
,af TRLateral sel) ,toQueryExpr $ af TRLateral sel)
-- TODO: bug, lateral should bind more tightly than the alias -- TODO: bug, lateral should bind more tightly than the alias
--,("select * from lateral t u" --,("select * from lateral t u"
-- ,a $ af sel TRLateral) -- ,a $ af sel TRLateral)
@ -2925,22 +2925,22 @@ TODO: only
-- TODO: make it work -- TODO: make it work
--,("select * from table(a)", undefined) --,("select * from table(a)", undefined)
-- parens -- parens
,("select * from (a join b)", jsel) ,("select * from (a join b)", toQueryExpr jsel)
,("select * from (a join b) u", a jsel) ,("select * from (a join b) u", toQueryExpr $ a jsel)
,("select * from ((a join b)) u", a $ af TRParens jsel) ,("select * from ((a join b)) u", toQueryExpr $ a $ af TRParens jsel)
,("select * from ((a join b) u) u", a $ af TRParens $ a jsel) ,("select * from ((a join b) u) u", toQueryExpr $ a $ af TRParens $ a jsel)
] ]
where where
sel = makeSelect sel = makeSelect
{qeSelectList = [(Star, Nothing)] {msSelectList = [(Star, Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]]} ,msFrom = [TRSimple [Name Nothing "t"]]}
af f s = s {qeFrom = map f (qeFrom s)} af f s = s {msFrom = map f (msFrom s)}
a s = af (\x -> TRAlias x $ Alias (Name Nothing "u") Nothing) s a s = af (\x -> TRAlias x $ Alias (Name Nothing "u") Nothing) s
sel1 = makeSelect sel1 = makeSelect
{qeSelectList = [(Star, Nothing)] {msSelectList = [(Star, Nothing)]
,qeFrom = [TRAlias (TRSimple [Name Nothing "t"]) ,msFrom = [TRAlias (TRSimple [Name Nothing "t"])
$ Alias (Name Nothing "u") $ Just [Name Nothing "a", Name Nothing "b"]]} $ Alias (Name Nothing "u") $ Just [Name Nothing "a", Name Nothing "b"]]}
jsel = sel {qeFrom = jsel = sel {msFrom =
[TRParens $ TRJoin (TRSimple [Name Nothing "a"]) [TRParens $ TRJoin (TRSimple [Name Nothing "a"])
False False
JInner JInner
@ -3032,9 +3032,9 @@ joinedTable = Group "joined table"
,sel $ TRJoin a True JFull b Nothing) ,sel $ TRJoin a True JFull b Nothing)
] ]
where where
sel t = makeSelect sel t = toQueryExpr $ makeSelect
{qeSelectList = [(Star, Nothing)] {msSelectList = [(Star, Nothing)]
,qeFrom = [t]} ,msFrom = [t]}
a = TRSimple [Name Nothing "a"] a = TRSimple [Name Nothing "a"]
b = TRSimple [Name Nothing "b"] b = TRSimple [Name Nothing "b"]
@ -3055,10 +3055,10 @@ whereClause :: TestItem
whereClause = Group "where clause" whereClause = Group "where clause"
$ map (uncurry (TestQueryExpr ansi2011)) $ map (uncurry (TestQueryExpr ansi2011))
[("select * from t where a = 5" [("select * from t where a = 5"
,makeSelect ,toQueryExpr $ makeSelect
{qeSelectList = [(Star,Nothing)] {msSelectList = [(Star,Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]] ,msFrom = [TRSimple [Name Nothing "t"]]
,qeWhere = Just $ BinOp (Iden [Name Nothing "a"]) [Name Nothing "="] (NumLit "5")})] ,msWhere = Just $ BinOp (Iden [Name Nothing "a"]) [Name Nothing "="] (NumLit "5")})]
{- {-
== 7.9 <group by clause> == 7.9 <group by clause>
@ -3117,11 +3117,11 @@ groupByClause :: TestItem
groupByClause = Group "group by clause" groupByClause = Group "group by clause"
$ map (uncurry (TestQueryExpr ansi2011)) $ map (uncurry (TestQueryExpr ansi2011))
[("select a,sum(x) from t group by a" [("select a,sum(x) from t group by a"
,qe [SimpleGroup $ Iden [Name Nothing "a"]]) ,toQueryExpr $ ms [SimpleGroup $ Iden [Name Nothing "a"]])
,("select a,sum(x) from t group by a collate c" ,("select a,sum(x) from t group by a collate c"
,qe [SimpleGroup $ Collate (Iden [Name Nothing "a"]) [Name Nothing "c"]]) ,toQueryExpr $ ms [SimpleGroup $ Collate (Iden [Name Nothing "a"]) [Name Nothing "c"]])
,("select a,b,sum(x) from t group by a,b" ,("select a,b,sum(x) from t group by a,b"
,qex [SimpleGroup $ Iden [Name Nothing "a"] ,toQueryExpr $ msx [SimpleGroup $ Iden [Name Nothing "a"]
,SimpleGroup $ Iden [Name Nothing "b"]]) ,SimpleGroup $ Iden [Name Nothing "b"]])
-- todo: group by set quantifier -- todo: group by set quantifier
--,("select a,sum(x) from t group by distinct a" --,("select a,sum(x) from t group by distinct a"
@ -3129,28 +3129,33 @@ groupByClause = Group "group by clause"
--,("select a,sum(x) from t group by all a" --,("select a,sum(x) from t group by all a"
-- ,undefined) -- ,undefined)
,("select a,b,sum(x) from t group by rollup(a,b)" ,("select a,b,sum(x) from t group by rollup(a,b)"
,qex [Rollup [SimpleGroup $ Iden [Name Nothing "a"] ,toQueryExpr $ msx [Rollup [SimpleGroup $ Iden [Name Nothing "a"]
,SimpleGroup $ Iden [Name Nothing "b"]]]) ,SimpleGroup $ Iden [Name Nothing "b"]]])
,("select a,b,sum(x) from t group by cube(a,b)" ,("select a,b,sum(x) from t group by cube(a,b)"
,qex [Cube [SimpleGroup $ Iden [Name Nothing "a"] ,toQueryExpr $ msx [Cube [SimpleGroup $ Iden [Name Nothing "a"]
,SimpleGroup $ Iden [Name Nothing "b"]]]) ,SimpleGroup $ Iden [Name Nothing "b"]]])
,("select a,b,sum(x) from t group by grouping sets((),(a,b))" ,("select a,b,sum(x) from t group by grouping sets((),(a,b))"
,qex [GroupingSets [GroupingParens [] ,toQueryExpr $ msx [GroupingSets [GroupingParens []
,GroupingParens [SimpleGroup $ Iden [Name Nothing "a"] ,GroupingParens [SimpleGroup $ Iden [Name Nothing "a"]
,SimpleGroup $ Iden [Name Nothing "b"]]]]) ,SimpleGroup $ Iden [Name Nothing "b"]]]])
,("select sum(x) from t group by ()" ,("select sum(x) from t group by ()"
,let x = qe [GroupingParens []] ,toQueryExpr $ makeSelect
in x {qeSelectList = tail $ qeSelectList x}) {msSelectList = [(App [Name Nothing "sum"] [Iden [Name Nothing "x"]], Nothing)]
,msFrom = [TRSimple [Name Nothing "t"]]
,msGroupBy = [GroupingParens []]})
] ]
where where
qe g = makeSelect ms g = makeSelect
{qeSelectList = [(Iden [Name Nothing "a"], Nothing) {msSelectList = [(Iden [Name Nothing "a"], Nothing)
,(App [Name Nothing "sum"] [Iden [Name Nothing "x"]], Nothing)] ,(App [Name Nothing "sum"] [Iden [Name Nothing "x"]], Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]] ,msFrom = [TRSimple [Name Nothing "t"]]
,qeGroupBy = g} ,msGroupBy = g}
qex g = let x = qe g msx g = makeSelect
in x {qeSelectList = let [a,b] = qeSelectList x {msSelectList = [(Iden [Name Nothing "a"], Nothing)
in [a,(Iden [Name Nothing "b"],Nothing),b]} ,(Iden [Name Nothing "b"],Nothing)
,(App [Name Nothing "sum"] [Iden [Name Nothing "x"]], Nothing)]
,msFrom = [TRSimple [Name Nothing "t"]]
,msGroupBy = g}
{- {-
== 7.10 <having clause> == 7.10 <having clause>
@ -3167,12 +3172,12 @@ havingClause :: TestItem
havingClause = Group "having clause" havingClause = Group "having clause"
$ map (uncurry (TestQueryExpr ansi2011)) $ map (uncurry (TestQueryExpr ansi2011))
[("select a,sum(x) from t group by a having sum(x) > 1000" [("select a,sum(x) from t group by a having sum(x) > 1000"
,makeSelect ,toQueryExpr $ makeSelect
{qeSelectList = [(Iden [Name Nothing "a"], Nothing) {msSelectList = [(Iden [Name Nothing "a"], Nothing)
,(App [Name Nothing "sum"] [Iden [Name Nothing "x"]], Nothing)] ,(App [Name Nothing "sum"] [Iden [Name Nothing "x"]], Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]] ,msFrom = [TRSimple [Name Nothing "t"]]
,qeGroupBy = [SimpleGroup $ Iden [Name Nothing "a"]] ,msGroupBy = [SimpleGroup $ Iden [Name Nothing "a"]]
,qeHaving = Just $ BinOp (App [Name Nothing "sum"] [Iden [Name Nothing "x"]]) ,msHaving = Just $ BinOp (App [Name Nothing "sum"] [Iden [Name Nothing "x"]])
[Name Nothing ">"] [Name Nothing ">"]
(NumLit "1000")}) (NumLit "1000")})
] ]
@ -3293,27 +3298,27 @@ Specify a table derived from the result of a <table expression>.
querySpecification :: TestItem querySpecification :: TestItem
querySpecification = Group "query specification" querySpecification = Group "query specification"
$ map (uncurry (TestQueryExpr ansi2011)) $ map (uncurry (TestQueryExpr ansi2011))
[("select a from t",qe) [("select a from t",toQueryExpr ms)
,("select all a from t",qe {qeSetQuantifier = All}) ,("select all a from t",toQueryExpr $ ms {msSetQuantifier = All})
,("select distinct a from t",qe {qeSetQuantifier = Distinct}) ,("select distinct a from t",toQueryExpr $ ms {msSetQuantifier = Distinct})
,("select * from t", qe {qeSelectList = [(Star,Nothing)]}) ,("select * from t", toQueryExpr $ ms {msSelectList = [(Star,Nothing)]})
,("select a.* from t" ,("select a.* from t"
,qe {qeSelectList = [(BinOp (Iden [Name Nothing "a"]) [Name Nothing "."] Star ,toQueryExpr $ ms {msSelectList = [(BinOp (Iden [Name Nothing "a"]) [Name Nothing "."] Star
,Nothing)]}) ,Nothing)]})
,("select a b from t" ,("select a b from t"
,qe {qeSelectList = [(Iden [Name Nothing "a"], Just $ Name Nothing "b")]}) ,toQueryExpr $ ms {msSelectList = [(Iden [Name Nothing "a"], Just $ Name Nothing "b")]})
,("select a as b from t" ,("select a as b from t"
,qe {qeSelectList = [(Iden [Name Nothing "a"], Just $ Name Nothing "b")]}) ,toQueryExpr $ ms {msSelectList = [(Iden [Name Nothing "a"], Just $ Name Nothing "b")]})
,("select a,b from t" ,("select a,b from t"
,qe {qeSelectList = [(Iden [Name Nothing "a"], Nothing) ,toQueryExpr $ ms {msSelectList = [(Iden [Name Nothing "a"], Nothing)
,(Iden [Name Nothing "b"], Nothing)]}) ,(Iden [Name Nothing "b"], Nothing)]})
-- todo: all field reference alias -- todo: all field reference alias
--,("select * as (a,b) from t",undefined) --,("select * as (a,b) from t",undefined)
] ]
where where
qe = makeSelect ms = makeSelect
{qeSelectList = [(Iden [Name Nothing "a"], Nothing)] {msSelectList = [(Iden [Name Nothing "a"], Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]] ,msFrom = [TRSimple [Name Nothing "t"]]
} }
{- {-
@ -3430,22 +3435,22 @@ orderOffsetFetchQueryExpression = Group "order, offset, fetch query expression"
$ map (uncurry (TestQueryExpr ansi2011)) $ map (uncurry (TestQueryExpr ansi2011))
[-- todo: finish tests for order offset and fetch [-- todo: finish tests for order offset and fetch
("select a from t order by a" ("select a from t order by a"
,qe {qeOrderBy = [SortSpec (Iden [Name Nothing "a"]) ,toQueryExpr $ ms {msOrderBy = [SortSpec (Iden [Name Nothing "a"])
DirDefault NullsOrderDefault]}) DirDefault NullsOrderDefault]})
,("select a from t offset 5 row" ,("select a from t offset 5 row"
,qe {qeOffset = Just $ NumLit "5"}) ,toQueryExpr $ ms {msOffset = Just $ NumLit "5"})
,("select a from t offset 5 rows" ,("select a from t offset 5 rows"
,qe {qeOffset = Just $ NumLit "5"}) ,toQueryExpr $ ms {msOffset = Just $ NumLit "5"})
,("select a from t fetch first 5 row only" ,("select a from t fetch first 5 row only"
,qe {qeFetchFirst = Just $ NumLit "5"}) ,toQueryExpr $ ms {msFetchFirst = Just $ NumLit "5"})
-- todo: support with ties and percent in fetch -- todo: support with ties and percent in fetch
--,("select a from t fetch next 5 rows with ties" --,("select a from t fetch next 5 rows with ties"
--,("select a from t fetch first 5 percent rows only" --,("select a from t fetch first 5 percent rows only"
] ]
where where
qe = makeSelect ms = makeSelect
{qeSelectList = [(Iden [Name Nothing "a"], Nothing)] {msSelectList = [(Iden [Name Nothing "a"], Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]] ,msFrom = [TRSimple [Name Nothing "t"]]
} }
@ -3813,20 +3818,20 @@ quantifiedComparisonPredicate = Group "quantified comparison predicate"
$ map (uncurry (TestScalarExpr 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 ms)
,("a <= some (select * from t)" ,("a <= some (select * from t)"
,QuantifiedComparison (Iden [Name Nothing "a"]) [Name Nothing "<="] CPSome qe) ,QuantifiedComparison (Iden [Name Nothing "a"]) [Name Nothing "<="] CPSome ms)
,("a > all (select * from t)" ,("a > all (select * from t)"
,QuantifiedComparison (Iden [Name Nothing "a"]) [Name Nothing ">"] CPAll qe) ,QuantifiedComparison (Iden [Name Nothing "a"]) [Name Nothing ">"] CPAll ms)
,("(a,b) <> all (select * from t)" ,("(a,b) <> all (select * from t)"
,QuantifiedComparison ,QuantifiedComparison
(SpecialOp [Name Nothing "rowctor"] [Iden [Name Nothing "a"] (SpecialOp [Name Nothing "rowctor"] [Iden [Name Nothing "a"]
,Iden [Name Nothing "b"]]) [Name Nothing "<>"] CPAll qe) ,Iden [Name Nothing "b"]]) [Name Nothing "<>"] CPAll ms)
] ]
where where
qe = makeSelect ms = toQueryExpr $ makeSelect
{qeSelectList = [(Star,Nothing)] {msSelectList = [(Star,Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]]} ,msFrom = [TRSimple [Name Nothing "t"]]}
{- {-
== 8.10 <exists predicate> == 8.10 <exists predicate>
@ -3842,10 +3847,10 @@ existsPredicate = Group "exists predicate"
$ map (uncurry (TestScalarExpr ansi2011)) $ map (uncurry (TestScalarExpr ansi2011))
[("exists(select * from t where a = 4)" [("exists(select * from t where a = 4)"
,SubQueryExpr SqExists ,SubQueryExpr SqExists
$ makeSelect $ toQueryExpr $ makeSelect
{qeSelectList = [(Star,Nothing)] {msSelectList = [(Star,Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]] ,msFrom = [TRSimple [Name Nothing "t"]]
,qeWhere = Just (BinOp (Iden [Name Nothing "a"]) [Name Nothing "="] (NumLit "4")) ,msWhere = Just (BinOp (Iden [Name Nothing "a"]) [Name Nothing "="] (NumLit "4"))
} }
)] )]
@ -3863,10 +3868,10 @@ uniquePredicate = Group "unique predicate"
$ map (uncurry (TestScalarExpr ansi2011)) $ map (uncurry (TestScalarExpr ansi2011))
[("unique(select * from t where a = 4)" [("unique(select * from t where a = 4)"
,SubQueryExpr SqUnique ,SubQueryExpr SqUnique
$ makeSelect $ toQueryExpr $ makeSelect
{qeSelectList = [(Star,Nothing)] {msSelectList = [(Star,Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]] ,msFrom = [TRSimple [Name Nothing "t"]]
,qeWhere = Just (BinOp (Iden [Name Nothing "a"]) [Name Nothing "="] (NumLit "4")) ,msWhere = Just (BinOp (Iden [Name Nothing "a"]) [Name Nothing "="] (NumLit "4"))
} }
)] )]
@ -3902,19 +3907,19 @@ matchPredicate :: TestItem
matchPredicate = Group "match predicate" matchPredicate = Group "match predicate"
$ map (uncurry (TestScalarExpr 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 $ toQueryExpr ms)
,("(a,b) match (select a,b from t)" ,("(a,b) match (select a,b from t)"
,Match (SpecialOp [Name Nothing "rowctor"] ,Match (SpecialOp [Name Nothing "rowctor"]
[Iden [Name Nothing "a"], Iden [Name Nothing "b"]]) False qea) [Iden [Name Nothing "a"], Iden [Name Nothing "b"]]) False $ toQueryExpr msa)
,("(a,b) match unique (select a,b from t)" ,("(a,b) match unique (select a,b from t)"
,Match (SpecialOp [Name Nothing "rowctor"] ,Match (SpecialOp [Name Nothing "rowctor"]
[Iden [Name Nothing "a"], Iden [Name Nothing "b"]]) True qea) [Iden [Name Nothing "a"], Iden [Name Nothing "b"]]) True $ toQueryExpr msa)
] ]
where where
qe = makeSelect ms = makeSelect
{qeSelectList = [(Iden [Name Nothing "a"],Nothing)] {msSelectList = [(Iden [Name Nothing "a"],Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]]} ,msFrom = [TRSimple [Name Nothing "t"]]}
qea = qe {qeSelectList = qeSelectList qe msa = ms {msSelectList = msSelectList ms
<> [(Iden [Name Nothing "b"],Nothing)]} <> [(Iden [Name Nothing "b"],Nothing)]}
{- {-
@ -4480,36 +4485,36 @@ sortSpecificationList :: TestItem
sortSpecificationList = Group "sort specification list" sortSpecificationList = Group "sort specification list"
$ map (uncurry (TestQueryExpr ansi2011)) $ map (uncurry (TestQueryExpr ansi2011))
[("select * from t order by a" [("select * from t order by a"
,qe {qeOrderBy = [SortSpec (Iden [Name Nothing "a"]) ,toQueryExpr $ ms {msOrderBy = [SortSpec (Iden [Name Nothing "a"])
DirDefault NullsOrderDefault]}) DirDefault NullsOrderDefault]})
,("select * from t order by a,b" ,("select * from t order by a,b"
,qe {qeOrderBy = [SortSpec (Iden [Name Nothing "a"]) ,toQueryExpr $ ms {msOrderBy = [SortSpec (Iden [Name Nothing "a"])
DirDefault NullsOrderDefault DirDefault NullsOrderDefault
,SortSpec (Iden [Name Nothing "b"]) ,SortSpec (Iden [Name Nothing "b"])
DirDefault NullsOrderDefault]}) DirDefault NullsOrderDefault]})
,("select * from t order by a asc,b" ,("select * from t order by a asc,b"
,qe {qeOrderBy = [SortSpec (Iden [Name Nothing "a"]) ,toQueryExpr $ ms {msOrderBy = [SortSpec (Iden [Name Nothing "a"])
Asc NullsOrderDefault Asc NullsOrderDefault
,SortSpec (Iden [Name Nothing "b"]) ,SortSpec (Iden [Name Nothing "b"])
DirDefault NullsOrderDefault]}) DirDefault NullsOrderDefault]})
,("select * from t order by a desc,b" ,("select * from t order by a desc,b"
,qe {qeOrderBy = [SortSpec (Iden [Name Nothing "a"]) ,toQueryExpr $ ms {msOrderBy = [SortSpec (Iden [Name Nothing "a"])
Desc NullsOrderDefault Desc NullsOrderDefault
,SortSpec (Iden [Name Nothing "b"]) ,SortSpec (Iden [Name Nothing "b"])
DirDefault NullsOrderDefault]}) 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 ,toQueryExpr $ ms {msOrderBy = [SortSpec
(Collate (Iden [Name Nothing "a"]) [Name Nothing "x"]) (Collate (Iden [Name Nothing "a"]) [Name Nothing "x"])
Desc NullsOrderDefault Desc NullsOrderDefault
,SortSpec (Iden [Name Nothing "b"]) ,SortSpec (Iden [Name Nothing "b"])
DirDefault NullsOrderDefault]}) DirDefault NullsOrderDefault]})
,("select * from t order by 1,2" ,("select * from t order by 1,2"
,qe {qeOrderBy = [SortSpec (NumLit "1") ,toQueryExpr $ ms {msOrderBy = [SortSpec (NumLit "1")
DirDefault NullsOrderDefault DirDefault NullsOrderDefault
,SortSpec (NumLit "2") ,SortSpec (NumLit "2")
DirDefault NullsOrderDefault]}) DirDefault NullsOrderDefault]})
] ]
where where
qe = makeSelect ms = makeSelect
{qeSelectList = [(Star,Nothing)] {msSelectList = [(Star,Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]]} ,msFrom = [TRSimple [Name Nothing "t"]]}

View file

@ -1161,48 +1161,48 @@ defintely skip
,(TestStatement ansi2011 ,(TestStatement ansi2011
"create view v as select * from t" "create view v as select * from t"
$ CreateView False [Name Nothing "v"] Nothing (makeSelect $ CreateView False [Name Nothing "v"] Nothing (toQueryExpr $ makeSelect
{qeSelectList = [(Star, Nothing)] {msSelectList = [(Star, Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]] ,msFrom = [TRSimple [Name Nothing "t"]]
}) Nothing) }) Nothing)
,(TestStatement ansi2011 ,(TestStatement ansi2011
"create recursive view v as select * from t" "create recursive view v as select * from t"
$ CreateView True [Name Nothing "v"] Nothing (makeSelect $ CreateView True [Name Nothing "v"] Nothing (toQueryExpr $ makeSelect
{qeSelectList = [(Star, Nothing)] {msSelectList = [(Star, Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]] ,msFrom = [TRSimple [Name Nothing "t"]]
}) Nothing) }) Nothing)
,(TestStatement ansi2011 ,(TestStatement ansi2011
"create view v(a,b) as select * from t" "create view v(a,b) as select * from t"
$ CreateView False [Name Nothing "v"] (Just [Name Nothing "a", Name Nothing "b"]) $ CreateView False [Name Nothing "v"] (Just [Name Nothing "a", Name Nothing "b"])
(makeSelect (toQueryExpr $ makeSelect
{qeSelectList = [(Star, Nothing)] {msSelectList = [(Star, Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]] ,msFrom = [TRSimple [Name Nothing "t"]]
}) Nothing) }) Nothing)
,(TestStatement ansi2011 ,(TestStatement ansi2011
"create view v as select * from t with check option" "create view v as select * from t with check option"
$ CreateView False [Name Nothing "v"] Nothing (makeSelect $ CreateView False [Name Nothing "v"] Nothing (toQueryExpr $ makeSelect
{qeSelectList = [(Star, Nothing)] {msSelectList = [(Star, Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]] ,msFrom = [TRSimple [Name Nothing "t"]]
}) (Just DefaultCheckOption)) }) (Just DefaultCheckOption))
,(TestStatement ansi2011 ,(TestStatement ansi2011
"create view v as select * from t with cascaded check option" "create view v as select * from t with cascaded check option"
$ CreateView False [Name Nothing "v"] Nothing (makeSelect $ CreateView False [Name Nothing "v"] Nothing (toQueryExpr $ makeSelect
{qeSelectList = [(Star, Nothing)] {msSelectList = [(Star, Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]] ,msFrom = [TRSimple [Name Nothing "t"]]
}) (Just CascadedCheckOption)) }) (Just CascadedCheckOption))
,(TestStatement ansi2011 ,(TestStatement ansi2011
"create view v as select * from t with local check option" "create view v as select * from t with local check option"
$ CreateView False [Name Nothing "v"] Nothing $ CreateView False [Name Nothing "v"] Nothing
(makeSelect (toQueryExpr $ makeSelect
{qeSelectList = [(Star, Nothing)] {msSelectList = [(Star, Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]] ,msFrom = [TRSimple [Name Nothing "t"]]
}) (Just LocalCheckOption)) }) (Just LocalCheckOption))
@ -1429,9 +1429,9 @@ defintely skip
"create assertion t1_not_empty CHECK ((select count(*) from t1) > 0);" "create assertion t1_not_empty CHECK ((select count(*) from t1) > 0);"
$ CreateAssertion [Name Nothing "t1_not_empty"] $ CreateAssertion [Name Nothing "t1_not_empty"]
$ BinOp (SubQueryExpr SqSq $ $ BinOp (SubQueryExpr SqSq $
makeSelect toQueryExpr $ makeSelect
{qeSelectList = [(App [Name Nothing "count"] [Star],Nothing)] {msSelectList = [(App [Name Nothing "count"] [Star],Nothing)]
,qeFrom = [TRSimple [Name Nothing "t1"]] ,msFrom = [TRSimple [Name Nothing "t1"]]
}) })
[Name Nothing ">"] (NumLit "0")) [Name Nothing ">"] (NumLit "0"))

View file

@ -196,9 +196,9 @@ subqueries = Group "unaryOperators" $ map (uncurry (TestScalarExpr ansi2011))
,QuantifiedComparison (Iden [Name Nothing "a"]) [Name Nothing "<="] CPAny ms) ,QuantifiedComparison (Iden [Name Nothing "a"]) [Name Nothing "<="] CPAny ms)
] ]
where where
ms = makeSelect ms = toQueryExpr $ makeSelect
{qeSelectList = [(Iden [Name Nothing "a"],Nothing)] {msSelectList = [(Iden [Name Nothing "a"],Nothing)]
,qeFrom = [TRSimple [Name Nothing "t"]] ,msFrom = [TRSimple [Name Nothing "t"]]
} }
miscOps :: TestItem miscOps :: TestItem

View file

@ -104,5 +104,5 @@ tableRefTests = Group "tableRefTests" $ map (uncurry (TestQueryExpr ansi2011))
False JCross (TRSimple [Name Nothing "v"]) Nothing]) False JCross (TRSimple [Name Nothing "v"]) Nothing])
] ]
where where
ms f = makeSelect {qeSelectList = [(Iden [Name Nothing "a"],Nothing)] ms f = toQueryExpr $ makeSelect {msSelectList = [(Iden [Name Nothing "a"],Nothing)]
,qeFrom = f} ,msFrom = f}