1
Fork 0

get rid of the string overloads in the tests

This commit is contained in:
Jake Wheat 2014-04-19 11:45:45 +03:00
parent fea6e347bd
commit 4fa21ceea8
8 changed files with 314 additions and 331 deletions
tools/Language/SQL/SimpleSQL

View file

@ -2,7 +2,6 @@
These are the tests for parsing focusing on the from part of query
expression
> {-# LANGUAGE OverloadedStrings #-}
> module Language.SQL.SimpleSQL.TableRefs (tableRefTests) where
> import Language.SQL.SimpleSQL.TestTypes
@ -12,96 +11,95 @@ expression
> tableRefTests :: TestItem
> tableRefTests = Group "tableRefTests" $ map (uncurry TestQueryExpr)
> [("select a from t"
> ,ms [TRSimple "t"])
> ,ms [TRSimple [Name "t"]])
> ,("select a from f(a)"
> ,ms [TRFunction "f" [Iden "a"]])
> ,ms [TRFunction [Name "f"] [Iden [Name "a"]]])
> ,("select a from t,u"
> ,ms [TRSimple "t", TRSimple "u"])
> ,ms [TRSimple [Name "t"], TRSimple [Name "u"]])
> ,("select a from s.t"
> ,ms [TRSimple ["s","t"]])
> ,ms [TRSimple [Name "s", Name "t"]])
these lateral queries make no sense but the syntax is valid
> ,("select a from lateral a"
> ,ms [TRLateral $ TRSimple "a"])
> ,ms [TRLateral $ TRSimple [Name "a"]])
> ,("select a from lateral a,b"
> ,ms [TRLateral $ TRSimple "a", TRSimple "b"])
> ,ms [TRLateral $ TRSimple [Name "a"], TRSimple [Name "b"]])
> ,("select a from a, lateral b"
> ,ms [TRSimple "a", TRLateral $ TRSimple "b"])
> ,ms [TRSimple [Name "a"], TRLateral $ TRSimple [Name "b"]])
> ,("select a from a natural join lateral b"
> ,ms [TRJoin (TRSimple "a") True JInner
> (TRLateral $ TRSimple "b")
> ,ms [TRJoin (TRSimple [Name "a"]) True JInner
> (TRLateral $ TRSimple [Name "b"])
> Nothing])
> -- the lateral binds on the outside of the join which is incorrect
> ,("select a from lateral a natural join lateral b"
> ,ms [TRJoin (TRLateral $ TRSimple "a") True JInner
> (TRLateral $ TRSimple "b")
> ,ms [TRJoin (TRLateral $ TRSimple [Name "a"]) True JInner
> (TRLateral $ TRSimple [Name "b"])
> Nothing])
> ,("select a from t inner join u on expr"
> ,ms [TRJoin (TRSimple "t") False JInner (TRSimple "u")
> (Just $ JoinOn $ Iden "expr")])
> ,ms [TRJoin (TRSimple [Name "t"]) False JInner (TRSimple [Name "u"])
> (Just $ JoinOn $ Iden [Name "expr"])])
> ,("select a from t join u on expr"
> ,ms [TRJoin (TRSimple "t") False JInner (TRSimple "u")
> (Just $ JoinOn $ Iden "expr")])
> ,ms [TRJoin (TRSimple [Name "t"]) False JInner (TRSimple [Name "u"])
> (Just $ JoinOn $ Iden [Name "expr"])])
> ,("select a from t left join u on expr"
> ,ms [TRJoin (TRSimple "t") False JLeft (TRSimple "u")
> (Just $ JoinOn $ Iden "expr")])
> ,ms [TRJoin (TRSimple [Name "t"]) False JLeft (TRSimple [Name "u"])
> (Just $ JoinOn $ Iden [Name "expr"])])
> ,("select a from t right join u on expr"
> ,ms [TRJoin (TRSimple "t") False JRight (TRSimple "u")
> (Just $ JoinOn $ Iden "expr")])
> ,ms [TRJoin (TRSimple [Name "t"]) False JRight (TRSimple [Name "u"])
> (Just $ JoinOn $ Iden [Name "expr"])])
> ,("select a from t full join u on expr"
> ,ms [TRJoin (TRSimple "t") False JFull (TRSimple "u")
> (Just $ JoinOn $ Iden "expr")])
> ,ms [TRJoin (TRSimple [Name "t"]) False JFull (TRSimple [Name "u"])
> (Just $ JoinOn $ Iden [Name "expr"])])
> ,("select a from t cross join u"
> ,ms [TRJoin (TRSimple "t") False
> JCross (TRSimple "u") Nothing])
> ,ms [TRJoin (TRSimple [Name "t"]) False
> JCross (TRSimple [Name "u"]) Nothing])
> ,("select a from t natural inner join u"
> ,ms [TRJoin (TRSimple "t") True JInner (TRSimple "u")
> ,ms [TRJoin (TRSimple [Name "t"]) True JInner (TRSimple [Name "u"])
> Nothing])
> ,("select a from t inner join u using(a,b)"
> ,ms [TRJoin (TRSimple "t") False JInner (TRSimple "u")
> (Just $ JoinUsing ["a", "b"])])
> ,ms [TRJoin (TRSimple [Name "t"]) False JInner (TRSimple [Name "u"])
> (Just $ JoinUsing [Name "a", Name "b"])])
> ,("select a from (select a from t)"
> ,ms [TRQueryExpr $ ms [TRSimple "t"]])
> ,ms [TRQueryExpr $ ms [TRSimple [Name "t"]]])
> ,("select a from t as u"
> ,ms [TRAlias (TRSimple "t") (Alias "u" Nothing)])
> ,ms [TRAlias (TRSimple [Name "t"]) (Alias (Name "u") Nothing)])
> ,("select a from t u"
> ,ms [TRAlias (TRSimple "t") (Alias "u" Nothing)])
> ,ms [TRAlias (TRSimple [Name "t"]) (Alias (Name "u") Nothing)])
> ,("select a from t u(b)"
> ,ms [TRAlias (TRSimple "t") (Alias "u" $ Just ["b"])])
> ,ms [TRAlias (TRSimple [Name "t"]) (Alias (Name "u") $ Just [Name "b"])])
> ,("select a from (t cross join u) as u"
> ,ms [TRAlias (TRParens $
> TRJoin (TRSimple "t") False JCross (TRSimple "u") Nothing)
> (Alias "u" Nothing)])
> TRJoin (TRSimple [Name "t"]) False JCross (TRSimple [Name "u"]) Nothing)
> (Alias (Name "u") Nothing)])
> -- todo: not sure if the associativity is correct
> ,("select a from t cross join u cross join v",
> ms [TRJoin
> (TRJoin (TRSimple "t") False
> JCross (TRSimple "u") Nothing)
> False JCross (TRSimple "v") Nothing])
> (TRJoin (TRSimple [Name "t"]) False
> JCross (TRSimple [Name "u"]) Nothing)
> False JCross (TRSimple [Name "v"]) Nothing])
> ]
> where
> ms f = makeSelect {qeSelectList = [(Iden "a",Nothing)]
> ms f = makeSelect {qeSelectList = [(Iden [Name "a"],Nothing)]
> ,qeFrom = f}