PageRenderTime 22ms CodeModel.GetById 8ms RepoModel.GetById 1ms app.codeStats 0ms

/test/System/Test/Cron.hs

http://github.com/MichaelXavier/cron
Haskell | 363 lines | 273 code | 67 blank | 23 comment | 6 complexity | 1fd1157042ce95058919f04bcdbac08d MD5 | raw file
Possible License(s): BSD-2-Clause
  1. {-# LANGUAGE OverloadedStrings #-}
  2. module System.Test.Cron (tests) where
  3. -------------------------------------------------------------------------------
  4. import Control.Monad
  5. import Data.List (find)
  6. import Data.List.NonEmpty (NonEmpty (..))
  7. import Data.Time.Clock.POSIX
  8. import Hedgehog as HH
  9. import qualified Hedgehog.Gen as Gen
  10. import qualified Hedgehog.Range as Range
  11. -------------------------------------------------------------------------------
  12. import SpecHelper
  13. -------------------------------------------------------------------------------
  14. tests :: TestTree
  15. tests = testGroup "System.Cron"
  16. [ describeScheduleMatches
  17. , describeCronScheduleShow
  18. , describeCrontabEntryShow
  19. , describeCrontabShow
  20. , describeNextMatch
  21. ]
  22. describeScheduleMatches :: TestTree
  23. describeScheduleMatches = testGroup "scheduleMatches"
  24. [
  25. testCase "matches a catch-all" $
  26. scheduleMatches stars (day 5 25 1 2) @?= True
  27. , testCase "matches a specific field" $
  28. scheduleMatches stars { hour = mkHourSpec' (Field (SpecificField' (mkSpecificField' 1)))}
  29. (day 5 25 1 2) @?= True
  30. , testCase "matches a range" $
  31. scheduleMatches stars { dayOfMonth = mkDayOfMonthSpec' (Field (RangeField' (mkRangeField' 3 5)))}
  32. (day 5 4 1 2) @?= True
  33. , testCase "matches a list" $
  34. scheduleMatches stars { month = mkMonthSpec' (ListField (SpecificField' (mkSpecificField' 1) :| [SpecificField' (mkSpecificField' 2), SpecificField' (mkSpecificField' 3)]))}
  35. (day 2 3 1 2) @?= True
  36. , testCase "matches a step field" $
  37. scheduleMatches stars { dayOfMonth = mkDayOfMonthSpec' (StepField' (mkStepField' (RangeField' (mkRangeField' 10 16)) 2))}
  38. (day 5 12 1 2) @?= True
  39. , testCase "does not match something missing the step field" $
  40. scheduleMatches stars { dayOfMonth = mkDayOfMonthSpec' (StepField' (mkStepField' (RangeField' (mkRangeField' 10 16)) 2))}
  41. (day 5 13 1 2) @?= False
  42. , testCase "matches starred stepped fields" $
  43. scheduleMatches stars { minute = mkMinuteSpec' (StepField' (mkStepField' Star 2))}
  44. (day 5 13 1 4) @?= True
  45. , testCase "does not match fields that miss starred stepped fields" $
  46. scheduleMatches stars { minute = mkMinuteSpec' (StepField' (mkStepField' Star 2))}
  47. (day 5 13 1 5) @?= False
  48. , testCase "matches multiple fields at once" $
  49. scheduleMatches stars { minute = mkMinuteSpec' (StepField' (mkStepField' Star 2)),
  50. dayOfMonth = mkDayOfMonthSpec' (Field (SpecificField' (mkSpecificField' 3))),
  51. hour = mkHourSpec' (Field (RangeField' (mkRangeField' 10 14))) }
  52. (day 5 3 13 2) @?= True
  53. , testCase "matches a monday as 1" $
  54. scheduleMatches stars { dayOfWeek = mkDayOfWeekSpec' (Field (SpecificField' (mkSpecificField' 1))) }
  55. (UTCTime (fromGregorian 2014 3 17) 0) @?= True
  56. , testCase "matches a sunday as 0" $
  57. scheduleMatches stars { dayOfWeek = mkDayOfWeekSpec' (Field (SpecificField' (mkSpecificField' 0))) }
  58. (UTCTime (fromGregorian 2014 3 16) 0) @?= True
  59. , testCase "matches a sunday as 7" $
  60. scheduleMatches stars { dayOfWeek = mkDayOfWeekSpec' (Field (SpecificField' (mkSpecificField' 7))) }
  61. (UTCTime (fromGregorian 2014 3 16) 0) @?= True
  62. , testCase "matches weekly on a sunday at 0:00" $
  63. scheduleMatches weekly (UTCTime (fromGregorian 2014 4 6) 0) @?= True
  64. , testCase "does not match weekly on a sunday at some time past midnight" $
  65. scheduleMatches weekly (UTCTime (fromGregorian 2014 6 4) 600) @?= False
  66. , testCase "does not match weekly on another day at midnight" $
  67. scheduleMatches weekly (UTCTime (fromGregorian 2014 6 5) 600) @?= False
  68. , testCase "only needs weekday or monthday to match" $
  69. -- man 5 crontab:
  70. -- Note: The day of a command's execution can be specified by two
  71. -- fields day of month, and day of week. If both fields are
  72. -- restricted (i.e., aren't *), the command will be run when either
  73. -- field matches the current time. For example, ``30 4 1,15 * 5''
  74. -- would cause a command to be run at 4:30 am on the 1st and 15th of
  75. -- each month, plus every Friday. One can, however, achieve the
  76. -- desired result by adding a test to the command (see the last
  77. -- example in EXAMPLE CRON FILE below).
  78. --
  79. -- so we deliberately set the correct day of month but wrong day of week
  80. scheduleMatches stars { dayOfWeek = mkDayOfWeekSpec' (Field (SpecificField' (mkSpecificField' 1))),
  81. dayOfMonth = mkDayOfMonthSpec' (Field (SpecificField' (mkSpecificField' 1))) }
  82. (UTCTime (fromGregorian 2014 11 1) 600) @?= True
  83. -- https://github.com/MichaelXavier/cron/issues/18
  84. , testCase "correctly schedules steps and ranges" $ do
  85. let Right oddMinute = parseOnly cronSchedule "1-59/2 * * * *"
  86. let Right evenMinute = parseOnly cronSchedule "0-59/2 * * * *"
  87. let t1 = mkTime 2015 7 17 15 17 0
  88. let t2 = mkTime 2015 7 17 15 18 0
  89. scheduleMatches oddMinute t1 @?= True
  90. scheduleMatches oddMinute t2 @?= False
  91. scheduleMatches evenMinute t1 @?= False
  92. scheduleMatches evenMinute t2 @?= True
  93. , testProperty "star matches everything" $ property $ do
  94. t <- forAll gen
  95. HH.assert (scheduleMatches stars t)
  96. , testProperty "exact time matches" $ property $ do
  97. t <- forAll gen
  98. let (_, m, d, h, mn) = timeComponents t
  99. sched = CronSchedule (mkMinuteSpec' (Field (SpecificField' (mkSpecificField' mn))))
  100. (mkHourSpec' (Field (SpecificField' (mkSpecificField' h))))
  101. (mkDayOfMonthSpec' (Field (SpecificField' (mkSpecificField' d))))
  102. (mkMonthSpec' (Field (SpecificField' (mkSpecificField' m))))
  103. (mkDayOfWeekSpec' (Field Star))
  104. HH.assert (scheduleMatches sched t)
  105. , testProperty "any time with the same minute as n * * * * matches" $ property $ do
  106. (y, m, d, h, mn) <- forAll genTimeFields
  107. let sched = stars { minute = mkMinuteSpec' (Field (SpecificField' (mkSpecificField' mn))) }
  108. t = day' y m d h mn
  109. HH.assert (scheduleMatches sched t)
  110. , testProperty "any time with the diff minute as n * * * * does not match" $ property $ do
  111. (y, m, d, h, mn) <- forAll genTimeFields
  112. let sched = stars { minute = mkMinuteSpec' (Field (SpecificField' (mkSpecificField' (stepMax 59 mn)))) }
  113. t = day' y m d h mn
  114. HH.assert (not (scheduleMatches sched t))
  115. , testProperty "any time with the same hour as * n * * * matches" $ property $ do
  116. (y, m, d, h, mn) <- forAll genTimeFields
  117. let sched = stars { hour = mkHourSpec' (Field (SpecificField' (mkSpecificField' h))) }
  118. t = day' y m d h mn
  119. HH.assert (scheduleMatches sched t)
  120. , testProperty "any time with the diff hour as * n * * * does not match" $ property $ do
  121. (y, m, d, h, mn) <- forAll genTimeFields
  122. let sched = stars { hour = mkHourSpec' (Field (SpecificField' (mkSpecificField' (stepMax 23 h)))) }
  123. t = day' y m d h mn
  124. HH.assert (not (scheduleMatches sched t))
  125. , testProperty "any time with the same day as * * n * * matches" $ property $ do
  126. t <- forAll gen
  127. let (_, m, d, h, mn) = timeComponents t
  128. sched = CronSchedule (mkMinuteSpec' (Field (SpecificField' (mkSpecificField' mn))))
  129. (mkHourSpec' (Field (SpecificField' (mkSpecificField' h))))
  130. (mkDayOfMonthSpec' (Field (SpecificField' (mkSpecificField' d))))
  131. (mkMonthSpec' (Field (SpecificField' (mkSpecificField' m))))
  132. (mkDayOfWeekSpec' (Field Star))
  133. HH.assert (scheduleMatches sched t)
  134. , testProperty "any time with the diff day as * * n * * does not match" $ property $ do
  135. (y, m, d, h, mn) <- forAll genTimeFields
  136. let sched = stars { dayOfMonth = mkDayOfMonthSpec' (Field (SpecificField' (mkSpecificField' (stepMax 31 d)))) }
  137. t = day' y m d h mn
  138. HH.assert (not (scheduleMatches sched t))
  139. ]
  140. where day = day' 2012
  141. day' y m d h mn = UTCTime (fromGregorian y m d) (diffTime h mn)
  142. diffTime h mn = timeOfDayToTime $ TimeOfDay h mn 1
  143. genTimeFields
  144. :: Gen (Integer, Int, Int, Int, Int)
  145. genTimeFields = do
  146. y <- Gen.integral (Range.linear 0 9999)
  147. m <- Gen.int (Range.linear 1 12)
  148. d <- Gen.int (Range.linear 1 28)
  149. h <- Gen.int (Range.linear 1 23)
  150. mn <- Gen.int (Range.linear 1 59)
  151. pure (y, m, d, h, mn)
  152. hoursMins :: DiffTime -> (Int, Int)
  153. hoursMins uTime = (hr, mn)
  154. where
  155. TimeOfDay { todHour = hr,
  156. todMin = mn} = timeToTimeOfDay uTime
  157. stepMax :: (Enum a, Ord a) => a -> a -> a
  158. stepMax mx n | n < mx = succ n
  159. | otherwise = pred n
  160. describeCronScheduleShow :: TestTree
  161. describeCronScheduleShow = testGroup "CronSchedule show"
  162. [
  163. testCase "formats stars" $
  164. show stars @?= "CronSchedule * * * * *"
  165. , testCase "formats specific numbers" $
  166. show stars { dayOfWeek = mkDayOfWeekSpec' (Field (SpecificField' (mkSpecificField' 3)))} @?=
  167. "CronSchedule * * * * 3"
  168. , testCase "formats lists" $
  169. show stars { minute = mkMinuteSpec' (ListField (SpecificField' (mkSpecificField' 1) :| [SpecificField' (mkSpecificField' 2), SpecificField' (mkSpecificField' 3)]))} @?=
  170. "CronSchedule 1,2,3 * * * *"
  171. , testCase "formats ranges" $
  172. show stars { hour = mkHourSpec' (Field (RangeField' (mkRangeField' 7 10)))} @?=
  173. "CronSchedule * 7-10 * * *"
  174. , testCase "formats steps" $
  175. show stars { dayOfMonth = mkDayOfMonthSpec' (StepField' (mkStepField' Star 2))} @?=
  176. "CronSchedule * * */2 * *"
  177. , testCase "formats @yearly" $
  178. show yearly @?= "CronSchedule 0 0 1 1 *"
  179. , testCase "formats @monthly" $
  180. show monthly @?= "CronSchedule 0 0 1 * *"
  181. , testCase "formats @weekly" $
  182. show weekly @?= "CronSchedule 0 0 * * 0"
  183. , testCase "formats @daily" $
  184. show daily @?= "CronSchedule 0 0 * * *"
  185. , testCase "formats @hourly" $
  186. show hourly @?= "CronSchedule 0 * * * *"
  187. , testCase "formats everyMinute" $
  188. show everyMinute @?= "CronSchedule * * * * *"
  189. ]
  190. describeCrontabShow :: TestTree
  191. describeCrontabShow = testGroup "Crontab Show"
  192. [
  193. testCase "prints nothing for an empty crontab" $
  194. show (Crontab []) @?= ""
  195. ]
  196. describeCrontabEntryShow :: TestTree
  197. describeCrontabEntryShow = testGroup "CrontabEntry Show"
  198. [
  199. testCase "formats environment variable sets" $
  200. show envSet @?= "FOO=BAR"
  201. , testCase "formats command entries" $
  202. show entry @?= "* * * * * do stuff"
  203. ]
  204. describeNextMatch :: TestTree
  205. describeNextMatch = testGroup "nextMatch"
  206. [ testProperty "is always in the future (at least 1 minute advanced)" $ property $ do
  207. cs <- forAll gen
  208. t <- forAll gen
  209. let tSecs = floor (utcTimeToPOSIXSeconds t) :: Integer
  210. minT2 = posixSecondsToUTCTime (fromInteger ((tSecs `div` 60) + 1) * 60)
  211. case nextMatch cs t of
  212. Just t2 -> HH.assert (t2 >= minT2)
  213. Nothing -> success
  214. , testProperty "always produces a time that will match the schedule" $ property $ do
  215. cs <- forAll gen
  216. t <- forAll gen
  217. case nextMatch cs t of
  218. Just t2 -> do
  219. unless (scheduleMatches cs t2) $ do
  220. annotate (show t2 <> " does not match " <> show cs)
  221. failure
  222. Nothing -> success
  223. -- , testCase "special case" $ do
  224. -- let Right cs = parseOnly cronSchedule "* * * * *"
  225. -- t = mkTime 1858 11 20 0 0 1
  226. -- nextMatch cs t @?= Just (mkTime 1858 11 20 0 1 0)
  227. -- this test has a really variable workload but is usually quite slow because it has to walk minute by minute until it finds the test case, so we'll set an upper bound here
  228. --TODO: resize 20?
  229. , testProperty "returns the first minute in the future that matches" $ property $ do
  230. cs <- forAll gen
  231. t <- forAll gen
  232. case nextMatch cs t of
  233. Just res ->
  234. let mactual = find (scheduleMatches cs) ((takeWhile (<= res) (nextMinutes t)))
  235. in case mactual of
  236. Just actual -> res `sameMinute` actual
  237. Nothing -> do
  238. annotate ("Could not find a next minute match for " <> show t <> ", expected " <> show res)
  239. failure
  240. Nothing -> success
  241. , testProperty "a schedule that produces Just for one t will produce it for any t" $ property $ do
  242. cs <- forAll gen
  243. t1 <- forAll (Gen.filter (isJust . nextMatch cs) gen)
  244. t2 <- forAll gen
  245. unless (isJust (nextMatch cs t2) == True) $ do
  246. annotate ("nextMatch produced Just for " <> show t1 <> " but not " <> show t2)
  247. failure
  248. , testCase "does not match impossible dates (restricted dow/dom bug)" $ do
  249. let t = posixSecondsToUTCTime 0
  250. let cs = stars { month = mkMonthSpec' (Field (SpecificField' (mkSpecificField' 9)))
  251. , dayOfMonth = mkDayOfMonthSpec' (ListField (SpecificField' (mkSpecificField' 31) :| []))
  252. , dayOfWeek = mkDayOfWeekSpec' (ListField (Star :| []))
  253. }
  254. nextMatch cs t @?= Nothing
  255. ]
  256. sameMinute :: (MonadTest m) => UTCTime -> UTCTime -> m ()
  257. sameMinute t1 t2 = t1' === t2'
  258. where
  259. t1' = t1 { utctDayTime = roundToMinute (utctDayTime t1)}
  260. t2' = t2 { utctDayTime = roundToMinute (utctDayTime t2)}
  261. nextMinutes :: UTCTime -> [UTCTime]
  262. nextMinutes t = [ addMinutes tRounded mins | mins <- [1..]]
  263. where
  264. addMinutes time mins = addUTCTime (fromInteger (60 * mins)) time
  265. -- round down to nearest 60
  266. tRounded = t { utctDayTime = roundToMinute (utctDayTime t)}
  267. roundToMinute :: DiffTime -> DiffTime
  268. roundToMinute n = secondsToDiffTime (nInt - (nInt `mod` 60))
  269. where
  270. nInt = truncate n
  271. envSet :: CrontabEntry
  272. envSet = EnvVariable "FOO" "BAR"
  273. entry :: CrontabEntry
  274. entry = CommandEntry stars (CronCommand "do stuff")
  275. stars :: CronSchedule
  276. stars = CronSchedule (mkMinuteSpec' (Field Star))
  277. (mkHourSpec' (Field Star))
  278. (mkDayOfMonthSpec' (Field Star))
  279. (mkMonthSpec' (Field Star))
  280. (mkDayOfWeekSpec' (Field Star))
  281. timeComponents :: UTCTime -> (Integer, Int, Int, Int, Int)
  282. timeComponents (UTCTime dy dt) = (y, m, d, h, mn)
  283. where
  284. (y, m, d) = toGregorian dy
  285. (h, mn) = hoursMins dt
  286. mkTime
  287. :: Integer
  288. -> Int
  289. -> Int
  290. -> DiffTime
  291. -> DiffTime
  292. -> DiffTime
  293. -> UTCTime
  294. mkTime y m d hr mn s = UTCTime day time
  295. where day = fromGregorian y m d
  296. time = s + 60 * mn + 60 * 60 * hr