module Control.Timer.TickSpec where import Control.Timer.Tick import Test.Hspec import qualified Control.Exception as E main :: IO () main = hspec spec spec :: Spec spec = do describe "creaTimedRes" $ do it "does not allow creation of empty timed resources" $ E.evaluate (creaTimedRes AlwaysLoop []) `shouldThrow` anyException describe "tick" $ do it "ticks a simple timer" $ let st = creaTimer 1 in isExpired (tick st) `shouldBe` True describe "ticks" $ do let t = creaTimer 10 it "fails on negative integer" $ E.evaluate (ticks (-3) t) `shouldThrow` anyException it "performs a number of ticks" $ isExpired (ticks 10 t) `shouldBe` True it "does not overtick" $ isExpired (ticks 9 t) `shouldBe` False it "does not choke on extra tick" $ isExpired (ticks 80 t) `shouldBe` True describe "loops" $ do let t = creaTimedRes (Times 2) [(1,())] let ta = creaTimedRes AlwaysLoop [(1,())] it "loops appropriately" $ isExpired (ticks 2 t) `shouldBe` True it "loops appropriately (forever)" $ isExpired (ticks 20 ta) `shouldBe` False it "expires appropriately" $ isExpired (ticks 1 t) `shouldBe` False describe "isExpired" $ do let st = creaTimer 10 it "checks if a timer is expired" $ isExpired (ticks 100 st) `shouldBe` True it "complements isLive" $ isExpired (ticks 100 st) `shouldBe` not (isLive (ticks 100 st)) describe "fetch" $ do let ta = creaTimedRes (Times 1) [(1,'a'), (2, 'b'), (1, 'c')] it "gets the underlying resoure" $ fetch (ticks 3 ta) `shouldBe` 'c' describe "reset" $ do let t = creaTimer 10 it "resets the timer" $ reset (ticks 30 t) `shouldBe` t