Support non-id primary key joins with columns not declared as ForeignKey but of ParentId type
This commit is contained in:
parent
477c0a4c21
commit
ad409312cf
@ -522,7 +522,12 @@ unsafeSqlBinOpList op sep (ERawList f1) (ERawList f2) = ERaw Never f
|
||||
zip b1 b2
|
||||
, vals1 <> vals2 )
|
||||
unsafeSqlBinOpList op _ a@(ERaw _ _) b@(ERaw _ _) = unsafeSqlBinOp op a b
|
||||
unsafeSqlBinOpList _ _ _ _ = error "unsafeSqlBinOpList: must operate against another composite key"
|
||||
unsafeSqlBinOpList op sep (ERaw p1 f1) b@(ERawList _) = unsafeSqlBinOpList op sep a b
|
||||
where a = ERawList $ \info -> let (b1, vals1) = f1 info
|
||||
in ([parensM p1 b1], vals1)
|
||||
unsafeSqlBinOpList op sep a@(ERawList _) (ERaw p2 f2) = unsafeSqlBinOpList op sep a b
|
||||
where b = ERawList $ \info -> let (b2, vals2) = f2 info
|
||||
in ([parensM p2 b2], vals2)
|
||||
{-# INLINE unsafeSqlBinOpList #-}
|
||||
|
||||
-- | (Internal) A raw SQL value. The same warning from
|
||||
|
||||
24
test/Test.hs
24
test/Test.hs
@ -71,6 +71,10 @@ share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistUpperCase|
|
||||
frontcoverNumber Int
|
||||
Foreign Frontcover fkfrontcover frontcoverNumber
|
||||
deriving Eq Show
|
||||
Article2
|
||||
title String
|
||||
frontcoverId FrontcoverId
|
||||
deriving Eq Show
|
||||
Point
|
||||
x Int
|
||||
y Int
|
||||
@ -979,7 +983,7 @@ main = do
|
||||
pPk `shouldBe` thePk
|
||||
-}
|
||||
|
||||
it "can join with a non-id primary key and return one entity" $
|
||||
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
|
||||
@ -995,7 +999,7 @@ main = do
|
||||
retFc `shouldBe` fc
|
||||
fcPk `shouldBe` thePk
|
||||
|
||||
it "can join with a non-id primary key and return both entities" $
|
||||
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
|
||||
@ -1012,6 +1016,22 @@ main = do
|
||||
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
|
||||
----------------------------------------------------------------------
|
||||
|
||||
|
||||
|
||||
Loading…
Reference in New Issue
Block a user