1
+ {-# OPTIONS_GHC -fno-warn-orphans #-}
1
2
{-# LANGUAGE StandaloneDeriving #-}
2
3
{-# LANGUAGE DeriveAnyClass #-}
3
4
{-# LANGUAGE RecordWildCards #-}
7
8
{-# LANGUAGE FlexibleInstances #-}
8
9
{-# LANGUAGE MultiParamTypeClasses #-}
9
10
{-# LANGUAGE DeriveGeneric #-}
11
+ {-# LANGUAGE DerivingStrategies #-}
12
+ {-# LANGUAGE DerivingVia #-}
10
13
11
14
module Pagila.Schema.V0001 where
12
15
-- TODO explicit module exports
@@ -59,6 +62,9 @@ import Data.Text (Text)
59
62
import Data.ByteString (ByteString )
60
63
import Data.Time.LocalTime (LocalTime )
61
64
import Data.Scientific (Scientific )
65
+ import Test.QuickCheck ( Arbitrary (arbitrary ) )
66
+ import Generic.Random ( genericArbitrary , uniform )
67
+ import Test.QuickCheck.Instances ()
62
68
63
69
-- Address table
64
70
@@ -73,9 +79,12 @@ data AddressT f
73
79
, addressPhone :: Columnar f Text
74
80
, addressLastUpdate :: Columnar f LocalTime
75
81
} deriving Generic
82
+
76
83
type Address = AddressT Identity
77
84
deriving instance Show Address
78
85
deriving instance Eq Address
86
+ instance Arbitrary Address where
87
+ arbitrary = genericArbitrary uniform
79
88
80
89
instance Table AddressT where
81
90
data PrimaryKey AddressT f = AddressId (Columnar f (SqlSerial Int32 )) deriving Generic
@@ -84,6 +93,11 @@ type AddressId = PrimaryKey AddressT Identity
84
93
deriving instance Show AddressId
85
94
deriving instance Eq AddressId
86
95
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
+
87
101
-- City table
88
102
89
103
data CityT f
@@ -96,13 +110,17 @@ data CityT f
96
110
type City = CityT Identity
97
111
deriving instance Show City
98
112
deriving instance Eq City
113
+ instance Arbitrary City where
114
+ arbitrary = genericArbitrary uniform
99
115
100
116
instance Table CityT where
101
117
data PrimaryKey CityT f = CityId (Columnar f Int32 ) deriving Generic
102
118
primaryKey = CityId . cityId
103
119
type CityId = PrimaryKey CityT Identity
104
120
deriving instance Show CityId
105
121
deriving instance Eq CityId
122
+ instance Arbitrary CityId where
123
+ arbitrary = genericArbitrary uniform -- should be fixed at 1
106
124
107
125
-- Country table
108
126
@@ -115,13 +133,17 @@ data CountryT f
115
133
type Country = CountryT Identity
116
134
deriving instance Show Country
117
135
deriving instance Eq Country
136
+ instance Arbitrary Country where
137
+ arbitrary = genericArbitrary uniform
118
138
119
139
instance Table CountryT where
120
140
data PrimaryKey CountryT f = CountryId (Columnar f Int32 ) deriving Generic
121
141
primaryKey = CountryId . countryId
122
142
type CountryId = PrimaryKey CountryT Identity
123
143
deriving instance Show CountryId
124
144
deriving instance Eq CountryId
145
+ instance Arbitrary CountryId where
146
+ arbitrary = genericArbitrary uniform -- should be fixed at 1
125
147
126
148
-- Actor
127
149
@@ -134,13 +156,17 @@ data ActorT f
134
156
} deriving Generic
135
157
type Actor = ActorT Identity
136
158
deriving instance Show Actor ; deriving instance Eq Actor
159
+ instance Arbitrary Actor where
160
+ arbitrary = genericArbitrary uniform
137
161
138
162
instance Table ActorT where
139
163
data PrimaryKey ActorT f = ActorId (Columnar f (SqlSerial Int32 ))
140
164
deriving Generic
141
165
primaryKey = ActorId . actorId
142
166
type ActorId = PrimaryKey ActorT Identity
143
167
deriving instance Show ActorId ; deriving instance Eq ActorId
168
+ instance Arbitrary ActorId where
169
+ arbitrary = genericArbitrary uniform
144
170
145
171
-- Category
146
172
@@ -152,12 +178,16 @@ data CategoryT f
152
178
} deriving Generic
153
179
type Category = CategoryT Identity
154
180
deriving instance Show Category ; deriving instance Eq Category
181
+ instance Arbitrary Category where
182
+ arbitrary = genericArbitrary uniform
155
183
156
184
instance Table CategoryT where
157
185
data PrimaryKey CategoryT f = CategoryId (Columnar f Int32 ) deriving Generic
158
186
primaryKey = CategoryId . categoryId
159
187
type CategoryId = PrimaryKey CategoryT Identity
160
188
deriving instance Show CategoryId ; deriving instance Eq CategoryId
189
+ instance Arbitrary CategoryId where
190
+ arbitrary = genericArbitrary uniform
161
191
162
192
-- Customer
163
193
@@ -175,13 +205,17 @@ data CustomerT f
175
205
} deriving Generic
176
206
type Customer = CustomerT Identity
177
207
deriving instance Show Customer ; deriving instance Eq Customer
208
+ instance Arbitrary Customer where
209
+ arbitrary = genericArbitrary uniform
178
210
179
211
instance Table CustomerT where
180
212
data PrimaryKey CustomerT f = CustomerId (Columnar f (SqlSerial Int32 ))
181
213
deriving Generic
182
214
primaryKey = CustomerId . customerId
183
215
type CustomerId = PrimaryKey CustomerT Identity
184
216
deriving instance Show CustomerId ; deriving instance Eq CustomerId
217
+ instance Arbitrary CustomerId where
218
+ arbitrary = genericArbitrary uniform
185
219
186
220
-- Store
187
221
@@ -200,6 +234,8 @@ instance Table StoreT where
200
234
primaryKey = StoreId . storeId
201
235
type StoreId = PrimaryKey StoreT Identity
202
236
deriving instance Show StoreId ; deriving instance Eq StoreId
237
+ instance Arbitrary StoreId where
238
+ arbitrary = genericArbitrary uniform
203
239
204
240
-- Staff
205
241
@@ -219,12 +255,16 @@ data StaffT f
219
255
} deriving Generic
220
256
type Staff = StaffT Identity
221
257
deriving instance Eq Staff ; deriving instance Show Staff
258
+ instance Arbitrary Staff where
259
+ arbitrary = genericArbitrary uniform
222
260
223
261
instance Table StaffT where
224
262
data PrimaryKey StaffT f = StaffId (Columnar f Int32 ) deriving Generic
225
263
primaryKey = StaffId . staffId
226
264
type StaffId = PrimaryKey StaffT Identity
227
265
deriving instance Eq StaffId ; deriving instance Show StaffId
266
+ instance Arbitrary StaffId where
267
+ arbitrary = genericArbitrary uniform
228
268
229
269
-- Film
230
270
@@ -246,6 +286,8 @@ data FilmT f
246
286
type Film = FilmT Identity
247
287
deriving instance Eq Film
248
288
deriving instance Show Film
289
+ instance Arbitrary Film where
290
+ arbitrary = genericArbitrary uniform
249
291
250
292
instance Table FilmT where
251
293
data PrimaryKey FilmT f = FilmId (Columnar f (SqlSerial Int32 ))
@@ -254,6 +296,8 @@ instance Table FilmT where
254
296
type FilmId = PrimaryKey FilmT Identity
255
297
deriving instance Eq FilmId
256
298
deriving instance Show FilmId
299
+ instance Arbitrary FilmId where
300
+ arbitrary = genericArbitrary uniform
257
301
258
302
-- Film category
259
303
@@ -265,13 +309,17 @@ data FilmCategoryT f
265
309
} deriving Generic
266
310
type FilmCategory = FilmCategoryT Identity
267
311
deriving instance Eq FilmCategory ; deriving instance Show FilmCategory
312
+ instance Arbitrary FilmCategory where
313
+ arbitrary = genericArbitrary uniform
268
314
269
315
instance Table FilmCategoryT where
270
316
data PrimaryKey FilmCategoryT f = FilmCategoryId (PrimaryKey CategoryT f ) (PrimaryKey FilmT f )
271
317
deriving Generic
272
318
primaryKey = FilmCategoryId <$> filmCategoryCategory <*> filmCategoryFilm
273
319
type FilmCategoryId = PrimaryKey FilmCategoryT Identity
274
320
deriving instance Eq FilmCategoryId ; deriving instance Show FilmCategoryId
321
+ instance Arbitrary FilmCategoryId where
322
+ arbitrary = genericArbitrary uniform
275
323
276
324
-- Language
277
325
@@ -283,13 +331,17 @@ data LanguageT f
283
331
} deriving Generic
284
332
type Language = LanguageT Identity
285
333
deriving instance Eq Language ; deriving instance Show Language
334
+ instance Arbitrary Language where
335
+ arbitrary = genericArbitrary uniform
286
336
287
337
instance Table LanguageT where
288
338
data PrimaryKey LanguageT f = LanguageId (Columnar f (SqlSerial Int32 ))
289
339
deriving Generic
290
340
primaryKey = LanguageId . languageId
291
341
type LanguageId = PrimaryKey LanguageT Identity
292
342
deriving instance Eq LanguageId ; deriving instance Show LanguageId
343
+ instance Arbitrary LanguageId where
344
+ arbitrary = genericArbitrary uniform
293
345
294
346
-- Pagila db
295
347
@@ -414,7 +466,7 @@ migration () = do
414
466
(field " email" (varchar (Just 50 )))
415
467
(StoreId (field " store_id" smallint notNull))
416
468
(field " active" boolean (defaultTo_ (val_ True )) notNull)
417
- (field " username" (varchar (Just 16 )) notNull)
469
+ (field " username" (varchar (Just 64 )) notNull)
418
470
(field " password" binaryLargeObject)
419
471
lastUpdateField
420
472
(field " picture" (maybeType bytea)))
0 commit comments