main.hs 6.4 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192
  1. {-# LANGUAGE ExistentialQuantification #-}
  2. {-# LANGUAGE FlexibleInstances #-}
  3. {-# LANGUAGE QuasiQuotes #-}
  4. {-# LANGUAGE MultiParamTypeClasses #-}
  5. {-# LANGUAGE TemplateHaskell #-}
  6. {-# LANGUAGE TypeFamilies #-}
  7. {-# LANGUAGE UndecidableInstances #-}
  8. {-# OPTIONS_GHC -Wno-unused-top-binds #-}
  9. import MyInit
  10. import Data.Time (Day, UTCTime (..), TimeOfDay, timeToTimeOfDay, timeOfDayToTime)
  11. import Data.Time.Clock.POSIX (utcTimeToPOSIXSeconds, posixSecondsToUTCTime)
  12. import Data.Fixed
  13. import Test.QuickCheck
  14. import qualified Data.Text as T
  15. import Data.IntMap (IntMap)
  16. import qualified Data.ByteString as BS
  17. import qualified CompositeTest
  18. import qualified CustomPersistFieldTest
  19. import qualified CustomPrimaryKeyReferenceTest
  20. import qualified DataTypeTest
  21. import qualified EmbedOrderTest
  22. import qualified EmbedTest
  23. import qualified EmptyEntityTest
  24. import qualified EquivalentTypeTest
  25. import qualified HtmlTest
  26. import qualified InsertDuplicateUpdate
  27. import qualified LargeNumberTest
  28. import qualified MaxLenTest
  29. import qualified MigrationColumnLengthTest
  30. import qualified MigrationIdempotencyTest
  31. import qualified MigrationOnlyTest
  32. import qualified MpsNoPrefixTest
  33. import qualified PersistentTest
  34. import qualified PersistUniqueTest
  35. -- FIXME: Not used... should it be?
  36. -- import qualified PrimaryTest
  37. import qualified RawSqlTest
  38. import qualified ReadWriteTest
  39. import qualified Recursive
  40. import qualified RenameTest
  41. import qualified SumTypeTest
  42. import qualified TransactionLevelTest
  43. import qualified UniqueTest
  44. import qualified UpsertTest
  45. type Tuple a b = (a, b)
  46. -- Test lower case names
  47. share [mkPersist persistSettings, mkMigrate "dataTypeMigrate"] [persistLowerCase|
  48. DataTypeTable no-json
  49. text Text
  50. textMaxLen Text maxlen=100
  51. bytes ByteString
  52. bytesTextTuple (Tuple ByteString Text)
  53. bytesMaxLen ByteString maxlen=100
  54. int Int
  55. intList [Int]
  56. intMap (IntMap Int)
  57. double Double
  58. bool Bool
  59. day Day
  60. pico Pico
  61. time TimeOfDay
  62. utc UTCTime
  63. -- For MySQL, provide extra tests for time fields with fractional seconds,
  64. -- since the default (used above) is to have no fractional part. This
  65. -- requires the server version to be at least 5.6.4, and should be switched
  66. -- off for older servers by defining OLD_MYSQL.
  67. timeFrac TimeOfDay sqltype=TIME(6)
  68. utcFrac UTCTime sqltype=DATETIME(6)
  69. |]
  70. instance Arbitrary (DataTypeTableGeneric backend) where
  71. arbitrary = DataTypeTable
  72. <$> arbText -- text
  73. <*> (T.take 100 <$> arbText) -- textManLen
  74. <*> arbitrary -- bytes
  75. <*> liftA2 (,) arbitrary arbText -- bytesTextTuple
  76. <*> (BS.take 100 <$> arbitrary) -- bytesMaxLen
  77. <*> arbitrary -- int
  78. <*> arbitrary -- intList
  79. <*> arbitrary -- intMap
  80. <*> arbitrary -- double
  81. <*> arbitrary -- bool
  82. <*> arbitrary -- day
  83. <*> arbitrary -- pico
  84. <*> (truncateTimeOfDay =<< arbitrary) -- time
  85. <*> (truncateUTCTime =<< arbitrary) -- utc
  86. <*> (truncateTimeOfDay =<< arbitrary) -- timeFrac
  87. <*> (truncateUTCTime =<< arbitrary) -- utcFrac
  88. setup :: MonadIO m => Migration -> ReaderT SqlBackend m ()
  89. setup migration = do
  90. printMigration migration
  91. runMigrationUnsafe migration
  92. main :: IO ()
  93. main = do
  94. runConn $ do
  95. mapM_ setup
  96. [ PersistentTest.testMigrate
  97. , PersistentTest.noPrefixMigrate
  98. , EmbedTest.embedMigrate
  99. , EmbedOrderTest.embedOrderMigrate
  100. , LargeNumberTest.numberMigrate
  101. , UniqueTest.uniqueMigrate
  102. , MaxLenTest.maxlenMigrate
  103. , Recursive.recursiveMigrate
  104. , CompositeTest.compositeMigrate
  105. , PersistUniqueTest.migration
  106. , RenameTest.migration
  107. , CustomPersistFieldTest.customFieldMigrate
  108. , InsertDuplicateUpdate.duplicateMigrate
  109. , MigrationIdempotencyTest.migration
  110. , CustomPrimaryKeyReferenceTest.migration
  111. , MigrationColumnLengthTest.migration
  112. , TransactionLevelTest.migration
  113. ]
  114. PersistentTest.cleanDB
  115. hspec $ do
  116. RenameTest.specsWith db
  117. DataTypeTest.specsWith
  118. db
  119. (Just (runMigrationSilent dataTypeMigrate))
  120. [ TestFn "text" dataTypeTableText
  121. , TestFn "textMaxLen" dataTypeTableTextMaxLen
  122. , TestFn "bytes" dataTypeTableBytes
  123. , TestFn "bytesTextTuple" dataTypeTableBytesTextTuple
  124. , TestFn "bytesMaxLen" dataTypeTableBytesMaxLen
  125. , TestFn "int" dataTypeTableInt
  126. , TestFn "intList" dataTypeTableIntList
  127. , TestFn "intMap" dataTypeTableIntMap
  128. , TestFn "bool" dataTypeTableBool
  129. , TestFn "day" dataTypeTableDay
  130. , TestFn "time" (roundTime . dataTypeTableTime)
  131. , TestFn "utc" (roundUTCTime . dataTypeTableUtc)
  132. , TestFn "timeFrac" (dataTypeTableTimeFrac)
  133. , TestFn "utcFrac" (dataTypeTableUtcFrac)
  134. ]
  135. [ ("pico", dataTypeTablePico) ]
  136. dataTypeTableDouble
  137. HtmlTest.specsWith
  138. db
  139. (Just (runMigrationSilent HtmlTest.htmlMigrate))
  140. EmbedTest.specsWith db
  141. EmbedOrderTest.specsWith db
  142. LargeNumberTest.specsWith db
  143. UniqueTest.specsWith db
  144. MaxLenTest.specsWith db
  145. Recursive.specsWith db
  146. SumTypeTest.specsWith db (Just (runMigrationSilent SumTypeTest.sumTypeMigrate))
  147. MigrationOnlyTest.specsWith db
  148. (Just
  149. $ runMigrationSilent MigrationOnlyTest.migrateAll1
  150. >> runMigrationSilent MigrationOnlyTest.migrateAll2
  151. )
  152. PersistentTest.specsWith db
  153. PersistentTest.filterOrSpecs db
  154. ReadWriteTest.specsWith db
  155. RawSqlTest.specsWith db
  156. UpsertTest.specsWith
  157. db
  158. UpsertTest.Don'tUpdateNull
  159. UpsertTest.UpsertPreserveOldKey
  160. MpsNoPrefixTest.specsWith db
  161. EmptyEntityTest.specsWith db (Just (runMigrationSilent EmptyEntityTest.migration))
  162. CompositeTest.specsWith db
  163. PersistUniqueTest.specsWith db
  164. CustomPersistFieldTest.specsWith db
  165. CustomPrimaryKeyReferenceTest.specsWith db
  166. InsertDuplicateUpdate.specs
  167. MigrationColumnLengthTest.specsWith db
  168. EquivalentTypeTest.specsWith db
  169. TransactionLevelTest.specsWith db
  170. MigrationIdempotencyTest.specsWith db
  171. roundFn :: RealFrac a => a -> Integer
  172. roundFn = round
  173. roundTime :: TimeOfDay -> TimeOfDay
  174. roundTime t = timeToTimeOfDay $ fromIntegral $ roundFn $ timeOfDayToTime t
  175. roundUTCTime :: UTCTime -> UTCTime
  176. roundUTCTime t =
  177. posixSecondsToUTCTime $ fromIntegral $ roundFn $ utcTimeToPOSIXSeconds t