1+ {-# OPTIONS_GHC -fno-warn-orphans #-}
12{-# LANGUAGE StandaloneDeriving #-}
23{-# LANGUAGE DeriveAnyClass #-}
34{-# LANGUAGE RecordWildCards #-}
78{-# LANGUAGE FlexibleInstances #-}
89{-# LANGUAGE MultiParamTypeClasses #-}
910{-# LANGUAGE DeriveGeneric #-}
11+ {-# LANGUAGE DerivingStrategies #-}
12+ {-# LANGUAGE DerivingVia #-}
1013
1114module Pagila.Schema.V0001 where
1215-- TODO explicit module exports
@@ -59,6 +62,9 @@ import Data.Text (Text)
5962import Data.ByteString (ByteString )
6063import Data.Time.LocalTime (LocalTime )
6164import 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+
7683type Address = AddressT Identity
7784deriving instance Show Address
7885deriving instance Eq Address
86+ instance Arbitrary Address where
87+ arbitrary = genericArbitrary uniform
7988
8089instance Table AddressT where
8190 data PrimaryKey AddressT f = AddressId (Columnar f (SqlSerial Int32 )) deriving Generic
@@ -84,6 +93,11 @@ type AddressId = PrimaryKey AddressT Identity
8493deriving instance Show AddressId
8594deriving 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
89103data CityT f
@@ -96,13 +110,17 @@ data CityT f
96110type City = CityT Identity
97111deriving instance Show City
98112deriving instance Eq City
113+ instance Arbitrary City where
114+ arbitrary = genericArbitrary uniform
99115
100116instance Table CityT where
101117 data PrimaryKey CityT f = CityId (Columnar f Int32 ) deriving Generic
102118 primaryKey = CityId . cityId
103119type CityId = PrimaryKey CityT Identity
104120deriving instance Show CityId
105121deriving 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
115133type Country = CountryT Identity
116134deriving instance Show Country
117135deriving instance Eq Country
136+ instance Arbitrary Country where
137+ arbitrary = genericArbitrary uniform
118138
119139instance Table CountryT where
120140 data PrimaryKey CountryT f = CountryId (Columnar f Int32 ) deriving Generic
121141 primaryKey = CountryId . countryId
122142type CountryId = PrimaryKey CountryT Identity
123143deriving instance Show CountryId
124144deriving 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
135157type Actor = ActorT Identity
136158deriving instance Show Actor ; deriving instance Eq Actor
159+ instance Arbitrary Actor where
160+ arbitrary = genericArbitrary uniform
137161
138162instance Table ActorT where
139163 data PrimaryKey ActorT f = ActorId (Columnar f (SqlSerial Int32 ))
140164 deriving Generic
141165 primaryKey = ActorId . actorId
142166type ActorId = PrimaryKey ActorT Identity
143167deriving 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
153179type Category = CategoryT Identity
154180deriving instance Show Category ; deriving instance Eq Category
181+ instance Arbitrary Category where
182+ arbitrary = genericArbitrary uniform
155183
156184instance Table CategoryT where
157185 data PrimaryKey CategoryT f = CategoryId (Columnar f Int32 ) deriving Generic
158186 primaryKey = CategoryId . categoryId
159187type CategoryId = PrimaryKey CategoryT Identity
160188deriving 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
176206type Customer = CustomerT Identity
177207deriving instance Show Customer ; deriving instance Eq Customer
208+ instance Arbitrary Customer where
209+ arbitrary = genericArbitrary uniform
178210
179211instance Table CustomerT where
180212 data PrimaryKey CustomerT f = CustomerId (Columnar f (SqlSerial Int32 ))
181213 deriving Generic
182214 primaryKey = CustomerId . customerId
183215type CustomerId = PrimaryKey CustomerT Identity
184216deriving 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
201235type StoreId = PrimaryKey StoreT Identity
202236deriving 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
220256type Staff = StaffT Identity
221257deriving instance Eq Staff ; deriving instance Show Staff
258+ instance Arbitrary Staff where
259+ arbitrary = genericArbitrary uniform
222260
223261instance Table StaffT where
224262 data PrimaryKey StaffT f = StaffId (Columnar f Int32 ) deriving Generic
225263 primaryKey = StaffId . staffId
226264type StaffId = PrimaryKey StaffT Identity
227265deriving 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
246286type Film = FilmT Identity
247287deriving instance Eq Film
248288deriving instance Show Film
289+ instance Arbitrary Film where
290+ arbitrary = genericArbitrary uniform
249291
250292instance Table FilmT where
251293 data PrimaryKey FilmT f = FilmId (Columnar f (SqlSerial Int32 ))
@@ -254,6 +296,8 @@ instance Table FilmT where
254296type FilmId = PrimaryKey FilmT Identity
255297deriving instance Eq FilmId
256298deriving 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
266310type FilmCategory = FilmCategoryT Identity
267311deriving instance Eq FilmCategory ; deriving instance Show FilmCategory
312+ instance Arbitrary FilmCategory where
313+ arbitrary = genericArbitrary uniform
268314
269315instance Table FilmCategoryT where
270316 data PrimaryKey FilmCategoryT f = FilmCategoryId (PrimaryKey CategoryT f ) (PrimaryKey FilmT f )
271317 deriving Generic
272318 primaryKey = FilmCategoryId <$> filmCategoryCategory <*> filmCategoryFilm
273319type FilmCategoryId = PrimaryKey FilmCategoryT Identity
274320deriving 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
284332type Language = LanguageT Identity
285333deriving instance Eq Language ; deriving instance Show Language
334+ instance Arbitrary Language where
335+ arbitrary = genericArbitrary uniform
286336
287337instance Table LanguageT where
288338 data PrimaryKey LanguageT f = LanguageId (Columnar f (SqlSerial Int32 ))
289339 deriving Generic
290340 primaryKey = LanguageId . languageId
291341type LanguageId = PrimaryKey LanguageT Identity
292342deriving 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