Track entity collision in the Entity class

Rather than having a single function in the Game.Lenses module for
determining what collision type if any an entity has, track it in the
Entity typeclass itself. This is both more extensible and a better
separation of concerns and gets rid of one of the two needs for a
circular import. Yay!

As part of this, I realized nothing was being done to prevent doors from
being placed on tiles that already had walls (since now that was
properly causing a collision!) so I've fixed that as well.
This commit is contained in:
Griffin Smith 2020-01-03 18:28:43 -05:00
parent 1b88921bc3
commit 84f32efad4
9 changed files with 37 additions and 35 deletions

View file

@ -1,4 +1,6 @@
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
--------------------------------------------------------------------------------
module Xanthous.Game.Lenses
( positionedCharacter
@ -11,7 +13,7 @@ module Xanthous.Game.Lenses
-- * Collisions
, Collision(..)
, entityCollision
, entitiesCollision
, collisionAt
) where
--------------------------------------------------------------------------------
@ -26,9 +28,6 @@ import Xanthous.Data
import qualified Xanthous.Data.EntityMap as EntityMap
import Xanthous.Data.EntityMap.Graphics (visiblePositions)
import Xanthous.Entities.Character (Character, mkCharacter)
import Xanthous.Entities.Environment (Door, open, GroundMessage)
import Xanthous.Entities.Item (Item)
import {-# SOURCE #-} Xanthous.Entities.Creature (Creature)
import {-# SOURCE #-} Xanthous.Entities.Entities ()
--------------------------------------------------------------------------------
@ -96,31 +95,17 @@ characterVisiblePositions game =
let charPos = game ^. characterPosition
in visiblePositions charPos visionRadius $ game ^. entities
data Collision
= Stop
| Combat
deriving stock (Show, Eq, Ord, Generic)
deriving anyclass (NFData)
entityCollision
:: ( MonoFoldable (f SomeEntity)
, Foldable f
, Element (f SomeEntity) ~ SomeEntity
, AsEmpty (f SomeEntity)
entitiesCollision
:: ( Functor f
, forall xx. MonoFoldable (f xx)
, forall xx. Element (f xx) ~ xx
, Element (f (Maybe Collision)) ~ Maybe Collision
, Show (f (Maybe Collision))
, Show (f SomeEntity)
)
=> f SomeEntity
-> Maybe Collision
entityCollision Empty = Nothing
entityCollision ents
-- TODO track entity collision in the Entity class
| any (entityIs @Creature) ents = pure Combat
| all (\e ->
entityIs @Item e
|| entityIs @GroundMessage e
) ents = Nothing
| doors@(_ : _) <- ents ^.. folded . _SomeEntity @Door
, all (view open) doors = Nothing
| otherwise = pure Stop
entitiesCollision = join . maximumMay . fmap entityCollision
collisionAt :: MonadState GameState m => Position -> m (Maybe Collision)
collisionAt pos = uses (entities . EntityMap.atPosition pos) entityCollision
collisionAt pos = uses (entities . EntityMap.atPosition pos) entitiesCollision