Implemented support for custom/composite primary keys

This commit is contained in:
Alberto Valverde 2014-12-23 14:13:07 +01:00
parent e22f2326e6
commit cc4844167f
2 changed files with 29 additions and 10 deletions

View File

@ -7,6 +7,7 @@
, MultiParamTypeClasses
, OverloadedStrings
, UndecidableInstances
, ScopedTypeVariables
#-}
-- | This is an internal module, anything exported by this module
-- may change without a major version bump. Please use only
@ -58,6 +59,8 @@ import Data.List (intersperse)
import Data.Monoid (Monoid(..), (<>))
import Data.Proxy (Proxy(..))
import Database.Esqueleto.Internal.PersistentImport
import Database.Persist.Sql.Util (
entityColumnNames, entityColumnCount, parseEntityValues)
import qualified Control.Monad.Trans.State as S
import qualified Control.Monad.Trans.Writer as W
import qualified Data.Conduit as C
@ -993,11 +996,9 @@ instance SqlSelect () () where
instance PersistEntity a => SqlSelect (SqlExpr (Entity a)) (Entity a) where
sqlSelectCols info expr@(EEntity ident) = ret
where
process ed = uncommas $
map ((name <>) . fromDBName info) $
map fieldDB $
entityId ed :
entityFields ed
conn = fst info
process ed = uncommas . map ((name <>) . TLB.fromText) $
entityColumnNames ed conn
-- 'name' is the biggest difference between 'RawSql' and
-- 'SqlSelect'. We automatically create names for tables
-- (since it's not the user who's writing the FROM
@ -1007,11 +1008,10 @@ instance PersistEntity a => SqlSelect (SqlExpr (Entity a)) (Entity a) where
name = useIdent info ident <> "."
ret = let ed = entityDef $ getEntityVal $ return expr
in (process ed, mempty)
sqlSelectColCount = (+1) . length . entityFields . entityDef . getEntityVal
sqlSelectProcessRow (idCol:ent) =
Entity <$> fromPersistValue idCol
<*> fromPersistValues ent
sqlSelectProcessRow _ = Left "SqlSelect (Entity a): wrong number of columns."
sqlSelectColCount = entityColumnCount . entityDef . getEntityVal
sqlSelectProcessRow = parseEntityValues ed
where ed = entityDef $ getEntityVal $ (Proxy :: Proxy (SqlExpr (Entity a)))
getEntityVal :: Proxy (SqlExpr (Entity a)) -> Proxy a
getEntityVal = const Proxy

View File

@ -1,6 +1,8 @@
{-# LANGUAGE ConstraintKinds
, EmptyDataDecls
, FlexibleContexts
, FlexibleInstances
, DeriveGeneric
, GADTs
, GeneralizedNewtypeDeriving
, MultiParamTypeClasses
@ -63,6 +65,11 @@ share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistUpperCase|
number Int
Primary number
deriving Eq Show
Point
x Int
y Int
Primary x y
deriving Eq Show
|]
-- | this could be achieved with S.fromList, but not all lists
@ -924,6 +931,18 @@ main = 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 $ return
liftIO $ do
ret `shouldBe` p
pPk `shouldBe` thePk
----------------------------------------------------------------------