Moved non-id/composite pk tests to their corresponding specs and marked failing tests as "pending"

This commit is contained in:
Alberto Valverde 2015-01-05 17:35:00 +01:00
parent 45295039e0
commit 9efc909f49
2 changed files with 137 additions and 114 deletions

View File

@ -523,8 +523,7 @@ unsafeSqlBinOp op (ERaw p1 f1) (ERaw p2 f2) = ERaw Parens f
(b2, vals2) = f2 info
in ( parensM p1 b1 <> op <> parensM p2 b2
, vals1 <> vals2 )
unsafeSqlBinOp op _ _ = error . TL.unpack . TLB.toLazyText $
"Operator '" <> op <> "' not supported on non-id/composite primary keys"
unsafeSqlBinOp _ _ _ = unexpectedCompositeKeyError
{-# INLINE unsafeSqlBinOp #-}
unsafeSqlBinOpList :: TLB.Builder -> TLB.Builder -> SqlExpr (Value a) -> SqlExpr (Value b) -> SqlExpr (Value c)
@ -1094,6 +1093,7 @@ instance PersistEntity a => SqlSelect (SqlExpr (Maybe (Entity a))) (Maybe (Entit
instance PersistField a => SqlSelect (SqlExpr (Value a)) (Value a) where
sqlSelectCols info (ERaw p f) = let (b, vals) = f info
in (parensM p b, vals)
sqlSelectCols _ (ERawList _) = unexpectedCompositeKeyError
sqlSelectColCount = const 1
sqlSelectProcessRow [pv] = Value <$> fromPersistValue pv
sqlSelectProcessRow _ = Left "SqlSelect (Value a): wrong number of columns."

View File

@ -249,6 +249,27 @@ main = do
return p
liftIO $ ret5 `shouldBe` [ p1e, p4e, p3e, p2e ]
it "works with non-id primary key" $
run $ do
let fc = Frontcover number ""
number = 101
Right thePk = keyFromValues [PersistInt64 $ fromIntegral number]
fcPk <- insert fc
[Entity _ ret] <- select $ from $ return
liftIO $ do
ret `shouldBe` fc
fcPk `shouldBe` thePk
it "works when returning a composite primary key from a query" $
pendingWith "Need to refactor 'Value a's SqlQuery instance"
{-
run $ do
let p = Point 10 20 ""
thePk <- insert p
[Value ppk] <- select $ from $ \p' -> return (p'^.PointId)
liftIO $ ppk `shouldBe` thePk
-}
describe "select/JOIN" $ do
it "works with a LEFT OUTER JOIN" $
@ -304,6 +325,76 @@ main = do
return (p, mb)
) `shouldThrow` (\(OnClauseWithoutMatchingJoinException _) -> True)
it "works with ForeignKey to a non-id primary key returning one entity" $
run $ do
let fc = Frontcover number ""
article = Article "Esqueleto supports composite pks!" number
number = 101
Right thePk = keyFromValues [PersistInt64 $ fromIntegral number]
fcPk <- insert fc
insert_ article
[Entity _ retFc] <- select $
from $ \(a `InnerJoin` f) -> do
on (f^.FrontcoverNumber ==. a^.ArticleFrontcoverNumber)
return f
liftIO $ do
retFc `shouldBe` fc
fcPk `shouldBe` thePk
it "works with a ForeignKey to a non-id primary key returning both entities" $
run $ do
let fc = Frontcover number ""
article = Article "Esqueleto supports composite pks!" number
number = 101
Right thePk = keyFromValues [PersistInt64 $ fromIntegral number]
fcPk <- insert fc
insert_ article
[(Entity _ retFc, Entity _ retArt)] <- select $
from $ \(a `InnerJoin` f) -> do
on (f^.FrontcoverNumber ==. a^.ArticleFrontcoverNumber)
return (f, a)
liftIO $ do
retFc `shouldBe` fc
retArt `shouldBe` article
fcPk `shouldBe` thePk
articleFkfrontcover retArt `shouldBe` thePk
it "works with a non-id primary key returning one entity" $
run $ do
let fc = Frontcover number ""
article = Article2 "Esqueleto supports composite pks!" thePk
number = 101
Right thePk = keyFromValues [PersistInt64 $ fromIntegral number]
fcPk <- insert fc
insert_ article
[Entity _ retFc] <- select $
from $ \(a `InnerJoin` f) -> do
on (f^.FrontcoverId ==. a^.Article2FrontcoverId)
return f
liftIO $ do
retFc `shouldBe` fc
fcPk `shouldBe` thePk
it "works with a composite primary key" $
pendingWith "Persistent does not create the CircleFkPoint constructor. See: https://github.com/yesodweb/persistent/issues/341"
{-
run $ do
let p = Point x y ""
c = Circle x y ""
x = 10
y = 15
Right thePk = keyFromValues [ PersistInt64 $ fromIntegral x
, PersistInt64 $ fromIntegral y]
pPk <- insert p
insert_ c
[Entity _ ret] <- select $ from $ \(c' `InnerJoin` p') -> do
on (p'^.PointId ==. c'^.CircleFkpoint)
return p'
liftIO $ do
ret `shouldBe` p
pPk `shouldBe` thePk
-}
describe "select/where_" $ do
it "works for a simple example with (==.)" $
run $ do
@ -501,6 +592,21 @@ main = do
, (p3e, Nothing, Nothing)
, (p2e, Just f21, Just p1e) ]
it "works with a composite primary key" $
run $ do
let p = Point x y ""
x = 10
y = 15
Right thePk = keyFromValues [ PersistInt64 $ fromIntegral x
, PersistInt64 $ fromIntegral y]
pPk <- insert p
[Entity _ ret] <- select $ from $ \p' -> do
where_ (p'^.PointId ==. val pPk)
return p'
liftIO $ do
ret `shouldBe` p
pPk `shouldBe` thePk
describe "select/orderBy" $ do
it "works with a single ASC field" $
@ -580,6 +686,16 @@ main = do
-- is 1/2^40, so this test should pass almost everytime.
liftIO $ S.size rets `shouldSatisfy` (>2)
it "works on a composite primary key" $
run $ do
let ps = [Point 2 1 "", Point 1 2 ""]
mapM_ insert ps
eps <- select $
from $ \p' -> do
orderBy [asc (p'^.PointId)]
return p'
liftIO $ map entityVal eps `shouldBe` reverse ps
describe "selectDistinct" $
it "works on a simple example" $
@ -734,6 +850,25 @@ main = do
, Entity p3k p3 { personAge = Just 7 }
, Entity p2k p2 { personAge = Just 0 } ]
it "works with a composite primary key" $
pendingWith "Need refactor to support composite pks on ESet"
{-
run $ do
let p = Point x y ""
x = 10
y = 15
newX = 20
newY = 25
Right newPk = keyFromValues [ PersistInt64 $ fromIntegral newX
, PersistInt64 $ fromIntegral newY]
insert_ p
() <- update $ \p' -> do
set p' [PointId =. val newPk]
[Entity _ ret] <- select $ from $ return
liftIO $ do
ret `shouldBe` Point newX newY []
-}
it "GROUP BY works with COUNT" $
run $ do
p1k <- insert p1
@ -937,118 +1072,6 @@ main = do
liftIO $ ret `shouldBe` [ Value (3) ]
it "works with custom primary key" $
run $ do
let fc = Frontcover number ""
number = 101
Right thePk = keyFromValues [PersistInt64 $ fromIntegral number]
fcPk <- insert fc
[Entity _ ret] <- select $ from $ return
liftIO $ do
ret `shouldBe` fc
fcPk `shouldBe` thePk
it "works with composite primary key" $
run $ do
let p = Point x y ""
x = 10
y = 15
Right thePk = keyFromValues [ PersistInt64 $ fromIntegral x
, PersistInt64 $ fromIntegral y]
pPk <- insert p
[Entity _ ret] <- select $ from $ \p' -> do
where_ (p'^.PointId ==. val pPk)
return p'
liftIO $ do
ret `shouldBe` p
pPk `shouldBe` thePk
{- FIXME: Persistent does not create the CircleFkPoint constructor.
- See: https://github.com/yesodweb/persistent/issues/341
it "can join on a composite primary key" $
run $ do
let p = Point x y ""
c = Circle x y ""
x = 10
y = 15
Right thePk = keyFromValues [ PersistInt64 $ fromIntegral x
, PersistInt64 $ fromIntegral y]
pPk <- insert p
insert_ c
[Entity _ ret] <- select $ from $ \(c' `InnerJoin` p') -> do
on (p'^.PointId ==. c'^.CircleFkpoint)
return p'
liftIO $ do
ret `shouldBe` p
pPk `shouldBe` thePk
-}
it "can join a ForeignKey with a non-id primary key and return one entity" $
run $ do
let fc = Frontcover number ""
article = Article "Esqueleto supports composite pks!" number
number = 101
Right thePk = keyFromValues [PersistInt64 $ fromIntegral number]
fcPk <- insert fc
insert_ article
[Entity _ retFc] <- select $
from $ \(a `InnerJoin` f) -> do
on (f^.FrontcoverNumber ==. a^.ArticleFrontcoverNumber)
return f
liftIO $ do
retFc `shouldBe` fc
fcPk `shouldBe` thePk
it "can join a ForeignKey with a non-id primary key and return both entities" $
run $ do
let fc = Frontcover number ""
article = Article "Esqueleto supports composite pks!" number
number = 101
Right thePk = keyFromValues [PersistInt64 $ fromIntegral number]
fcPk <- insert fc
insert_ article
[(Entity _ retFc, Entity _ retArt)] <- select $
from $ \(a `InnerJoin` f) -> do
on (f^.FrontcoverNumber ==. a^.ArticleFrontcoverNumber)
return (f, a)
liftIO $ do
retFc `shouldBe` fc
retArt `shouldBe` article
fcPk `shouldBe` thePk
articleFkfrontcover retArt `shouldBe` thePk
it "can join with a non-id primary key and return one entity" $
run $ do
let fc = Frontcover number ""
article = Article2 "Esqueleto supports composite pks!" thePk
number = 101
Right thePk = keyFromValues [PersistInt64 $ fromIntegral number]
fcPk <- insert fc
insert_ article
[Entity _ retFc] <- select $
from $ \(a `InnerJoin` f) -> do
on (f^.FrontcoverId ==. a^.Article2FrontcoverId)
return f
liftIO $ do
retFc `shouldBe` fc
fcPk `shouldBe` thePk
it "can orderBy composite primary key" $
run $ do
let ps = [Point 2 1 "", Point 1 2 ""]
mapM_ insert ps
eps <- select $
from $ \p' -> do
orderBy [asc (p'^.PointId)]
return p'
liftIO $ map entityVal eps `shouldBe` reverse ps
it "can return a composite primary key from a query" $
run $ do
let p = Point 10 20 ""
thePk <- insert p
[Value ppk] <- select $ from $ \p' -> return (p'^.PointId)
liftIO $ ppk `shouldBe` thePk
----------------------------------------------------------------------