Skip to content

Commit

Permalink
Add support for multiple levels
Browse files Browse the repository at this point in the history
Add a data structure, based on the zipper comonad, which provides
support for multiple levels, each of which is its own entity map. The
current level is provided by coreturn, which the `entities` lens has
been updated to use. Nothing currently supports going up or down levels
yet - that's coming next.
  • Loading branch information
glittershark committed Jan 5, 2020
1 parent e669b54 commit 6b0bab0
Show file tree
Hide file tree
Showing 11 changed files with 397 additions and 14 deletions.
92 changes: 92 additions & 0 deletions build/update-comonad-extras.patch
Original file line number Diff line number Diff line change
@@ -0,0 +1,92 @@
diff --git a/comonad-extras.cabal b/comonad-extras.cabal
index fc3745a..77a2f0d 100644
--- a/comonad-extras.cabal
+++ b/comonad-extras.cabal
@@ -1,7 +1,7 @@
name: comonad-extras
category: Control, Comonads
-version: 4.0
+version: 5.0
x-revision: 1
license: BSD3
cabal-version: >= 1.6
license-file: LICENSE
@@ -34,8 +34,8 @@ library
build-depends:
array >= 0.3 && < 0.6,
- base >= 4 && < 4.7,
- containers >= 0.4 && < 0.6,
- comonad >= 4 && < 5,
+ base >= 4 && < 5,
+ containers >= 0.6 && < 0.7,
+ comonad >= 5 && < 6,
distributive >= 0.3.2 && < 1,
- semigroupoids >= 4 && < 5,
- transformers >= 0.2 && < 0.4
+ semigroupoids >= 5 && < 6,
+ transformers >= 0.5 && < 0.6

exposed-modules:
Control.Comonad.Store.Zipper
diff --git a/src/Control/Comonad/Store/Pointer.hs b/src/Control/Comonad/Store/Pointer.hs
index 5044a1e..8d4c62d 100644
--- a/src/Control/Comonad/Store/Pointer.hs
+++ b/src/Control/Comonad/Store/Pointer.hs
@@ -41,7 +41,6 @@ module Control.Comonad.Store.Pointer
, module Control.Comonad.Store.Class
) where

-import Control.Applicative
import Control.Comonad
import Control.Comonad.Hoist.Class
import Control.Comonad.Trans.Class
@@ -51,27 +50,8 @@ import Control.Comonad.Env.Class
import Data.Functor.Identity
import Data.Functor.Extend
import Data.Array
-
#ifdef __GLASGOW_HASKELL__
import Data.Typeable
-instance (Typeable i, Typeable1 w) => Typeable1 (PointerT i w) where
- typeOf1 diwa = mkTyConApp storeTTyCon [typeOf (i diwa), typeOf1 (w diwa)]
- where
- i :: PointerT i w a -> i
- i = undefined
- w :: PointerT i w a -> w a
- w = undefined
-
-instance (Typeable i, Typeable1 w, Typeable a) => Typeable (PointerT i w a) where
- typeOf = typeOfDefault
-
-storeTTyCon :: TyCon
-#if __GLASGOW_HASKELL__ < 704
-storeTTyCon = mkTyCon "Control.Comonad.Trans.Store.Pointer.PointerT"
-#else
-storeTTyCon = mkTyCon3 "comonad-extras" "Control.Comonad.Trans.Store.Pointer" "PointerT"
-#endif
-{-# NOINLINE storeTTyCon #-}
#endif

type Pointer i = PointerT i Identity
@@ -83,6 +63,9 @@ runPointer :: Pointer i a -> (Array i a, i)
runPointer (PointerT (Identity f) i) = (f, i)

data PointerT i w a = PointerT (w (Array i a)) i
+#ifdef __GLASGOW_HASKELL__
+ deriving Typeable
+#endif

runPointerT :: PointerT i w a -> (w (Array i a), i)
runPointerT (PointerT g i) = (g, i)
diff --git a/src/Control/Comonad/Store/Zipper.hs b/src/Control/Comonad/Store/Zipper.hs
index 3b70c86..decc378 100644
--- a/src/Control/Comonad/Store/Zipper.hs
+++ b/src/Control/Comonad/Store/Zipper.hs
@@ -15,7 +15,6 @@
module Control.Comonad.Store.Zipper
( Zipper, zipper, zipper1, unzipper, size) where

-import Control.Applicative
import Control.Comonad (Comonad(..))
import Data.Functor.Extend
import Data.Foldable
3 changes: 3 additions & 0 deletions haskell-overlay.nix
Original file line number Diff line number Diff line change
Expand Up @@ -29,4 +29,7 @@ in self: super: with pkgs.haskell.lib; rec {
};
version = "0.12.0";
};

comonad-extras = appendPatch (markUnbroken super.comonad-extras)
[ ./build/update-comonad-extras.patch ];
}
3 changes: 3 additions & 0 deletions package.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -26,6 +26,7 @@ dependencies:
- checkers
- classy-prelude
- comonad
- comonad-extras
- constraints
- containers
- data-default
Expand All @@ -48,6 +49,7 @@ dependencies:
- MonadRandom
- mtl
- optparse-applicative
- pointed
- random
- random-fu
- random-extras
Expand All @@ -59,6 +61,7 @@ dependencies:
- stache
- semigroupoids
- tomland
- text
- text-zipper
- vector
- vty
Expand Down
170 changes: 170 additions & 0 deletions src/Xanthous/Data/Levels.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,170 @@
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
--------------------------------------------------------------------------------
module Xanthous.Data.Levels
( Levels
, allLevels
, nextLevel
, prevLevel
, mkLevels1
, mkLevels
, oneLevel
, current
, ComonadStore(..)
) where
--------------------------------------------------------------------------------
import Xanthous.Prelude hiding ((<.>), Empty, foldMap, levels)
import Xanthous.Util (between, EqProp, EqEqProp(..))
import Xanthous.Util.Comonad (current)
import Xanthous.Orphans ()
--------------------------------------------------------------------------------
import Control.Comonad.Store
import Control.Comonad.Store.Zipper
import Data.Aeson (ToJSON(..), FromJSON(..))
import Data.Aeson.Generic.DerivingVia
import Data.Functor.Apply
import Data.Foldable (foldMap)
import Data.List.NonEmpty (NonEmpty)
import qualified Data.List.NonEmpty as NE
import Data.Maybe (fromJust)
import Data.Sequence (Seq((:<|), Empty))
import Data.Semigroup.Foldable.Class
import Data.Text (replace)
import Test.QuickCheck
--------------------------------------------------------------------------------

-- | Collection of levels plus a pointer to the current level
--
-- Navigation is via the 'Comonad' instance. We can get the current level with
-- 'extract':
--
-- extract @Levels :: Levels level -> level
--
-- For access to and modification of the level, use
-- 'Xanthous.Util.Comonad.current'
newtype Levels a = Levels { levelZipper :: Zipper Seq a }
deriving stock (Generic)
deriving (Functor, Comonad, Foldable) via (Zipper Seq)
deriving (ComonadStore Int) via (Zipper Seq)

type instance Element (Levels a) = a
instance MonoFoldable (Levels a)
instance MonoFunctor (Levels a)
instance MonoTraversable (Levels a)

instance Traversable Levels where
traverse f (Levels z) = Levels <$> traverse f z

instance Foldable1 Levels

instance Traversable1 Levels where
traverse1 f (Levels z) = seek (pos z) . partialMkLevels <$> go (unzipper z)
where
go Empty = error "empty seq, unreachable"
go (x :<| xs) = (<|) <$> f x <.> go xs

-- | Always takes the position of the latter element
instance Semigroup (Levels a) where
levs₁ <> levs₂
= seek (pos levs₂)
. partialMkLevels
$ allLevels levs₁ <> allLevels levs₂

-- | Make Levels from a Seq. Throws an error if the seq is not empty
partialMkLevels :: Seq a -> Levels a
partialMkLevels = Levels . fromJust . zipper

-- | Make Levels from a possibly-empty structure
mkLevels :: Foldable1 f => f level -> Maybe (Levels level)
mkLevels = fmap Levels . zipper . foldMap pure

-- | Make Levels from a non-empty structure
mkLevels1 :: Foldable1 f => f level -> Levels level
mkLevels1 = fromJust . mkLevels

oneLevel :: a -> Levels a
oneLevel = mkLevels1 . Identity

-- | Get a sequence of all the levels
allLevels :: Levels a -> Seq a
allLevels = unzipper . levelZipper

-- | Step to the next level, generating a new level if necessary using the given
-- applicative action
nextLevel
:: Applicative m
=> m level -- ^ Generate a new level, if necessary
-> Levels level
-> m (Levels level)
nextLevel genLevel levs
| pos levs + 1 < size (levelZipper levs)
= pure $ seeks succ levs
| otherwise
= genLevel <&> \level ->
seek (pos levs + 1) . partialMkLevels $ level <| allLevels levs

-- | Go to the previous level. Returns Nothing if 'pos' is 0
prevLevel :: Levels level -> Maybe (Levels level)
prevLevel levs | pos levs == 0 = Nothing
| otherwise = Just $ seeks pred levs

--------------------------------------------------------------------------------

-- | alternate, slower representation of Levels we can Iso into to perform
-- various operations
data AltLevels a = AltLevels
{ _levels :: NonEmpty a
, _currentLevel :: Int -- ^ invariant: is within the bounds of _levels
}
deriving stock (Show, Eq, Generic)
deriving anyclass (NFData, CoArbitrary, Function)
deriving (ToJSON, FromJSON)
via WithOptions '[ FieldLabelModifier '[Drop 1] ]
(AltLevels a)
makeLenses ''AltLevels

alt :: Iso (Levels a) (Levels b) (AltLevels a) (AltLevels b)
alt = iso hither yon
where
hither levs = AltLevels (NE.fromList . toList $ allLevels levs) (pos levs)
yon (AltLevels levs curr) = seek curr $ mkLevels1 levs

instance Eq a => Eq (Levels a) where
(==) = (==) `on` view alt

deriving via EqEqProp (Levels a) instance Eq a => EqProp (Levels a)

instance Show a => Show (Levels a) where
show = unpack . replace "AltLevels" "Levels" . pack . show . view alt

instance NFData a => NFData (Levels a) where
rnf = rnf . view alt

instance ToJSON a => ToJSON (Levels a) where
toJSON = toJSON . view alt

instance FromJSON a => FromJSON (Levels a) where
parseJSON = fmap (review alt) . parseJSON

instance Arbitrary a => Arbitrary (AltLevels a) where
arbitrary = do
_levels <- arbitrary
_currentLevel <- choose (0, length _levels - 1)
pure AltLevels {..}
shrink als = do
_levels <- shrink $ als ^. levels
_currentLevel <- filter (between 0 $ length _levels - 1)
$ shrink $ als ^. currentLevel
pure AltLevels {..}


instance Arbitrary a => Arbitrary (Levels a) where
arbitrary = review alt <$> arbitrary
shrink = fmap (review alt) . shrink . view alt

instance CoArbitrary a => CoArbitrary (Levels a) where
coarbitrary = coarbitrary . view alt

instance Function a => Function (Levels a) where
function = functionMap (view alt) (review alt)
18 changes: 12 additions & 6 deletions src/Xanthous/Game/Arbitrary.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,25 +5,31 @@
--------------------------------------------------------------------------------
module Xanthous.Game.Arbitrary where
--------------------------------------------------------------------------------
import Xanthous.Prelude
import Xanthous.Prelude hiding (levels, foldMap)
--------------------------------------------------------------------------------
import Test.QuickCheck
import System.Random
import Data.Foldable (foldMap)
--------------------------------------------------------------------------------
import Xanthous.Game.State
import Xanthous.Data.Levels
import qualified Xanthous.Data.EntityMap as EntityMap
import Xanthous.Entities.Entities ()
import Xanthous.Entities.Character
import qualified Xanthous.Data.EntityMap as EntityMap
import Xanthous.Game.State
--------------------------------------------------------------------------------

instance Arbitrary GameState where
arbitrary = do
chr <- arbitrary @Character
charPos <- arbitrary
_messageHistory <- arbitrary
(_characterEntityID, _entities) <- arbitrary <&>
EntityMap.insertAtReturningID charPos (SomeEntity chr)
_revealedPositions <- fmap setFromList . sublistOf $ EntityMap.positions _entities
levels <- arbitrary
let (_characterEntityID, currentLevel) =
EntityMap.insertAtReturningID charPos (SomeEntity chr)
$ extract levels
_levels = levels & current .~ currentLevel
_revealedPositions <- fmap setFromList . sublistOf
$ foldMap EntityMap.positions levels
_randomGen <- mkStdGen <$> arbitrary
let _promptState = NoPrompt -- TODO
_activePanel <- arbitrary
Expand Down
6 changes: 4 additions & 2 deletions src/Xanthous/Game/Lenses.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,6 +25,7 @@ import Control.Monad.Random (getRandom)
--------------------------------------------------------------------------------
import Xanthous.Game.State
import Xanthous.Data
import Xanthous.Data.Levels
import qualified Xanthous.Data.EntityMap as EntityMap
import Xanthous.Data.EntityMap.Graphics (visiblePositions)
import Xanthous.Entities.Character (Character, mkCharacter)
Expand All @@ -38,11 +39,12 @@ initialStateFromSeed :: Int -> GameState
initialStateFromSeed seed =
let _randomGen = mkStdGen seed
chr = mkCharacter
(_characterEntityID, _entities)
(_characterEntityID, level)
= EntityMap.insertAtReturningID
(Position 0 0)
(SomeEntity chr)
mempty
_levels = oneLevel level
_messageHistory = mempty
_revealedPositions = mempty
_promptState = NoPrompt
Expand Down Expand Up @@ -108,4 +110,4 @@ entitiesCollision
entitiesCollision = join . maximumMay . fmap entityCollision

collisionAt :: MonadState GameState m => Position -> m (Maybe Collision)
collisionAt pos = uses (entities . EntityMap.atPosition pos) entitiesCollision
collisionAt p = uses (entities . EntityMap.atPosition p) entitiesCollision
Loading

0 comments on commit 6b0bab0

Please sign in to comment.