{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE UndecidableInstances #-}
module PersistUniqueTest where
import Init
share [mkPersist persistSettings { mpsGeneric = False }, mkMigrate "migration"] [persistLowerCase|
Fo
foo Int
bar Int
Primary foo
UniqueBar bar
deriving Eq Show
Ba
foo Int
baz Int
UniqueBaz baz
deriving Eq Show
OnlyPrimaryKey
foo Int
name String
Primary foo
deriving Eq Show
|]
deriving stock instance Eq (Unique Fo)
deriving stock instance Show (Unique Fo)
deriving stock instance Show (Unique Ba)
deriving stock instance Eq (Unique Ba)
shouldCompile :: (OnlyOneUniqueKey OnlyPrimaryKey, AtLeastOneUniqueKey OnlyPrimaryKey) => IO ()
shouldCompile :: IO ()
shouldCompile = () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
cleanDB :: (MonadIO m, PersistQuery backend, PersistEntityBackend Fo ~ backend) => ReaderT backend m ()
cleanDB :: ReaderT backend m ()
cleanDB = do
[Filter Fo] -> ReaderT backend m ()
forall backend (m :: * -> *) record.
(PersistQueryWrite backend, MonadIO m,
PersistRecordBackend record backend) =>
[Filter record] -> ReaderT backend m ()
deleteWhere ([] :: [Filter Fo])
specsWith :: Runner SqlBackend m => RunDb SqlBackend m -> Spec
specsWith :: RunDb SqlBackend m -> Spec
specsWith RunDb SqlBackend m
runDb = String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"PersistUniqueTest" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"getBy" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> IO () -> SpecWith (Arg (IO ()))
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"works to pull a record from the database" (IO () -> SpecWith (Arg (IO ())))
-> IO () -> SpecWith (Arg (IO ()))
forall a b. (a -> b) -> a -> b
$ RunDb SqlBackend m
runDb RunDb SqlBackend m -> RunDb SqlBackend m
forall a b. (a -> b) -> a -> b
$ do
let b :: Int
b = Int
5
Key Fo
k <- Fo -> ReaderT SqlBackend m (Key Fo)
forall backend record (m :: * -> *).
(PersistStoreWrite backend, MonadIO m,
PersistRecordBackend record backend, SafeToInsert record) =>
record -> ReaderT backend m (Key record)
insert Fo :: Int -> Int -> Fo
Fo { foFoo :: Int
foFoo = Int
3, foBar :: Int
foBar = Int
b }
Just Fo
vk <- Key Fo -> ReaderT SqlBackend m (Maybe Fo)
forall backend record (m :: * -> *).
(PersistStoreRead backend, MonadIO m,
PersistRecordBackend record backend) =>
Key record -> ReaderT backend m (Maybe record)
get Key Fo
k
Just Entity Fo
vu <- Unique Fo -> ReaderT SqlBackend m (Maybe (Entity Fo))
forall backend record (m :: * -> *).
(PersistUniqueRead backend, MonadIO m,
PersistRecordBackend record backend) =>
Unique record -> ReaderT backend m (Maybe (Entity record))
getBy (Int -> Unique Fo
UniqueBar Int
b)
Entity Fo
vu Entity Fo -> Entity Fo -> ReaderT SqlBackend m ()
forall a (m :: * -> *).
(HasCallStack, Eq a, Show a, MonadIO m) =>
a -> a -> m ()
@== Key Fo -> Fo -> Entity Fo
forall rec. Key rec -> rec -> Entity rec
Entity Key Fo
k Fo
vk
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"insertUniqueEntity" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> IO () -> SpecWith (Arg (IO ()))
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"inserts a value if no conflicts are present" (IO () -> SpecWith (Arg (IO ())))
-> IO () -> SpecWith (Arg (IO ()))
forall a b. (a -> b) -> a -> b
$ RunDb SqlBackend m
runDb RunDb SqlBackend m -> RunDb SqlBackend m
forall a b. (a -> b) -> a -> b
$ do
let fo :: Fo
fo = Int -> Int -> Fo
Fo Int
3 Int
5
Just (Entity Key Fo
_ Fo
insertedFoValue) <- Fo -> ReaderT SqlBackend m (Maybe (Entity Fo))
forall record backend (m :: * -> *).
(MonadIO m, PersistRecordBackend record backend,
PersistUniqueWrite backend, SafeToInsert record) =>
record -> ReaderT backend m (Maybe (Entity record))
insertUniqueEntity Fo
fo
Fo
fo Fo -> Fo -> ReaderT SqlBackend m ()
forall a (m :: * -> *).
(HasCallStack, Eq a, Show a, MonadIO m) =>
a -> a -> m ()
@== Fo
insertedFoValue
String -> IO () -> SpecWith (Arg (IO ()))
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"does not insert if the record is entirely the same" (IO () -> SpecWith (Arg (IO ())))
-> IO () -> SpecWith (Arg (IO ()))
forall a b. (a -> b) -> a -> b
$ RunDb SqlBackend m
runDb RunDb SqlBackend m -> RunDb SqlBackend m
forall a b. (a -> b) -> a -> b
$ do
let fo :: Fo
fo = Int -> Int -> Fo
Fo Int
3 Int
5
Just (Entity Key Fo
_ Fo
insertedFoValue) <- Fo -> ReaderT SqlBackend m (Maybe (Entity Fo))
forall record backend (m :: * -> *).
(MonadIO m, PersistRecordBackend record backend,
PersistUniqueWrite backend, SafeToInsert record) =>
record -> ReaderT backend m (Maybe (Entity record))
insertUniqueEntity Fo
fo
Maybe (Entity Fo)
mresult <- Fo -> ReaderT SqlBackend m (Maybe (Entity Fo))
forall record backend (m :: * -> *).
(MonadIO m, PersistRecordBackend record backend,
PersistUniqueWrite backend, SafeToInsert record) =>
record -> ReaderT backend m (Maybe (Entity record))
insertUniqueEntity Fo
fo
Maybe (Entity Fo)
mresult Maybe (Entity Fo) -> Maybe (Entity Fo) -> ReaderT SqlBackend m ()
forall a (m :: * -> *).
(HasCallStack, Eq a, Show a, MonadIO m) =>
a -> a -> m ()
@== Maybe (Entity Fo)
forall a. Maybe a
Nothing
String -> IO () -> SpecWith (Arg (IO ()))
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"does not insert if there is a primary key conflict" (IO () -> SpecWith (Arg (IO ())))
-> IO () -> SpecWith (Arg (IO ()))
forall a b. (a -> b) -> a -> b
$ RunDb SqlBackend m
runDb RunDb SqlBackend m -> RunDb SqlBackend m
forall a b. (a -> b) -> a -> b
$ do
let fo :: Fo
fo = Int -> Int -> Fo
Fo Int
3 Int
5
Just (Entity Key Fo
_ Fo
insertedFoValue) <- Fo -> ReaderT SqlBackend m (Maybe (Entity Fo))
forall record backend (m :: * -> *).
(MonadIO m, PersistRecordBackend record backend,
PersistUniqueWrite backend, SafeToInsert record) =>
record -> ReaderT backend m (Maybe (Entity record))
insertUniqueEntity Fo
fo
Maybe (Entity Fo)
mresult <- Fo -> ReaderT SqlBackend m (Maybe (Entity Fo))
forall record backend (m :: * -> *).
(MonadIO m, PersistRecordBackend record backend,
PersistUniqueWrite backend, SafeToInsert record) =>
record -> ReaderT backend m (Maybe (Entity record))
insertUniqueEntity Fo
fo { foFoo :: Int
foFoo = Int
4 }
Maybe (Entity Fo)
mresult Maybe (Entity Fo) -> Maybe (Entity Fo) -> ReaderT SqlBackend m ()
forall a (m :: * -> *).
(HasCallStack, Eq a, Show a, MonadIO m) =>
a -> a -> m ()
@== Maybe (Entity Fo)
forall a. Maybe a
Nothing
String -> IO () -> SpecWith (Arg (IO ()))
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"does not insert if there is a unique key conflict" (IO () -> SpecWith (Arg (IO ())))
-> IO () -> SpecWith (Arg (IO ()))
forall a b. (a -> b) -> a -> b
$ RunDb SqlBackend m
runDb RunDb SqlBackend m -> RunDb SqlBackend m
forall a b. (a -> b) -> a -> b
$ do
let fo :: Fo
fo = Int -> Int -> Fo
Fo Int
3 Int
5
Just (Entity Key Fo
_ Fo
insertedFoValue) <- Fo -> ReaderT SqlBackend m (Maybe (Entity Fo))
forall record backend (m :: * -> *).
(MonadIO m, PersistRecordBackend record backend,
PersistUniqueWrite backend, SafeToInsert record) =>
record -> ReaderT backend m (Maybe (Entity record))
insertUniqueEntity Fo
fo
Maybe (Entity Fo)
mresult <- Fo -> ReaderT SqlBackend m (Maybe (Entity Fo))
forall record backend (m :: * -> *).
(MonadIO m, PersistRecordBackend record backend,
PersistUniqueWrite backend, SafeToInsert record) =>
record -> ReaderT backend m (Maybe (Entity record))
insertUniqueEntity Fo
fo { foBar :: Int
foBar = Int
4 }
Maybe (Entity Fo)
mresult Maybe (Entity Fo) -> Maybe (Entity Fo) -> ReaderT SqlBackend m ()
forall a (m :: * -> *).
(HasCallStack, Eq a, Show a, MonadIO m) =>
a -> a -> m ()
@== Maybe (Entity Fo)
forall a. Maybe a
Nothing
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"checkUniqueUpdateable" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"with standard id" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> IO () -> SpecWith (Arg (IO ()))
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"returns the unique constraint that failed" (IO () -> SpecWith (Arg (IO ())))
-> IO () -> SpecWith (Arg (IO ()))
forall a b. (a -> b) -> a -> b
$ RunDb SqlBackend m
runDb RunDb SqlBackend m -> RunDb SqlBackend m
forall a b. (a -> b) -> a -> b
$ do
let ba :: Ba
ba = Ba :: Int -> Int -> Ba
Ba { baFoo :: Int
baFoo = Int
1, baBaz :: Int
baBaz = Int
2 }
Key Ba
bk <- Ba -> ReaderT SqlBackend m (Key Ba)
forall backend record (m :: * -> *).
(PersistStoreWrite backend, MonadIO m,
PersistRecordBackend record backend, SafeToInsert record) =>
record -> ReaderT backend m (Key record)
insert Ba
ba
Maybe (Unique Ba)
mresult <- Ba -> ReaderT SqlBackend m (Maybe (Unique Ba))
forall record backend (m :: * -> *).
(MonadIO m, PersistRecordBackend record backend,
PersistUniqueRead backend) =>
record -> ReaderT backend m (Maybe (Unique record))
checkUnique Ba
ba
Maybe (Unique Ba)
mresult Maybe (Unique Ba) -> Maybe (Unique Ba) -> ReaderT SqlBackend m ()
forall a (m :: * -> *).
(HasCallStack, Eq a, Show a, MonadIO m) =>
a -> a -> m ()
@== Unique Ba -> Maybe (Unique Ba)
forall a. a -> Maybe a
Just (Int -> Unique Ba
UniqueBaz Int
2)
String -> IO () -> SpecWith (Arg (IO ()))
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"returns Nothing if no constraint conflict exists" (IO () -> SpecWith (Arg (IO ())))
-> IO () -> SpecWith (Arg (IO ()))
forall a b. (a -> b) -> a -> b
$ RunDb SqlBackend m
runDb RunDb SqlBackend m -> RunDb SqlBackend m
forall a b. (a -> b) -> a -> b
$ do
let ba :: Ba
ba = Ba :: Int -> Int -> Ba
Ba { baFoo :: Int
baFoo = Int
1, baBaz :: Int
baBaz = Int
2 }
Maybe (Unique Ba)
mresult <- Ba -> ReaderT SqlBackend m (Maybe (Unique Ba))
forall record backend (m :: * -> *).
(MonadIO m, PersistRecordBackend record backend,
PersistUniqueRead backend) =>
record -> ReaderT backend m (Maybe (Unique record))
checkUnique Ba
ba
Maybe (Unique Ba)
mresult Maybe (Unique Ba) -> Maybe (Unique Ba) -> ReaderT SqlBackend m ()
forall a (m :: * -> *).
(HasCallStack, Eq a, Show a, MonadIO m) =>
a -> a -> m ()
@== Maybe (Unique Ba)
forall a. Maybe a
Nothing
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"with Primary" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> IO () -> SpecWith (Arg (IO ()))
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"conflicts with itself" (IO () -> SpecWith (Arg (IO ())))
-> IO () -> SpecWith (Arg (IO ()))
forall a b. (a -> b) -> a -> b
$ RunDb SqlBackend m
runDb RunDb SqlBackend m -> RunDb SqlBackend m
forall a b. (a -> b) -> a -> b
$ do
let f :: Int
f = Int
3
let b :: Int
b = Int
5
let fo :: Fo
fo = Int -> Int -> Fo
Fo Int
f Int
b
Key Fo
k <- Fo -> ReaderT SqlBackend m (Key Fo)
forall backend record (m :: * -> *).
(PersistStoreWrite backend, MonadIO m,
PersistRecordBackend record backend, SafeToInsert record) =>
record -> ReaderT backend m (Key record)
insert Fo
fo
Maybe (Unique Fo)
mresult <- Fo -> ReaderT SqlBackend m (Maybe (Unique Fo))
forall record backend (m :: * -> *).
(MonadIO m, PersistRecordBackend record backend,
PersistUniqueRead backend) =>
record -> ReaderT backend m (Maybe (Unique record))
checkUnique Fo
fo
Maybe (Unique Fo)
mresult Maybe (Unique Fo) -> Maybe (Unique Fo) -> ReaderT SqlBackend m ()
forall a (m :: * -> *).
(HasCallStack, Eq a, Show a, MonadIO m) =>
a -> a -> m ()
@== Unique Fo -> Maybe (Unique Fo)
forall a. a -> Maybe a
Just (Int -> Unique Fo
FoPrimaryKey Int
f)
String -> IO () -> SpecWith (Arg (IO ()))
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"returns the key that failed" (IO () -> SpecWith (Arg (IO ())))
-> IO () -> SpecWith (Arg (IO ()))
forall a b. (a -> b) -> a -> b
$ RunDb SqlBackend m
runDb RunDb SqlBackend m -> RunDb SqlBackend m
forall a b. (a -> b) -> a -> b
$ do
let f :: Int
f = Int
3
let b :: Int
b = Int
5
let fo :: Fo
fo = Int -> Int -> Fo
Fo Int
f Int
b
Key Fo
k <- Fo -> ReaderT SqlBackend m (Key Fo)
forall backend record (m :: * -> *).
(PersistStoreWrite backend, MonadIO m,
PersistRecordBackend record backend, SafeToInsert record) =>
record -> ReaderT backend m (Key record)
insert Fo
fo
Maybe (Unique Fo)
_ <- Fo -> ReaderT SqlBackend m (Maybe (Unique Fo))
forall record backend (m :: * -> *).
(MonadIO m, PersistRecordBackend record backend,
PersistUniqueRead backend) =>
record -> ReaderT backend m (Maybe (Unique record))
checkUnique Fo
fo
let fo' :: Fo
fo' = Int -> Int -> Fo
Fo (Int
f Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Int
b
Just Unique Fo
_ <- Fo -> ReaderT SqlBackend m (Maybe (Unique Fo))
forall record backend (m :: * -> *).
(MonadIO m, PersistRecordBackend record backend,
PersistUniqueRead backend) =>
record -> ReaderT backend m (Maybe (Unique record))
checkUnique Fo
fo'
Maybe (Unique Fo)
Nothing <- Entity Fo -> ReaderT SqlBackend m (Maybe (Unique Fo))
forall record backend (m :: * -> *).
(MonadIO m, PersistRecordBackend record backend,
PersistUniqueRead backend) =>
Entity record -> ReaderT backend m (Maybe (Unique record))
checkUniqueUpdateable (Entity Fo -> ReaderT SqlBackend m (Maybe (Unique Fo)))
-> Entity Fo -> ReaderT SqlBackend m (Maybe (Unique Fo))
forall a b. (a -> b) -> a -> b
$ Key Fo -> Fo -> Entity Fo
forall rec. Key rec -> rec -> Entity rec
Entity Key Fo
k Fo
fo'
let fo'' :: Fo
fo'' = Int -> Int -> Fo
Fo (Int
f Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Int
b Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
Fo -> ReaderT SqlBackend m ()
forall backend record (m :: * -> *).
(PersistStoreWrite backend, MonadIO m,
PersistRecordBackend record backend, SafeToInsert record) =>
record -> ReaderT backend m ()
insert_ Fo
fo''
Maybe (Unique Fo)
mresult <- Entity Fo -> ReaderT SqlBackend m (Maybe (Unique Fo))
forall record backend (m :: * -> *).
(MonadIO m, PersistRecordBackend record backend,
PersistUniqueRead backend) =>
Entity record -> ReaderT backend m (Maybe (Unique record))
checkUniqueUpdateable (Entity Fo -> ReaderT SqlBackend m (Maybe (Unique Fo)))
-> Entity Fo -> ReaderT SqlBackend m (Maybe (Unique Fo))
forall a b. (a -> b) -> a -> b
$ Key Fo -> Fo -> Entity Fo
forall rec. Key rec -> rec -> Entity rec
Entity Key Fo
k Fo
fo''
Maybe (Unique Fo)
mresult Maybe (Unique Fo) -> Maybe (Unique Fo) -> ReaderT SqlBackend m ()
forall a (m :: * -> *).
(HasCallStack, Eq a, Show a, MonadIO m) =>
a -> a -> m ()
@== Unique Fo -> Maybe (Unique Fo)
forall a. a -> Maybe a
Just (Int -> Unique Fo
FoPrimaryKey (Int
f Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1))
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"upsert" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"OnlyPrimaryKey" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> IO () -> SpecWith (Arg (IO ()))
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"can upsert" (IO () -> SpecWith (Arg (IO ())))
-> IO () -> SpecWith (Arg (IO ()))
forall a b. (a -> b) -> a -> b
$ RunDb SqlBackend m
runDb RunDb SqlBackend m -> RunDb SqlBackend m
forall a b. (a -> b) -> a -> b
$ do
let
record :: OnlyPrimaryKey
record =
OnlyPrimaryKey :: Int -> String -> OnlyPrimaryKey
OnlyPrimaryKey
{ onlyPrimaryKeyFoo :: Int
onlyPrimaryKeyFoo = Int
1
, onlyPrimaryKeyName :: String
onlyPrimaryKeyName = String
"Oh no"
}
Entity OnlyPrimaryKey
entity <- OnlyPrimaryKey
-> [Update OnlyPrimaryKey]
-> ReaderT SqlBackend m (Entity OnlyPrimaryKey)
forall backend record (m :: * -> *).
(PersistUniqueWrite backend, MonadIO m,
PersistRecordBackend record backend, OnlyOneUniqueKey record,
SafeToInsert record) =>
record -> [Update record] -> ReaderT backend m (Entity record)
upsert OnlyPrimaryKey
record [EntityField OnlyPrimaryKey String
forall typ. (typ ~ String) => EntityField OnlyPrimaryKey typ
OnlyPrimaryKeyName EntityField OnlyPrimaryKey String
-> String -> Update OnlyPrimaryKey
forall v typ.
PersistField typ =>
EntityField v typ -> typ -> Update v
=. String
"Hello"]
Entity OnlyPrimaryKey -> OnlyPrimaryKey
forall rec. Entity rec -> rec
entityVal Entity OnlyPrimaryKey
entity OnlyPrimaryKey -> OnlyPrimaryKey -> ReaderT SqlBackend m ()
forall a (m :: * -> *).
(HasCallStack, Eq a, Show a, MonadIO m) =>
a -> a -> m ()
@== OnlyPrimaryKey
record
Entity OnlyPrimaryKey
entity' <- OnlyPrimaryKey
-> [Update OnlyPrimaryKey]
-> ReaderT SqlBackend m (Entity OnlyPrimaryKey)
forall backend record (m :: * -> *).
(PersistUniqueWrite backend, MonadIO m,
PersistRecordBackend record backend, OnlyOneUniqueKey record,
SafeToInsert record) =>
record -> [Update record] -> ReaderT backend m (Entity record)
upsert OnlyPrimaryKey
record [EntityField OnlyPrimaryKey String
forall typ. (typ ~ String) => EntityField OnlyPrimaryKey typ
OnlyPrimaryKeyName EntityField OnlyPrimaryKey String
-> String -> Update OnlyPrimaryKey
forall v typ.
PersistField typ =>
EntityField v typ -> typ -> Update v
=. String
"Hello"]
Entity OnlyPrimaryKey -> OnlyPrimaryKey
forall rec. Entity rec -> rec
entityVal Entity OnlyPrimaryKey
entity' OnlyPrimaryKey -> OnlyPrimaryKey -> ReaderT SqlBackend m ()
forall a (m :: * -> *).
(HasCallStack, Eq a, Show a, MonadIO m) =>
a -> a -> m ()
@== OnlyPrimaryKey
record { onlyPrimaryKeyName :: String
onlyPrimaryKeyName = String
"Hello" }
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"Fo" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> IO () -> SpecWith (Arg (IO ()))
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"cannot upsert" (IO () -> SpecWith (Arg (IO ())))
-> IO () -> SpecWith (Arg (IO ()))
forall a b. (a -> b) -> a -> b
$ RunDb SqlBackend m
runDb RunDb SqlBackend m -> RunDb SqlBackend m
forall a b. (a -> b) -> a -> b
$ do
() -> ReaderT SqlBackend m ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
String -> IO () -> SpecWith (Arg (IO ()))
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"can upsertBy" (IO () -> SpecWith (Arg (IO ())))
-> IO () -> SpecWith (Arg (IO ()))
forall a b. (a -> b) -> a -> b
$ RunDb SqlBackend m
runDb RunDb SqlBackend m -> RunDb SqlBackend m
forall a b. (a -> b) -> a -> b
$ do
let f :: Fo
f = Fo :: Int -> Int -> Fo
Fo { foFoo :: Int
foFoo = Int
1, foBar :: Int
foBar = Int
2 }
Entity Fo
entity <- Unique Fo -> Fo -> [Update Fo] -> ReaderT SqlBackend m (Entity Fo)
forall backend record (m :: * -> *).
(PersistUniqueWrite backend, MonadIO m,
PersistRecordBackend record backend, SafeToInsert record) =>
Unique record
-> record -> [Update record] -> ReaderT backend m (Entity record)
upsertBy (Int -> Unique Fo
FoPrimaryKey Int
1) Fo
f [EntityField Fo Int
forall typ. (typ ~ Int) => EntityField Fo typ
FoBar EntityField Fo Int -> Int -> Update Fo
forall v typ.
PersistField typ =>
EntityField v typ -> typ -> Update v
+=. Int
1]
Entity Fo -> Fo
forall rec. Entity rec -> rec
entityVal Entity Fo
entity Fo -> Fo -> ReaderT SqlBackend m ()
forall a (m :: * -> *).
(HasCallStack, Eq a, Show a, MonadIO m) =>
a -> a -> m ()
@== Fo
f
Entity Fo
entity' <- Unique Fo -> Fo -> [Update Fo] -> ReaderT SqlBackend m (Entity Fo)
forall backend record (m :: * -> *).
(PersistUniqueWrite backend, MonadIO m,
PersistRecordBackend record backend, SafeToInsert record) =>
Unique record
-> record -> [Update record] -> ReaderT backend m (Entity record)
upsertBy (Int -> Unique Fo
FoPrimaryKey Int
1) Fo
f [EntityField Fo Int
forall typ. (typ ~ Int) => EntityField Fo typ
FoBar EntityField Fo Int -> Int -> Update Fo
forall v typ.
PersistField typ =>
EntityField v typ -> typ -> Update v
+=. Int
1]
Entity Fo -> Fo
forall rec. Entity rec -> rec
entityVal Entity Fo
entity' Fo -> Fo -> ReaderT SqlBackend m ()
forall a (m :: * -> *).
(HasCallStack, Eq a, Show a, MonadIO m) =>
a -> a -> m ()
@== Fo
f { foBar :: Int
foBar = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Fo -> Int
foBar Fo
f }
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"OnlyPrimaryKey" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> IO () -> SpecWith (Arg (IO ()))
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"has unique constraints" (IO () -> SpecWith (Arg (IO ())))
-> IO () -> SpecWith (Arg (IO ()))
forall a b. (a -> b) -> a -> b
$ do
IO ()
(OnlyOneUniqueKey OnlyPrimaryKey,
AtLeastOneUniqueKey OnlyPrimaryKey) =>
IO ()
shouldCompile