Implement saving+loading the game

Implement ToJSON and FromJSON for all of the various pieces of the game
state, and add a pair of functions saveGame/loadGame implementing a
prism to save the game as zlib-compressed JSON. To test this, there's
now Arbitrary, CoArbitrary, and Function instances for all the parts of
the game state - to get around circular imports with the concrete
entities this unfortunately is happening via orphan instances, plus an
hs-boot file to break a circular import that was just a little too hard
to remove by moving things around. Ugh.
This commit is contained in:
Griffin Smith 2019-11-29 14:33:52 -05:00
parent 2f2e5a0b68
commit f37d0f75c0
30 changed files with 620 additions and 97 deletions

View file

@ -1,6 +1,7 @@
import Test.Prelude
import qualified Xanthous.Data.EntityMapSpec
import qualified Xanthous.DataSpec
import qualified Xanthous.EntitiesSpec
import qualified Xanthous.Entities.RawsSpec
import qualified Xanthous.GameSpec
import qualified Xanthous.Generators.UtilSpec
@ -16,6 +17,7 @@ main = defaultMain test
test :: TestTree
test = testGroup "Xanthous"
[ Xanthous.Data.EntityMapSpec.test
, Xanthous.EntitiesSpec.test
, Xanthous.Entities.RawsSpec.test
, Xanthous.GameSpec.test
, Xanthous.Generators.UtilSpec.test

View file

@ -13,6 +13,7 @@ import Test.Tasty.QuickCheck
import Test.Tasty.HUnit
import Test.QuickCheck.Classes
import Test.QuickCheck.Checkers (TestBatch)
import Test.QuickCheck.Instances.ByteString ()
testBatch :: TestBatch -> TestTree
testBatch (name, tests) = testGroup name $ uncurry testProperty <$> tests

View file

@ -2,9 +2,11 @@
--------------------------------------------------------------------------------
module Xanthous.Data.EntityMapSpec where
--------------------------------------------------------------------------------
import Test.Prelude
import Test.Prelude
--------------------------------------------------------------------------------
import Xanthous.Data.EntityMap
import qualified Data.Aeson as JSON
--------------------------------------------------------------------------------
import Xanthous.Data.EntityMap
--------------------------------------------------------------------------------
main :: IO ()
@ -30,4 +32,9 @@ test = localOption (QuickCheckTests 20)
then (em == em)
else True
]
, testGroup "JSON encoding/decoding"
[ testProperty "Preserves IDs" $ \(em :: EntityMap Int) ->
let Just em' = JSON.decode $ JSON.encode em
in toEIDsAndPositioned em' === toEIDsAndPositioned em
]
]

View file

@ -0,0 +1,20 @@
--------------------------------------------------------------------------------
module Xanthous.EntitiesSpec where
--------------------------------------------------------------------------------
import Test.Prelude
--------------------------------------------------------------------------------
import qualified Data.Aeson as JSON
--------------------------------------------------------------------------------
import Xanthous.Entities
--------------------------------------------------------------------------------
main :: IO ()
main = defaultMain test
test :: TestTree
test = testGroup "Xanthous.Entities"
[ testGroup "EntityChar"
[ testProperty "JSON round-trip" $ \(ec :: EntityChar) ->
JSON.decode (JSON.encode ec) === Just ec
]
]

View file

@ -44,4 +44,10 @@ test
(oextend f . oextend g) mh === oextend (f . oextend g) mh
]
]
, testGroup "Saving the game"
[ testProperty "forms a prism" $ isPrism saved
, testProperty "preserves the character ID" $ \gs ->
let Just gs' = loadGame $ saveGame gs
in gs' ^. character === gs ^. character
]
]

View file

@ -1,12 +1,16 @@
{-# LANGUAGE BlockArguments #-}
--------------------------------------------------------------------------------
module Xanthous.OrphansSpec where
import Test.Prelude
import Xanthous.Orphans
import Text.Mustache
import Text.Megaparsec (errorBundlePretty)
import Xanthous.Orphans ()
--------------------------------------------------------------------------------
import Test.Prelude
--------------------------------------------------------------------------------
import Text.Mustache
import Text.Megaparsec (errorBundlePretty)
import Graphics.Vty.Attributes
import qualified Data.Aeson as JSON
--------------------------------------------------------------------------------
import Xanthous.Orphans
--------------------------------------------------------------------------------
main :: IO ()
main = defaultMain test
@ -27,5 +31,12 @@ test = testGroup "Xanthous.Orphans"
$ Right expected === do
(Template actual cache) <- res
maybe (Left "Template not found") Right $ cache ^? at actual
, testProperty "JSON round trip" $ \(tpl :: Template) ->
counterexample (unpack $ ppTemplate tpl)
$ JSON.decode (JSON.encode tpl) === Just tpl
]
, testGroup "Attr"
[ testProperty "JSON round trip" $ \(attr :: Attr) ->
JSON.decode (JSON.encode attr) === Just attr
]
]