Skip to content

Commit ba070df

Browse files
committed
generate arbitrary data for example
1 parent df858c3 commit ba070df

File tree

5 files changed

+129
-18
lines changed

5 files changed

+129
-18
lines changed

beam-postgres/examples/app/Main.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -8,12 +8,12 @@ import Database.Beam.Backend.SQL ( BeamSqlBackendSyntax )
88
import qualified Data.Text.Lazy as TL
99
import qualified Data.Text.Lazy.Encoding as TL
1010
import Data.Text (unpack)
11-
import Pagila.Schema (migration)
11+
import Pagila.Schema (allMigrationSteps)
1212

1313
main :: IO ()
1414
main = do
1515
putStrLn "Migration steps:"
16-
mapM_ (putStrLn . unpack) (stepNames migration)
16+
mapM_ (putStrLn . unpack) (stepNames allMigrationSteps)
1717
putStrLn "-------------"
1818
putStrLn "For each migration step, the sequence of SQL scripts:"
1919
let
@@ -23,4 +23,4 @@ main = do
2323
where
2424
commandType = show . pgCommandType $ syntax
2525
sqlScript = TL.unpack . TL.decodeUtf8 . pgRenderSyntaxScript . fromPgCommand $ syntax
26-
putStrLn $ backendMigrationStepsScript renderer migration
26+
putStrLn $ backendMigrationStepsScript renderer allMigrationSteps

beam-postgres/examples/pagila.cabal

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,9 @@ library
2222
scientific,
2323
bytestring,
2424
text,
25-
exceptions,
25+
generic-random,
26+
QuickCheck,
27+
quickcheck-instances,
2628
postgresql-simple,
2729
beam-core,
2830
beam-postgres,
Lines changed: 57 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -1,38 +1,82 @@
11
{-# LANGUAGE OverloadedStrings #-}
2+
{-# LANGUAGE ScopedTypeVariables #-}
23
module Pagila.Schema
34
( module Pagila.Schema.V0002
4-
, migration, migrateDB, dbSettings ) where
5+
, allMigrationSteps, migrateDB, dbSettings, dbSettings' ) where
56

67
import Database.PostgreSQL.Simple
78

89
import Pagila.Schema.V0002 hiding (migration)
910

10-
import qualified Pagila.Schema.V0001 as V0001 (migration)
11-
import qualified Pagila.Schema.V0002 as V0002 (migration)
11+
import qualified Pagila.Schema.V0001 as V0001
12+
import qualified Pagila.Schema.V0002 as V0002
1213

1314
import Control.Arrow ( (>>>) )
1415

15-
import Database.Beam (DatabaseSettings)
16+
import Test.QuickCheck.Gen (Gen, sample')
17+
import Test.QuickCheck.Arbitrary (arbitrary)
18+
19+
import Database.Beam (DatabaseSettings, liftIO, insert, insertValues, runInsert)
1620
import Database.Beam.Migrate.Types ( CheckedDatabaseSettings, MigrationSteps, unCheckDatabase
1721
, evaluateDatabase, migrationStep)
1822
import Database.Beam.Postgres (Postgres, runBeamPostgresDebug)
1923
import Database.Beam.Migrate.Simple (BringUpToDateHooks, bringUpToDateWithHooks, defaultUpToDateHooks, runIrreversibleHook)
2024
import qualified Database.Beam.Postgres.Migrate as Pg
2125

22-
migration :: MigrationSteps Postgres () (CheckedDatabaseSettings Postgres Pagila.Schema.V0002.PagilaDb)
23-
migration = migrationStep "Initial commit" V0001.migration >>>
24-
migrationStep "Add film actor, inventory, rental table" V0002.migration
26+
firstMigrationStep :: MigrationSteps Postgres () (CheckedDatabaseSettings Postgres V0001.PagilaDb)
27+
firstMigrationStep = migrationStep "Initial commit" V0001.migration
28+
29+
secondMigrationStep :: MigrationSteps Postgres (CheckedDatabaseSettings Postgres V0001.PagilaDb) (CheckedDatabaseSettings Postgres V0002.PagilaDb)
30+
secondMigrationStep = migrationStep "Add film actor, inventory, rental table" V0002.migration
31+
32+
allMigrationSteps :: MigrationSteps Postgres () (CheckedDatabaseSettings Postgres V0002.PagilaDb)
33+
allMigrationSteps = firstMigrationStep >>> secondMigrationStep
2534

26-
dbSettings :: DatabaseSettings Postgres Pagila.Schema.V0002.PagilaDb
27-
dbSettings = unCheckDatabase (evaluateDatabase migration)
35+
dbSettings :: DatabaseSettings Postgres V0001.PagilaDb
36+
dbSettings = unCheckDatabase (evaluateDatabase firstMigrationStep)
37+
38+
dbSettings' :: DatabaseSettings Postgres V0002.PagilaDb
39+
dbSettings' = unCheckDatabase (evaluateDatabase allMigrationSteps)
2840

2941
allowDestructive :: (MonadFail m) => BringUpToDateHooks m
3042
allowDestructive =
3143
defaultUpToDateHooks
3244
{ runIrreversibleHook = return True
3345
}
3446

35-
migrateDB :: Connection -> IO (Maybe (CheckedDatabaseSettings Postgres Pagila.Schema.V0002.PagilaDb))
36-
migrateDB conn =
37-
runBeamPostgresDebug putStrLn conn
38-
$ bringUpToDateWithHooks allowDestructive Pg.migrationBackend migration
47+
{- |
48+
Run two migrations: V0001 and V0002.
49+
After V0001 migration, insert randomly generated countries and staff.
50+
This demonstrates the V0002 migration will not delete that data.
51+
-}
52+
migrateDB :: Connection -> IO (Maybe (CheckedDatabaseSettings Postgres V0002.PagilaDb))
53+
migrateDB conn = runBeamPostgresDebug putStrLn conn $ do
54+
55+
-- Run migration V0001
56+
mx :: Maybe (CheckedDatabaseSettings Postgres V0001.PagilaDb) <- bringUpToDateWithHooks allowDestructive Pg.migrationBackend firstMigrationStep
57+
58+
case mx of
59+
-- if migration V0001 succeeded, proceed.
60+
Just (_ :: CheckedDatabaseSettings Postgres V0001.PagilaDb) -> do
61+
-- generate random countries
62+
randomCountries :: [V0001.Country] <- liftIO
63+
. fmap (zipWith (\i country -> country { V0001.countryId = i }) [1..])
64+
$ sample' (arbitrary :: Gen V0001.Country)
65+
runInsert $ insert (V0001.country dbSettings) $ insertValues randomCountries
66+
67+
-- generate random V0001 Staff
68+
randomStaff :: [V0001.Staff] <-
69+
liftIO
70+
. fmap (zipWith (\i staff -> staff { V0001.staffId = i }) [1..])
71+
. fmap (fmap (\staffMember -> staffMember { V0001.staffPicture = Nothing } )) -- overwrite picture with null
72+
$ sample' (arbitrary :: Gen V0001.Staff)
73+
74+
runInsert $ insert (V0001.staff dbSettings) $ insertValues randomStaff
75+
76+
{- Run migrations V0001 (redundantly) and V0002.
77+
The V0002 migration will add staff `salary` field, among other changes.
78+
See 'Pagila.Schema.V0002.migrateToNewStaffWithSalary'.
79+
-}
80+
bringUpToDateWithHooks allowDestructive Pg.migrationBackend allMigrationSteps
81+
Nothing ->
82+
pure Nothing

beam-postgres/examples/src/Pagila/Schema/V0001.hs

Lines changed: 53 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# OPTIONS_GHC -fno-warn-orphans #-}
12
{-# LANGUAGE StandaloneDeriving #-}
23
{-# LANGUAGE DeriveAnyClass #-}
34
{-# LANGUAGE RecordWildCards #-}
@@ -7,6 +8,8 @@
78
{-# LANGUAGE FlexibleInstances #-}
89
{-# LANGUAGE MultiParamTypeClasses #-}
910
{-# LANGUAGE DeriveGeneric #-}
11+
{-# LANGUAGE DerivingStrategies #-}
12+
{-# LANGUAGE DerivingVia #-}
1013

1114
module Pagila.Schema.V0001 where
1215
-- TODO explicit module exports
@@ -59,6 +62,9 @@ import Data.Text (Text)
5962
import Data.ByteString (ByteString)
6063
import Data.Time.LocalTime (LocalTime)
6164
import Data.Scientific (Scientific)
65+
import Test.QuickCheck ( Arbitrary(arbitrary) )
66+
import Generic.Random ( genericArbitrary, uniform )
67+
import Test.QuickCheck.Instances ()
6268

6369
-- Address table
6470

@@ -73,9 +79,12 @@ data AddressT f
7379
, addressPhone :: Columnar f Text
7480
, addressLastUpdate :: Columnar f LocalTime
7581
} deriving Generic
82+
7683
type Address = AddressT Identity
7784
deriving instance Show Address
7885
deriving instance Eq Address
86+
instance Arbitrary Address where
87+
arbitrary = genericArbitrary uniform
7988

8089
instance Table AddressT where
8190
data PrimaryKey AddressT f = AddressId (Columnar f (SqlSerial Int32)) deriving Generic
@@ -84,6 +93,11 @@ type AddressId = PrimaryKey AddressT Identity
8493
deriving instance Show AddressId
8594
deriving instance Eq AddressId
8695

96+
instance Arbitrary (SqlSerial Int32) where
97+
arbitrary = genericArbitrary uniform
98+
instance Arbitrary AddressId where
99+
arbitrary = genericArbitrary uniform -- should be fixed at 1
100+
87101
-- City table
88102

89103
data CityT f
@@ -96,13 +110,17 @@ data CityT f
96110
type City = CityT Identity
97111
deriving instance Show City
98112
deriving instance Eq City
113+
instance Arbitrary City where
114+
arbitrary = genericArbitrary uniform
99115

100116
instance Table CityT where
101117
data PrimaryKey CityT f = CityId (Columnar f Int32) deriving Generic
102118
primaryKey = CityId . cityId
103119
type CityId = PrimaryKey CityT Identity
104120
deriving instance Show CityId
105121
deriving instance Eq CityId
122+
instance Arbitrary CityId where
123+
arbitrary = genericArbitrary uniform -- should be fixed at 1
106124

107125
-- Country table
108126

@@ -115,13 +133,17 @@ data CountryT f
115133
type Country = CountryT Identity
116134
deriving instance Show Country
117135
deriving instance Eq Country
136+
instance Arbitrary Country where
137+
arbitrary = genericArbitrary uniform
118138

119139
instance Table CountryT where
120140
data PrimaryKey CountryT f = CountryId (Columnar f Int32) deriving Generic
121141
primaryKey = CountryId . countryId
122142
type CountryId = PrimaryKey CountryT Identity
123143
deriving instance Show CountryId
124144
deriving instance Eq CountryId
145+
instance Arbitrary CountryId where
146+
arbitrary = genericArbitrary uniform -- should be fixed at 1
125147

126148
-- Actor
127149

@@ -134,13 +156,17 @@ data ActorT f
134156
} deriving Generic
135157
type Actor = ActorT Identity
136158
deriving instance Show Actor; deriving instance Eq Actor
159+
instance Arbitrary Actor where
160+
arbitrary = genericArbitrary uniform
137161

138162
instance Table ActorT where
139163
data PrimaryKey ActorT f = ActorId (Columnar f (SqlSerial Int32))
140164
deriving Generic
141165
primaryKey = ActorId . actorId
142166
type ActorId = PrimaryKey ActorT Identity
143167
deriving instance Show ActorId; deriving instance Eq ActorId
168+
instance Arbitrary ActorId where
169+
arbitrary = genericArbitrary uniform
144170

145171
-- Category
146172

@@ -152,12 +178,16 @@ data CategoryT f
152178
} deriving Generic
153179
type Category = CategoryT Identity
154180
deriving instance Show Category; deriving instance Eq Category
181+
instance Arbitrary Category where
182+
arbitrary = genericArbitrary uniform
155183

156184
instance Table CategoryT where
157185
data PrimaryKey CategoryT f = CategoryId (Columnar f Int32) deriving Generic
158186
primaryKey = CategoryId . categoryId
159187
type CategoryId = PrimaryKey CategoryT Identity
160188
deriving instance Show CategoryId; deriving instance Eq CategoryId
189+
instance Arbitrary CategoryId where
190+
arbitrary = genericArbitrary uniform
161191

162192
-- Customer
163193

@@ -175,13 +205,17 @@ data CustomerT f
175205
} deriving Generic
176206
type Customer = CustomerT Identity
177207
deriving instance Show Customer; deriving instance Eq Customer
208+
instance Arbitrary Customer where
209+
arbitrary = genericArbitrary uniform
178210

179211
instance Table CustomerT where
180212
data PrimaryKey CustomerT f = CustomerId (Columnar f (SqlSerial Int32))
181213
deriving Generic
182214
primaryKey = CustomerId . customerId
183215
type CustomerId = PrimaryKey CustomerT Identity
184216
deriving instance Show CustomerId; deriving instance Eq CustomerId
217+
instance Arbitrary CustomerId where
218+
arbitrary = genericArbitrary uniform
185219

186220
-- Store
187221

@@ -200,6 +234,8 @@ instance Table StoreT where
200234
primaryKey = StoreId . storeId
201235
type StoreId = PrimaryKey StoreT Identity
202236
deriving instance Show StoreId; deriving instance Eq StoreId
237+
instance Arbitrary StoreId where
238+
arbitrary = genericArbitrary uniform
203239

204240
-- Staff
205241

@@ -219,12 +255,16 @@ data StaffT f
219255
} deriving Generic
220256
type Staff = StaffT Identity
221257
deriving instance Eq Staff; deriving instance Show Staff
258+
instance Arbitrary Staff where
259+
arbitrary = genericArbitrary uniform
222260

223261
instance Table StaffT where
224262
data PrimaryKey StaffT f = StaffId (Columnar f Int32) deriving Generic
225263
primaryKey = StaffId . staffId
226264
type StaffId = PrimaryKey StaffT Identity
227265
deriving instance Eq StaffId; deriving instance Show StaffId
266+
instance Arbitrary StaffId where
267+
arbitrary = genericArbitrary uniform
228268

229269
-- Film
230270

@@ -246,6 +286,8 @@ data FilmT f
246286
type Film = FilmT Identity
247287
deriving instance Eq Film
248288
deriving instance Show Film
289+
instance Arbitrary Film where
290+
arbitrary = genericArbitrary uniform
249291

250292
instance Table FilmT where
251293
data PrimaryKey FilmT f = FilmId (Columnar f (SqlSerial Int32))
@@ -254,6 +296,8 @@ instance Table FilmT where
254296
type FilmId = PrimaryKey FilmT Identity
255297
deriving instance Eq FilmId
256298
deriving instance Show FilmId
299+
instance Arbitrary FilmId where
300+
arbitrary = genericArbitrary uniform
257301

258302
-- Film category
259303

@@ -265,13 +309,17 @@ data FilmCategoryT f
265309
} deriving Generic
266310
type FilmCategory = FilmCategoryT Identity
267311
deriving instance Eq FilmCategory; deriving instance Show FilmCategory
312+
instance Arbitrary FilmCategory where
313+
arbitrary = genericArbitrary uniform
268314

269315
instance Table FilmCategoryT where
270316
data PrimaryKey FilmCategoryT f = FilmCategoryId (PrimaryKey CategoryT f) (PrimaryKey FilmT f)
271317
deriving Generic
272318
primaryKey = FilmCategoryId <$> filmCategoryCategory <*> filmCategoryFilm
273319
type FilmCategoryId = PrimaryKey FilmCategoryT Identity
274320
deriving instance Eq FilmCategoryId; deriving instance Show FilmCategoryId
321+
instance Arbitrary FilmCategoryId where
322+
arbitrary = genericArbitrary uniform
275323

276324
-- Language
277325

@@ -283,13 +331,17 @@ data LanguageT f
283331
} deriving Generic
284332
type Language = LanguageT Identity
285333
deriving instance Eq Language; deriving instance Show Language
334+
instance Arbitrary Language where
335+
arbitrary = genericArbitrary uniform
286336

287337
instance Table LanguageT where
288338
data PrimaryKey LanguageT f = LanguageId (Columnar f (SqlSerial Int32))
289339
deriving Generic
290340
primaryKey = LanguageId . languageId
291341
type LanguageId = PrimaryKey LanguageT Identity
292342
deriving instance Eq LanguageId; deriving instance Show LanguageId
343+
instance Arbitrary LanguageId where
344+
arbitrary = genericArbitrary uniform
293345

294346
-- Pagila db
295347

@@ -414,7 +466,7 @@ migration () = do
414466
(field "email" (varchar (Just 50)))
415467
(StoreId (field "store_id" smallint notNull))
416468
(field "active" boolean (defaultTo_ (val_ True)) notNull)
417-
(field "username" (varchar (Just 16)) notNull)
469+
(field "username" (varchar (Just 64)) notNull)
418470
(field "password" binaryLargeObject)
419471
lastUpdateField
420472
(field "picture" (maybeType bytea)))

0 commit comments

Comments
 (0)