module Terminal.Game.Layer.ImperativeSpec where import Terminal.Game.Layer.Imperative import Terminal.Game.Layer.Object.Interface import Terminal.Game.Layer.Object.Narrate import Alone import Test.Hspec import Test.Hspec.QuickCheck import Test.QuickCheck spec :: Spec spec = do let nd = error "" s :: (Integer, Bool, Integer) s = (0, False, 0) lf (t, True, i) Tick = (t+1, True, i+1) lf (t, b, i) Tick = (t+1, b, i ) lf (t, _, i) (KeyPress _) = (t, True, i ) qf (3, _, _) = True qf _ = False es = [Tick, KeyPress 'c', KeyPress 'c', Tick, Tick] g = Game 10 10 nd s lf nd qf describe "runGame" $ do it "does not confuse input and logic" $ testGame g es `shouldBe` (3, True, 2) describe "testGame" $ do r <- runIO $ readRecord "test/alone-recors-test.gr" it "tests a game" $ testGame aloneInARoom r `shouldBe` MyState (20, 66) Stop True it "does not hang on empty/unclosed input" $ testGame aloneInARoom [Tick] `shouldBe` MyState (10, 10) Stop False modifyMaxSize (const 1000) $ it "does not crash/hang on random input" $ property $ \e -> let a = testGame aloneInARoom e in a == a -- todo recordGame untestable? [test] -- describe "recordGame" $ do -- it "does write on file even when an exception occours" $ -- testGame g es `shouldBe` (3, True, 2)