about summary refs log tree commit diff
path: root/users/aspen/xanthous/test/Xanthous/GameSpec.hs
blob: 2fa8527d0e59e52cb7505d9f7f902a5b9cd783f7 (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
module Xanthous.GameSpec where

import Test.Prelude hiding (Down)
import Xanthous.Game
import Xanthous.Game.State
import Control.Lens.Properties
import Xanthous.Data (move, Direction(Down))
import Xanthous.Data.EntityMap (atPosition)

main :: IO ()
main = defaultMain test

test :: TestTree
test
  = localOption (QuickCheckTests 10)
  . localOption (QuickCheckMaxSize 10)
  $ testGroup "Xanthous.Game"
  [ testGroup "positionedCharacter"
    [ testProperty "lens laws" $ isLens positionedCharacter
    , testCase "updates the position of the character" $ do
      initialGame <- getInitialState
      let initialPos = initialGame ^. characterPosition
          updatedGame = initialGame & characterPosition %~ move Down
          updatedPos = updatedGame ^. characterPosition
      updatedPos @?= move Down initialPos
      updatedGame ^. entities . atPosition initialPos @?= fromList []
      updatedGame ^. entities . atPosition updatedPos
        @?= fromList [SomeEntity $ initialGame ^. character]
    ]
  , testGroup "characterPosition"
    [ testProperty "lens laws" $ isLens characterPosition
    ]
  , testGroup "character"
    [ testProperty "lens laws" $ isLens character
    ]
  , testGroup "MessageHistory"
    [ testGroup "MonoComonad laws"
      [ testProperty "oextend oextract ≡ id"
        $ \(mh :: MessageHistory) -> oextend oextract mh === mh
      , testProperty "oextract ∘ oextend f ≡ f"
        $ \(mh :: MessageHistory) f -> (oextract . oextend f) mh === f mh
      , testProperty "oextend f ∘ oextend g ≡ oextend (f . oextend g)"
        $ \(mh :: MessageHistory) f g ->
          (oextend f . oextend g) mh === oextend (f . oextend g) mh
      ]
    ]
  , testGroup "Saving the game"
    [ testProperty "forms a prism" $ isPrism saved
    , testProperty "round-trips" $ \gs ->
        loadGame (saveGame gs) === Just gs
    , testProperty "preserves the character ID" $ \gs ->
        let Just gs' = loadGame $ saveGame gs
        in gs' ^. character === gs ^. character
    ]
  ]