Store revealed positions on the level itself
This was a bit of an oversight initially - we should be storing the positions that the character has seen *on the level*, rather than on the entire game state, for obvious reasons. This introduces a GameLevel record, which has this field, the entities, and also the up staircase position, which we can *also* use to position the character after going down to a level we've already visited.
This commit is contained in:
parent
72edcff323
commit
7082a4088b
5 changed files with 61 additions and 19 deletions
|
@ -1,5 +1,6 @@
|
||||||
{-# LANGUAGE ViewPatterns #-}
|
{-# LANGUAGE ViewPatterns #-}
|
||||||
{-# LANGUAGE UndecidableInstances #-}
|
{-# LANGUAGE UndecidableInstances #-}
|
||||||
|
{-# LANGUAGE RecordWildCards #-}
|
||||||
--------------------------------------------------------------------------------
|
--------------------------------------------------------------------------------
|
||||||
module Xanthous.App (makeApp) where
|
module Xanthous.App (makeApp) where
|
||||||
--------------------------------------------------------------------------------
|
--------------------------------------------------------------------------------
|
||||||
|
@ -298,7 +299,7 @@ handleCommand GoDown = do
|
||||||
then do
|
then do
|
||||||
levs <- use levels
|
levs <- use levels
|
||||||
let newLevelNum = Levels.pos levs + 1
|
let newLevelNum = Levels.pos levs + 1
|
||||||
levs' <- nextLevel (levelToEntityMap <$> genLevel newLevelNum) levs
|
levs' <- nextLevel (levelToGameLevel <$> genLevel newLevelNum) levs
|
||||||
cEID <- use characterEntityID
|
cEID <- use characterEntityID
|
||||||
pCharacter <- entities . at cEID <<.= Nothing
|
pCharacter <- entities . at cEID <<.= Nothing
|
||||||
levels .= levs'
|
levels .= levs'
|
||||||
|
@ -600,3 +601,10 @@ genLevel _num = do
|
||||||
Dungeon -> generateLevel SDungeon Dungeon.defaultParams dims
|
Dungeon -> generateLevel SDungeon Dungeon.defaultParams dims
|
||||||
characterPosition .= level ^. levelCharacterPosition
|
characterPosition .= level ^. levelCharacterPosition
|
||||||
pure $!! level
|
pure $!! level
|
||||||
|
|
||||||
|
levelToGameLevel :: Level -> GameLevel
|
||||||
|
levelToGameLevel level =
|
||||||
|
let _levelEntities = levelToEntityMap level
|
||||||
|
_upStaircasePosition = level ^. levelCharacterPosition
|
||||||
|
_levelRevealedPositions = mempty
|
||||||
|
in GameLevel {..}
|
||||||
|
|
|
@ -40,6 +40,8 @@ instance FromJSON SomeEntity where
|
||||||
"GroundMessage" -> SomeEntity @GroundMessage <$> obj .: "data"
|
"GroundMessage" -> SomeEntity @GroundMessage <$> obj .: "data"
|
||||||
_ -> fail . unpack $ "Invalid entity type \"" <> entityType <> "\""
|
_ -> fail . unpack $ "Invalid entity type \"" <> entityType <> "\""
|
||||||
|
|
||||||
|
deriving via WithOptions '[ FieldLabelModifier '[Drop 1] ] GameLevel
|
||||||
|
instance FromJSON GameLevel
|
||||||
deriving via WithOptions '[ FieldLabelModifier '[Drop 1] ] GameState
|
deriving via WithOptions '[ FieldLabelModifier '[Drop 1] ] GameState
|
||||||
instance FromJSON GameState
|
instance FromJSON GameState
|
||||||
|
|
||||||
|
|
|
@ -16,20 +16,26 @@ import qualified Xanthous.Data.EntityMap as EntityMap
|
||||||
import Xanthous.Entities.Entities ()
|
import Xanthous.Entities.Entities ()
|
||||||
import Xanthous.Entities.Character
|
import Xanthous.Entities.Character
|
||||||
import Xanthous.Game.State
|
import Xanthous.Game.State
|
||||||
|
import Xanthous.Util.QuickCheck (GenericArbitrary(..))
|
||||||
--------------------------------------------------------------------------------
|
--------------------------------------------------------------------------------
|
||||||
|
|
||||||
|
deriving via GenericArbitrary GameLevel instance Arbitrary GameLevel
|
||||||
|
|
||||||
instance Arbitrary GameState where
|
instance Arbitrary GameState where
|
||||||
arbitrary = do
|
arbitrary = do
|
||||||
chr <- arbitrary @Character
|
chr <- arbitrary @Character
|
||||||
charPos <- arbitrary
|
_upStaircasePosition <- arbitrary
|
||||||
_messageHistory <- arbitrary
|
_messageHistory <- arbitrary
|
||||||
levs <- arbitrary
|
levs <- arbitrary @(Levels GameLevel)
|
||||||
let (_characterEntityID, currentLevel) =
|
_levelRevealedPositions <-
|
||||||
EntityMap.insertAtReturningID charPos (SomeEntity chr)
|
fmap setFromList
|
||||||
$ extract levs
|
. sublistOf
|
||||||
_levels = levs & current .~ currentLevel
|
. foldMap (EntityMap.positions . _levelEntities)
|
||||||
_revealedPositions <- fmap setFromList . sublistOf
|
$ levs
|
||||||
$ foldMap EntityMap.positions levs
|
let (_characterEntityID, _levelEntities) =
|
||||||
|
EntityMap.insertAtReturningID _upStaircasePosition (SomeEntity chr)
|
||||||
|
$ levs ^. current . levelEntities
|
||||||
|
_levels = levs & current .~ GameLevel {..}
|
||||||
_randomGen <- mkStdGen <$> arbitrary
|
_randomGen <- mkStdGen <$> arbitrary
|
||||||
let _promptState = NoPrompt -- TODO
|
let _promptState = NoPrompt -- TODO
|
||||||
_activePanel <- arbitrary
|
_activePanel <- arbitrary
|
||||||
|
@ -38,6 +44,8 @@ instance Arbitrary GameState where
|
||||||
pure $ GameState {..}
|
pure $ GameState {..}
|
||||||
|
|
||||||
|
|
||||||
|
instance CoArbitrary GameLevel
|
||||||
|
instance Function GameLevel
|
||||||
instance CoArbitrary GameState
|
instance CoArbitrary GameState
|
||||||
instance Function GameState
|
instance Function GameState
|
||||||
deriving newtype instance CoArbitrary (m (a, GameState)) => CoArbitrary (AppT m a)
|
deriving newtype instance CoArbitrary (m (a, GameState)) => CoArbitrary (AppT m a)
|
||||||
|
|
|
@ -39,14 +39,16 @@ initialStateFromSeed :: Int -> GameState
|
||||||
initialStateFromSeed seed =
|
initialStateFromSeed seed =
|
||||||
let _randomGen = mkStdGen seed
|
let _randomGen = mkStdGen seed
|
||||||
chr = mkCharacter
|
chr = mkCharacter
|
||||||
(_characterEntityID, level)
|
_upStaircasePosition = Position 0 0
|
||||||
|
(_characterEntityID, _levelEntities)
|
||||||
= EntityMap.insertAtReturningID
|
= EntityMap.insertAtReturningID
|
||||||
(Position 0 0)
|
_upStaircasePosition
|
||||||
(SomeEntity chr)
|
(SomeEntity chr)
|
||||||
mempty
|
mempty
|
||||||
|
_levelRevealedPositions = mempty
|
||||||
|
level = GameLevel {..}
|
||||||
_levels = oneLevel level
|
_levels = oneLevel level
|
||||||
_messageHistory = mempty
|
_messageHistory = mempty
|
||||||
_revealedPositions = mempty
|
|
||||||
_promptState = NoPrompt
|
_promptState = NoPrompt
|
||||||
_activePanel = Nothing
|
_activePanel = Nothing
|
||||||
_debugState = DebugState
|
_debugState = DebugState
|
||||||
|
|
|
@ -17,6 +17,12 @@ module Xanthous.Game.State
|
||||||
, characterEntityID
|
, characterEntityID
|
||||||
, GamePromptState(..)
|
, GamePromptState(..)
|
||||||
|
|
||||||
|
-- * Game Level
|
||||||
|
, GameLevel(..)
|
||||||
|
, levelEntities
|
||||||
|
, upStaircasePosition
|
||||||
|
, levelRevealedPositions
|
||||||
|
|
||||||
-- * Messages
|
-- * Messages
|
||||||
, MessageHistory(..)
|
, MessageHistory(..)
|
||||||
, HasMessages(..)
|
, HasMessages(..)
|
||||||
|
@ -80,6 +86,7 @@ import qualified Graphics.Vty.Attributes as Vty
|
||||||
import qualified Graphics.Vty.Image as Vty
|
import qualified Graphics.Vty.Image as Vty
|
||||||
--------------------------------------------------------------------------------
|
--------------------------------------------------------------------------------
|
||||||
import Xanthous.Util (KnownBool(..))
|
import Xanthous.Util (KnownBool(..))
|
||||||
|
import Xanthous.Util.QuickCheck (GenericArbitrary(..))
|
||||||
import Xanthous.Data
|
import Xanthous.Data
|
||||||
import Xanthous.Data.Levels
|
import Xanthous.Data.Levels
|
||||||
import Xanthous.Data.EntityMap (EntityMap, EntityID)
|
import Xanthous.Data.EntityMap (EntityMap, EntityID)
|
||||||
|
@ -98,6 +105,7 @@ data MessageHistory
|
||||||
}
|
}
|
||||||
deriving stock (Show, Eq, Generic)
|
deriving stock (Show, Eq, Generic)
|
||||||
deriving anyclass (NFData, CoArbitrary, Function)
|
deriving anyclass (NFData, CoArbitrary, Function)
|
||||||
|
deriving Arbitrary via GenericArbitrary MessageHistory
|
||||||
deriving (ToJSON, FromJSON)
|
deriving (ToJSON, FromJSON)
|
||||||
via WithOptions '[ FieldLabelModifier '[Drop 1] ]
|
via WithOptions '[ FieldLabelModifier '[Drop 1] ]
|
||||||
MessageHistory
|
MessageHistory
|
||||||
|
@ -113,9 +121,6 @@ instance Semigroup MessageHistory where
|
||||||
instance Monoid MessageHistory where
|
instance Monoid MessageHistory where
|
||||||
mempty = MessageHistory mempty 0 Nothing
|
mempty = MessageHistory mempty 0 Nothing
|
||||||
|
|
||||||
instance Arbitrary MessageHistory where
|
|
||||||
arbitrary = genericArbitrary
|
|
||||||
|
|
||||||
type instance Element MessageHistory = [Text]
|
type instance Element MessageHistory = [Text]
|
||||||
instance MonoFunctor MessageHistory where
|
instance MonoFunctor MessageHistory where
|
||||||
omap f mh@(MessageHistory _ t _) =
|
omap f mh@(MessageHistory _ t _) =
|
||||||
|
@ -400,6 +405,19 @@ instance
|
||||||
|
|
||||||
--------------------------------------------------------------------------------
|
--------------------------------------------------------------------------------
|
||||||
|
|
||||||
|
data GameLevel = GameLevel
|
||||||
|
{ _levelEntities :: !(EntityMap SomeEntity)
|
||||||
|
, _upStaircasePosition :: !Position
|
||||||
|
, _levelRevealedPositions :: !(Set Position)
|
||||||
|
}
|
||||||
|
deriving stock (Show, Eq, Generic)
|
||||||
|
deriving anyclass (NFData)
|
||||||
|
deriving (ToJSON)
|
||||||
|
via WithOptions '[ FieldLabelModifier '[Drop 1] ]
|
||||||
|
GameLevel
|
||||||
|
|
||||||
|
--------------------------------------------------------------------------------
|
||||||
|
|
||||||
|
|
||||||
data DebugState = DebugState
|
data DebugState = DebugState
|
||||||
{ _allRevealed :: !Bool
|
{ _allRevealed :: !Bool
|
||||||
|
@ -415,8 +433,7 @@ instance Arbitrary DebugState where
|
||||||
arbitrary = genericArbitrary
|
arbitrary = genericArbitrary
|
||||||
|
|
||||||
data GameState = GameState
|
data GameState = GameState
|
||||||
{ _levels :: !(Levels (EntityMap SomeEntity))
|
{ _levels :: !(Levels GameLevel)
|
||||||
, _revealedPositions :: !(Set Position)
|
|
||||||
, _characterEntityID :: !EntityID
|
, _characterEntityID :: !EntityID
|
||||||
, _messageHistory :: !MessageHistory
|
, _messageHistory :: !MessageHistory
|
||||||
, _randomGen :: !StdGen
|
, _randomGen :: !StdGen
|
||||||
|
@ -433,10 +450,15 @@ data GameState = GameState
|
||||||
deriving (ToJSON)
|
deriving (ToJSON)
|
||||||
via WithOptions '[ FieldLabelModifier '[Drop 1] ]
|
via WithOptions '[ FieldLabelModifier '[Drop 1] ]
|
||||||
GameState
|
GameState
|
||||||
|
|
||||||
|
makeLenses ''GameLevel
|
||||||
makeLenses ''GameState
|
makeLenses ''GameState
|
||||||
|
|
||||||
entities :: Lens' GameState (EntityMap SomeEntity)
|
entities :: Lens' GameState (EntityMap SomeEntity)
|
||||||
entities = levels . current
|
entities = levels . current . levelEntities
|
||||||
|
|
||||||
|
revealedPositions :: Lens' GameState (Set Position)
|
||||||
|
revealedPositions = levels . current . levelRevealedPositions
|
||||||
|
|
||||||
instance Eq GameState where
|
instance Eq GameState where
|
||||||
(==) = (==) `on` \gs ->
|
(==) = (==) `on` \gs ->
|
||||||
|
|
Loading…
Add table
Reference in a new issue