Progressively reveal the map to the player

As the character walks around the map, progressively reveal the entities
on the map to them, using an algorithm based on well known
circle-rasterizing and line-rasterizing algorithms to calculate lines of
sight that are potentially obscured by walls.
This commit is contained in:
Griffin Smith 2019-09-15 13:00:28 -04:00
parent 6678ac986c
commit 58fce2ec19
17 changed files with 454 additions and 52 deletions

View file

@ -6,6 +6,7 @@ import qualified Brick
import Graphics.Vty.Attributes (defAttr) import Graphics.Vty.Attributes (defAttr)
import Graphics.Vty.Input.Events (Event(EvKey)) import Graphics.Vty.Input.Events (Event(EvKey))
import Control.Monad.State (get) import Control.Monad.State (get)
import Control.Monad.State.Class (modify)
import Control.Monad.Random (getRandom) import Control.Monad.Random (getRandom)
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
import Xanthous.Command import Xanthous.Command
@ -60,6 +61,7 @@ startEvent = do
$ Dimensions 80 80 $ Dimensions 80 80
entities <>= level entities <>= level
characterPosition .= charPos characterPosition .= charPos
modify updateCharacterVision
-- entities %= EntityMap.insertAt (Position 10 10) (SomeEntity testGormlak) -- entities %= EntityMap.insertAt (Position 10 10) (SomeEntity testGormlak)
@ -75,7 +77,9 @@ handleCommand Quit = halt
handleCommand (Move dir) = do handleCommand (Move dir) = do
newPos <- uses characterPosition $ move dir newPos <- uses characterPosition $ move dir
collisionAt newPos >>= \case collisionAt newPos >>= \case
Nothing -> characterPosition .= newPos Nothing -> do
characterPosition .= newPos
modify updateCharacterVision
Just Combat -> undefined Just Combat -> undefined
Just Stop -> pure () Just Stop -> pure ()
continue continue

View file

@ -12,9 +12,11 @@ module Xanthous.Data
, y , y
, Positioned(..) , Positioned(..)
, _Positioned
, position , position
, positioned , positioned
, loc , loc
, _Position
, positionFromPair , positionFromPair
-- * -- *
@ -73,6 +75,12 @@ data Positioned a where
deriving stock (Show, Eq, Ord, Functor, Foldable, Traversable, Generic) deriving stock (Show, Eq, Ord, Functor, Foldable, Traversable, Generic)
deriving anyclass (CoArbitrary, Function) deriving anyclass (CoArbitrary, Function)
_Positioned :: Iso (Position, a) (Position, b) (Positioned a) (Positioned b)
_Positioned = iso hither yon
where
hither (pos, a) = Positioned pos a
yon (Positioned pos b) = (pos, b)
instance Arbitrary a => Arbitrary (Positioned a) where instance Arbitrary a => Arbitrary (Positioned a) where
arbitrary = Positioned <$> arbitrary <*> arbitrary arbitrary = Positioned <$> arbitrary <*> arbitrary
@ -92,6 +100,12 @@ loc = iso hither yon
hither (Position px py) = Location (px, py) hither (Position px py) = Location (px, py)
yon (Location (lx, ly)) = Position lx ly yon (Location (lx, ly)) = Position lx ly
_Position :: Iso' Position (Int, Int)
_Position = iso hither yon
where
hither (Position px py) = (px, py)
yon (lx, ly) = Position lx ly
positionFromPair :: (Integral i, Integral j) => (i, j) -> Position positionFromPair :: (Integral i, Integral j) => (i, j) -> Position
positionFromPair (i, j) = Position (fromIntegral i) (fromIntegral j) positionFromPair (i, j) = Position (fromIntegral i) (fromIntegral j)

View file

@ -1,27 +1,31 @@
{-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE TupleSections #-} {-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE DeriveFunctor #-}
--------------------------------------------------------------------------------
module Xanthous.Data.EntityMap module Xanthous.Data.EntityMap
( EntityMap ( EntityMap
, _EntityMap
, EntityID , EntityID
, emptyEntityMap , emptyEntityMap
, insertAt , insertAt
, insertAtReturningID , insertAtReturningID
, fromEIDsAndPositioned
, atPosition , atPosition
, atPositionWithIDs
, positions , positions
, lookup , lookup
, lookupWithPosition , lookupWithPosition
-- , positionedEntities -- , positionedEntities
, neighbors , neighbors
, Deduplicate(..)
-- * Querying an entityMap
) where ) where
--------------------------------------------------------------------------------
import Data.Monoid (Endo(..))
import Test.QuickCheck (Arbitrary(..))
import Test.QuickCheck.Checkers (EqProp)
import Xanthous.Prelude hiding (lookup) import Xanthous.Prelude hiding (lookup)
import Xanthous.Data import Xanthous.Data
( Position ( Position
@ -33,7 +37,11 @@ import Xanthous.Data
) )
import Xanthous.Orphans () import Xanthous.Orphans ()
import Xanthous.Util (EqEqProp(..)) import Xanthous.Util (EqEqProp(..))
--------------------------------------------------------------------------------
import Data.Monoid (Endo(..))
import Test.QuickCheck (Arbitrary(..))
import Test.QuickCheck.Checkers (EqProp)
--------------------------------------------------------------------------------
type EntityID = Word32 type EntityID = Word32
type NonNullVector a = NonNull (Vector a) type NonNullVector a = NonNull (Vector a)
@ -43,7 +51,7 @@ data EntityMap a where
, _byID :: HashMap EntityID (Positioned a) , _byID :: HashMap EntityID (Positioned a)
, _lastID :: EntityID , _lastID :: EntityID
} -> EntityMap a } -> EntityMap a
deriving stock (Functor, Foldable, Traversable) deriving stock (Functor, Foldable, Traversable, Generic)
deriving via (EqEqProp (EntityMap a)) instance Eq a => EqProp (EntityMap a) deriving via (EqEqProp (EntityMap a)) instance Eq a => EqProp (EntityMap a)
makeLenses ''EntityMap makeLenses ''EntityMap
@ -85,9 +93,36 @@ instance At (EntityMap a) where
removeEIDAtPos pos = removeEIDAtPos pos =
byPosition . at pos %~ (>>= fromNullable . nfilter (/= eid)) byPosition . at pos %~ (>>= fromNullable . nfilter (/= eid))
instance Semigroup (EntityMap a) where
em <> em = alaf Endo foldMap (uncurry insertAt) (em ^. _EntityMap) em
instance Monoid (EntityMap a) where
mempty = emptyEntityMap
emptyEntityMap :: EntityMap a emptyEntityMap :: EntityMap a
emptyEntityMap = EntityMap mempty mempty 0 emptyEntityMap = EntityMap mempty mempty 0
newtype Deduplicate a = Deduplicate (EntityMap a)
deriving stock (Show, Traversable, Generic)
deriving newtype (Eq, Functor, Foldable, EqProp, Arbitrary)
instance Semigroup (Deduplicate a) where
(Deduplicate em) <> (Deduplicate em) =
let _byID = em ^. byID <> em ^. byID
_byPosition = mempty &~ do
ifor_ _byID $ \eid (Positioned pos _) ->
at pos %= \case
Just eids -> Just $ eid <| eids
Nothing -> Just $ ncons eid mempty
_lastID = fromMaybe 1 $ maximumOf (ifolded . asIndex) _byID
in Deduplicate EntityMap{..}
instance Monoid (Deduplicate a) where
mempty = Deduplicate emptyEntityMap
--------------------------------------------------------------------------------
_EntityMap :: Iso' (EntityMap a) [(Position, a)] _EntityMap :: Iso' (EntityMap a) [(Position, a)]
_EntityMap = iso hither yon _EntityMap = iso hither yon
where where
@ -100,12 +135,6 @@ _EntityMap = iso hither yon
yon :: [(Position, a)] -> EntityMap a yon :: [(Position, a)] -> EntityMap a
yon poses = alaf Endo foldMap (uncurry insertAt) poses emptyEntityMap yon poses = alaf Endo foldMap (uncurry insertAt) poses emptyEntityMap
instance Semigroup (EntityMap a) where
em <> em = alaf Endo foldMap (uncurry insertAt) (em ^. _EntityMap) em
instance Monoid (EntityMap a) where
mempty = emptyEntityMap
insertAtReturningID :: forall a. Position -> a -> EntityMap a -> (EntityID, EntityMap a) insertAtReturningID :: forall a. Position -> a -> EntityMap a -> (EntityID, EntityMap a)
insertAtReturningID pos e em = insertAtReturningID pos e em =
@ -124,17 +153,37 @@ atPosition :: forall a. Position -> Lens' (EntityMap a) (Vector a)
atPosition pos = lens getter setter atPosition pos = lens getter setter
where where
getter em = getter em =
let let eids :: Vector EntityID
eids :: Vector EntityID eids = maybe mempty toNullable $ em ^. byPosition . at pos
eids = maybe mempty toNullable $ em ^. byPosition . at pos in getEIDAssume em <$> eids
getEIDAssume :: EntityID -> a
getEIDAssume eid = fromMaybe byIDInvariantError
$ em ^? byID . ix eid . positioned
in getEIDAssume <$> eids
setter em Empty = em & byPosition . at pos .~ Nothing setter em Empty = em & byPosition . at pos .~ Nothing
setter em entities = alaf Endo foldMap (insertAt pos) entities em setter em entities = alaf Endo foldMap (insertAt pos) entities em
getEIDAssume :: EntityMap a -> EntityID -> a
getEIDAssume em eid = fromMaybe byIDInvariantError
$ em ^? byID . ix eid . positioned
atPositionWithIDs :: Position -> EntityMap a -> Vector (EntityID, Positioned a)
atPositionWithIDs pos em =
let eids = maybe mempty toNullable $ em ^. byPosition . at pos
in (id &&& Positioned pos . getEIDAssume em) <$> eids
fromEIDsAndPositioned
:: (MonoFoldable mono, Element mono ~ (EntityID, Positioned a))
=> mono
-> EntityMap a
fromEIDsAndPositioned eps = newLastID $ alaf Endo foldMap insert' eps mempty
where
insert' (eid, pe@(Positioned pos _))
= (byID . at eid ?~ pe)
. (byPosition . at pos %~ \case
Just eids -> Just $ eid <| eids
Nothing -> Just $ ncons eid mempty
)
newLastID em = em & lastID
.~ fromMaybe 1
(maximumOf (ifolded . asIndex) (em ^. byID))
positions :: EntityMap a -> [Position] positions :: EntityMap a -> [Position]
positions = toListOf $ byPosition . to keys . folded positions = toListOf $ byPosition . to keys . folded
@ -150,3 +199,6 @@ lookup eid = fmap (view positioned) . lookupWithPosition eid
neighbors :: Position -> EntityMap a -> Neighbors (Vector a) neighbors :: Position -> EntityMap a -> Neighbors (Vector a)
neighbors pos em = (\p -> view (atPosition p) em) <$> neighborPositions pos neighbors pos em = (\p -> view (atPosition p) em) <$> neighborPositions pos
--------------------------------------------------------------------------------
makeWrapped ''Deduplicate

View file

@ -0,0 +1,28 @@
{-# LANGUAGE ViewPatterns #-}
--------------------------------------------------------------------------------
module Xanthous.Data.EntityMap.Graphics where
--------------------------------------------------------------------------------
import Xanthous.Prelude
--------------------------------------------------------------------------------
import Xanthous.Util (takeWhileInclusive)
import Xanthous.Data
import Xanthous.Data.EntityMap
import Xanthous.Entities
import Xanthous.Util.Graphics (circle, line)
--------------------------------------------------------------------------------
-- | Given a point and a radius of vision, returns a list of all entities that
-- are *visible* (eg, not blocked by an entity that obscures vision) from that
-- point
visibleEntities :: Position -> Word -> EntityMap SomeEntity -> EntityMap SomeEntity
visibleEntities (view _Position -> pos) visionRadius em
= fromEIDsAndPositioned . fold . fold $ sightAdjustedLines
where
-- I love laziness!
radius = circle pos $ fromIntegral visionRadius
linesOfSight = radius <&> line pos
entitiesOnLines = linesOfSight <&> map getPositionedAt
sightAdjustedLines = entitiesOnLines <&> takeWhileInclusive (none $ blocksVision . snd)
getPositionedAt p =
let ppos = _Position # p
in atPositionWithIDs ppos em

View file

@ -7,7 +7,7 @@ module Xanthous.Entities
( Draw(..) ( Draw(..)
, DrawCharacter(..) , DrawCharacter(..)
, DrawStyledCharacter(..) , DrawStyledCharacter(..)
, Entity , Entity(..)
, SomeEntity(..) , SomeEntity(..)
, downcastEntity , downcastEntity
, entityIs , entityIs
@ -29,8 +29,11 @@ import Data.Aeson
import Xanthous.Data import Xanthous.Data
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
class (Show a, Eq a, Draw a) => Entity a class (Show a, Eq a, Draw a) => Entity a where
instance (Show a, Eq a, Draw a) => Entity a blocksVision :: a -> Bool
instance Entity a => Entity (Positioned a) where
blocksVision (Positioned _ ent) = blocksVision ent
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
data SomeEntity where data SomeEntity where
@ -47,6 +50,9 @@ instance Eq SomeEntity where
instance Draw SomeEntity where instance Draw SomeEntity where
drawWithNeighbors ns (SomeEntity ent) = drawWithNeighbors ns ent drawWithNeighbors ns (SomeEntity ent) = drawWithNeighbors ns ent
instance Entity SomeEntity where
blocksVision (SomeEntity ent) = blocksVision ent
downcastEntity :: (Entity a, Typeable a) => SomeEntity -> Maybe a downcastEntity :: (Entity a, Typeable a) => SomeEntity -> Maybe a
downcastEntity (SomeEntity e) = cast e downcastEntity (SomeEntity e) = cast e
@ -61,6 +67,10 @@ class Draw a where
draw :: a -> Widget n draw :: a -> Widget n
draw = drawWithNeighbors $ pure mempty draw = drawWithNeighbors $ pure mempty
instance Draw a => Draw (Positioned a) where
drawWithNeighbors ns (Positioned _ a) = drawWithNeighbors ns a
draw (Positioned _ a) = draw a
newtype DrawCharacter (char :: Symbol) (a :: Type) where newtype DrawCharacter (char :: Symbol) (a :: Type) where
DrawCharacter :: a -> DrawCharacter char a DrawCharacter :: a -> DrawCharacter char a

View file

@ -14,6 +14,9 @@ data Character = Character
deriving anyclass (CoArbitrary, Function) deriving anyclass (CoArbitrary, Function)
deriving Draw via (DrawCharacter "@" Character) deriving Draw via (DrawCharacter "@" Character)
instance Entity Character where
blocksVision _ = False
instance Arbitrary Character where instance Arbitrary Character where
arbitrary = pure Character arbitrary = pure Character

View file

@ -8,7 +8,7 @@ import Data.Word
import Xanthous.Prelude import Xanthous.Prelude
import Xanthous.Entities.RawTypes hiding (Creature) import Xanthous.Entities.RawTypes hiding (Creature)
import Xanthous.Entities (Draw(..)) import Xanthous.Entities (Draw(..), Entity(..))
data Creature = Creature data Creature = Creature
{ _creatureType :: CreatureType { _creatureType :: CreatureType
@ -17,6 +17,9 @@ data Creature = Creature
deriving stock (Eq, Show, Generic) deriving stock (Eq, Show, Generic)
makeLenses ''Creature makeLenses ''Creature
instance Entity Creature where
blocksVision _ = False
instance Draw Creature where instance Draw Creature where
draw = draw .view (creatureType . char) draw = draw .view (creatureType . char)

View file

@ -7,7 +7,7 @@ import Test.QuickCheck
import Brick (str) import Brick (str)
import Brick.Widgets.Border.Style (unicode) import Brick.Widgets.Border.Style (unicode)
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
import Xanthous.Entities (Draw(..), entityIs) import Xanthous.Entities (Draw(..), entityIs, Entity(..))
import Xanthous.Entities.Draw.Util import Xanthous.Entities.Draw.Util
import Xanthous.Data import Xanthous.Data
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
@ -16,6 +16,9 @@ data Wall = Wall
deriving stock (Show, Eq, Ord, Generic, Enum) deriving stock (Show, Eq, Ord, Generic, Enum)
deriving anyclass (CoArbitrary, Function) deriving anyclass (CoArbitrary, Function)
instance Entity Wall where
blocksVision _ = True
instance Arbitrary Wall where instance Arbitrary Wall where
arbitrary = pure Wall arbitrary = pure Wall

View file

@ -1,10 +1,11 @@
{-# LANGUAGE MultiWayIf #-} {-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE RecordWildCards #-}
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
module Xanthous.Game module Xanthous.Game
( GameState(..) ( GameState(..)
, entities , entities
, revealedEntities
, messageHistory , messageHistory
, randomGen , randomGen
@ -13,6 +14,7 @@ module Xanthous.Game
, positionedCharacter , positionedCharacter
, character , character
, characterPosition , characterPosition
, updateCharacterVision
, MessageHistory(..) , MessageHistory(..)
, pushMessage , pushMessage
@ -33,8 +35,10 @@ import Test.QuickCheck
import Test.QuickCheck.Arbitrary.Generic import Test.QuickCheck.Arbitrary.Generic
import Control.Monad.State.Class import Control.Monad.State.Class
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
import Xanthous.Util (appendVia)
import Xanthous.Data.EntityMap (EntityMap, EntityID) import Xanthous.Data.EntityMap (EntityMap, EntityID)
import qualified Xanthous.Data.EntityMap as EntityMap import qualified Xanthous.Data.EntityMap as EntityMap
import Xanthous.Data.EntityMap.Graphics
import Xanthous.Data (Positioned, Position(..), positioned, position) import Xanthous.Data (Positioned, Position(..), positioned, position)
import Xanthous.Entities (SomeEntity(..), downcastEntity, entityIs) import Xanthous.Entities (SomeEntity(..), downcastEntity, entityIs)
import Xanthous.Entities.Character import Xanthous.Entities.Character
@ -68,6 +72,8 @@ hideMessage (MessageHistory msgs _) = MessageHistory msgs False
data GameState = GameState data GameState = GameState
{ _entities :: EntityMap SomeEntity { _entities :: EntityMap SomeEntity
-- | A subset of the overall set of entities
, _revealedEntities :: EntityMap SomeEntity
, _characterEntityID :: EntityID , _characterEntityID :: EntityID
, _messageHistory :: MessageHistory , _messageHistory :: MessageHistory
, _randomGen :: StdGen , _randomGen :: StdGen
@ -76,10 +82,12 @@ data GameState = GameState
makeLenses ''GameState makeLenses ''GameState
instance Eq GameState where instance Eq GameState where
(GameState es ceid mh _) == (GameState es ceid mh _) (==) = (==) `on` \gs ->
= es == es ( gs ^. entities
&& ceid == ceid , gs ^. revealedEntities
&& mh == mh , gs ^. characterEntityID
, gs ^. messageHistory
)
instance Arbitrary GameState where instance Arbitrary GameState where
arbitrary = do arbitrary = do
@ -88,6 +96,11 @@ instance Arbitrary GameState where
_messageHistory <- arbitrary _messageHistory <- arbitrary
(_characterEntityID, _entities) <- arbitrary <&> (_characterEntityID, _entities) <- arbitrary <&>
EntityMap.insertAtReturningID charPos (SomeEntity char) EntityMap.insertAtReturningID charPos (SomeEntity char)
revealedPositions <- sublistOf $ EntityMap.positions _entities
let _revealedEntities = mempty &~ do
for_ revealedPositions $ \pos -> do
let ents = _entities ^. EntityMap.atPosition pos
EntityMap.atPosition pos <>= ents
_randomGen <- mkStdGen <$> arbitrary _randomGen <- mkStdGen <$> arbitrary
pure $ GameState {..} pure $ GameState {..}
@ -101,6 +114,7 @@ getInitialState = do
(SomeEntity char) (SomeEntity char)
mempty mempty
_messageHistory = NoMessageHistory _messageHistory = NoMessageHistory
_revealedEntities = _entities
pure GameState {..} pure GameState {..}
positionedCharacter :: Lens' GameState (Positioned Character) positionedCharacter :: Lens' GameState (Positioned Character)
@ -130,6 +144,17 @@ character = positionedCharacter . positioned
characterPosition :: Lens' GameState Position characterPosition :: Lens' GameState Position
characterPosition = positionedCharacter . position characterPosition = positionedCharacter . position
visionRadius :: Word
visionRadius = 12 -- TODO make this dynamic
-- | Update the revealed entities at the character's position based on their vision
updateCharacterVision :: GameState -> GameState
updateCharacterVision game =
let charPos = game ^. characterPosition
visible = visibleEntities charPos visionRadius $ game ^. entities
in game & revealedEntities %~ appendVia EntityMap.Deduplicate visible
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
data Collision data Collision

View file

@ -17,6 +17,7 @@ import Xanthous.Entities
import Xanthous.Game import Xanthous.Game
( GameState(..) ( GameState(..)
, entities , entities
, revealedEntities
, characterPosition , characterPosition
, MessageHistory(..) , MessageHistory(..)
, messageHistory , messageHistory
@ -35,8 +36,11 @@ drawMessages (MessageHistory (lastMessage :| _) True) = txt lastMessage
-- (MessageHistory _ False) -> padTop (Pad 2) $ str " " -- (MessageHistory _ False) -> padTop (Pad 2) $ str " "
-- (MessageHistory (lastMessage :| _) True) -> txt lastMessage -- (MessageHistory (lastMessage :| _) True) -> txt lastMessage
drawEntities :: EntityMap SomeEntity -> Widget Name drawEntities
drawEntities em :: EntityMap SomeEntity -- ^ visible entities
-> EntityMap SomeEntity -- ^ all entities
-> Widget Name
drawEntities em allEnts
= vBox rows = vBox rows
where where
entityPositions = EntityMap.positions em entityPositions = EntityMap.positions em
@ -45,7 +49,7 @@ drawEntities em
rows = mkRow <$> [0..maxY] rows = mkRow <$> [0..maxY]
mkRow rowY = hBox $ renderEntityAt . flip Position rowY <$> [0..maxX] mkRow rowY = hBox $ renderEntityAt . flip Position rowY <$> [0..maxX]
renderEntityAt pos = renderEntityAt pos =
let neighbors = EntityMap.neighbors pos em let neighbors = EntityMap.neighbors pos allEnts
in maybe (str " ") (drawWithNeighbors neighbors) in maybe (str " ") (drawWithNeighbors neighbors)
$ em ^? atPosition pos . folded $ em ^? atPosition pos . folded
@ -53,8 +57,9 @@ drawMap :: GameState -> Widget Name
drawMap game drawMap game
= viewport MapViewport Both = viewport MapViewport Both
. showCursor Character (game ^. characterPosition . loc) . showCursor Character (game ^. characterPosition . loc)
. drawEntities $ drawEntities
$ game ^. entities (game ^. revealedEntities)
(game ^. entities)
drawGame :: GameState -> [Widget Name] drawGame :: GameState -> [Widget Name]
drawGame game drawGame game

View file

@ -104,14 +104,6 @@ fillOuterEdgesM arr = do
writeArray arr (minX, y) True writeArray arr (minX, y) True
writeArray arr (maxX, y) True writeArray arr (maxX, y) True
safeGet :: (IArray a e, Ix i) => a i e -> i -> Maybe e
safeGet arr idx =
let (minIdx, maxIdx) = bounds arr
in if idx < minIdx || idx > maxIdx
then Nothing
else Just $ arr ! idx
cloneMArray cloneMArray
:: forall a a' i e m. :: forall a a' i e m.
( Ix i ( Ix i

View file

@ -1,4 +1,5 @@
{-# LANGUAGE BangPatterns #-} {-# LANGUAGE BangPatterns #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
module Xanthous.Util module Xanthous.Util
( EqEqProp(..) ( EqEqProp(..)
@ -6,12 +7,29 @@ module Xanthous.Util
, foldlMapM , foldlMapM
, foldlMapM' , foldlMapM'
, between , between
, appendVia
-- * Foldable
-- ** Uniqueness
-- *** Predicates on uniqueness
, isUniqueOf
, isUnique
-- *** Removing all duplicate elements in n * log n time
, uniqueOf
, unique
-- *** Removing sequentially duplicate elements in linear time
, uniqOf
, uniq
-- ** Bag sequence algorithms
, takeWhileInclusive
) where ) where
import Xanthous.Prelude hiding (foldr) import Xanthous.Prelude hiding (foldr)
import Test.QuickCheck.Checkers import Test.QuickCheck.Checkers
import Data.Foldable (foldr) import Data.Foldable (foldr)
import Data.Monoid
newtype EqEqProp a = EqEqProp a newtype EqEqProp a = EqEqProp a
deriving newtype Eq deriving newtype Eq
@ -44,3 +62,134 @@ between
-> a -- ^ scrutinee -> a -- ^ scrutinee
-> Bool -> Bool
between lower upper x = x >= lower && x <= upper between lower upper x = x >= lower && x <= upper
-- |
-- >>> appendVia Sum 1 2
-- 3
appendVia :: (Rewrapping s t, Semigroup s) => (Unwrapped s -> s) -> Unwrapped s -> Unwrapped s -> Unwrapped s
appendVia wrap x y = op wrap $ wrap x <> wrap y
--------------------------------------------------------------------------------
-- | Returns True if the targets of the given 'Fold' are unique per the 'Ord' instance for @a@
--
-- >>> isUniqueOf (folded . _1) ([(1, 2), (2, 2), (3, 2)] :: [(Int, Int)])
-- True
--
-- >>> isUniqueOf (folded . _2) ([(1, 2), (2, 2), (3, 2)] :: [(Int, Int)])
-- False
--
-- @
-- 'isUniqueOf' :: Ord a => 'Getter' s a -> s -> 'Bool'
-- 'isUniqueOf' :: Ord a => 'Fold' s a -> s -> 'Bool'
-- 'isUniqueOf' :: Ord a => 'Lens'' s a -> s -> 'Bool'
-- 'isUniqueOf' :: Ord a => 'Iso'' s a -> s -> 'Bool'
-- 'isUniqueOf' :: Ord a => 'Traversal'' s a -> s -> 'Bool'
-- 'isUniqueOf' :: Ord a => 'Prism'' s a -> s -> 'Bool'
-- @
isUniqueOf :: Ord a => Getting (Endo (Set a, Bool)) s a -> s -> Bool
isUniqueOf aFold = orOf _2 . foldrOf aFold rejectUnique (mempty, True)
where
rejectUnique x (seen, acc)
| seen ^. contains x = (seen, False)
| otherwise = (seen & contains x .~ True, acc)
-- | Returns true if the given 'Foldable' container contains only unique
-- elements, as determined by the 'Ord' instance for @a@
--
-- >>> isUnique ([3, 1, 2] :: [Int])
-- True
--
-- >>> isUnique ([1, 1, 2, 2, 3, 1] :: [Int])
-- False
isUnique :: (Foldable f, Ord a) => f a -> Bool
isUnique = isUniqueOf folded
-- | O(n * log n). Returns a monoidal, 'Cons'able container (a list, a Set,
-- etc.) consisting of the unique (per the 'Ord' instance for @a@) targets of
-- the given 'Fold'
--
-- >>> uniqueOf (folded . _2) ([(1, 2), (2, 2), (3, 2), (4, 3)] :: [(Int, Int)]) :: [Int]
-- [2,3]
--
-- @
-- 'uniqueOf' :: Ord a => 'Getter' s a -> s -> [a]
-- 'uniqueOf' :: Ord a => 'Fold' s a -> s -> [a]
-- 'uniqueOf' :: Ord a => 'Lens'' s a -> s -> [a]
-- 'uniqueOf' :: Ord a => 'Iso'' s a -> s -> [a]
-- 'uniqueOf' :: Ord a => 'Traversal'' s a -> s -> [a]
-- 'uniqueOf' :: Ord a => 'Prism'' s a -> s -> [a]
-- @
uniqueOf
:: (Monoid c, Ord w, Cons c c w w) => Getting (Endo (Set w, c)) a w -> a -> c
uniqueOf aFold = snd . foldrOf aFold rejectUnique (mempty, mempty)
where
rejectUnique x (seen, acc)
| seen ^. contains x = (seen, acc)
| otherwise = (seen & contains x .~ True, cons x acc)
-- | Returns a monoidal, 'Cons'able container (a list, a Set, etc.) consisting
-- of the unique (per the 'Ord' instance for @a@) contents of the given
-- 'Foldable' container
--
-- >>> unique [1, 1, 2, 2, 3, 1] :: [Int]
-- [2,3,1]
-- >>> unique [1, 1, 2, 2, 3, 1] :: Set Int
-- fromList [3,2,1]
unique :: (Foldable f, Cons c c a a, Ord a, Monoid c) => f a -> c
unique = uniqueOf folded
--------------------------------------------------------------------------------
-- | O(n). Returns a monoidal, 'Cons'able container (a list, a Vector, etc.)
-- consisting of the targets of the given 'Fold' with sequential duplicate
-- elements removed
--
-- This function (sorry for the confusing name) differs from 'uniqueOf' in that
-- it only compares /sequentially/ duplicate elements (and thus operates in
-- linear time).
-- cf 'Data.Vector.uniq' and POSIX @uniq@ for the name
--
-- >>> uniqOf (folded . _2) ([(1, 2), (2, 2), (3, 1), (4, 2)] :: [(Int, Int)]) :: [Int]
-- [2,1,2]
--
-- @
-- 'uniqOf' :: Eq a => 'Getter' s a -> s -> [a]
-- 'uniqOf' :: Eq a => 'Fold' s a -> s -> [a]
-- 'uniqOf' :: Eq a => 'Lens'' s a -> s -> [a]
-- 'uniqOf' :: Eq a => 'Iso'' s a -> s -> [a]
-- 'uniqOf' :: Eq a => 'Traversal'' s a -> s -> [a]
-- 'uniqOf' :: Eq a => 'Prism'' s a -> s -> [a]
-- @
uniqOf :: (Monoid c, Cons c c w w, Eq w) => Getting (Endo (Maybe w, c)) a w -> a -> c
uniqOf aFold = snd . foldrOf aFold rejectSeen (Nothing, mempty)
where
rejectSeen x (Nothing, acc) = (Just x, x <| acc)
rejectSeen x tup@(Just a, acc)
| x == a = tup
| otherwise = (Just x, x <| acc)
-- | O(n). Returns a monoidal, 'Cons'able container (a list, a Vector, etc.)
-- consisting of the targets of the given 'Foldable' container with sequential
-- duplicate elements removed
--
-- This function (sorry for the confusing name) differs from 'unique' in that
-- it only compares /sequentially/ unique elements (and thus operates in linear
-- time).
-- cf 'Data.Vector.uniq' and POSIX @uniq@ for the name
--
-- >>> uniq [1, 1, 1, 2, 2, 2, 3, 3, 1] :: [Int]
-- [1,2,3,1]
--
-- >>> uniq [1, 1, 1, 2, 2, 2, 3, 3, 1] :: Vector Int
-- [1,2,3,1]
--
uniq :: (Foldable f, Eq a, Cons c c a a, Monoid c) => f a -> c
uniq = uniqOf folded
-- | Like 'takeWhile', but inclusive
takeWhileInclusive :: (a -> Bool) -> [a] -> [a]
takeWhileInclusive _ [] = []
takeWhileInclusive p (x:xs) = x : if p x then takeWhileInclusive p xs else []

View file

@ -0,0 +1,64 @@
-- | Graphics algorithms and utils for rendering things in 2D space
--------------------------------------------------------------------------------
module Xanthous.Util.Graphics where
--------------------------------------------------------------------------------
import Xanthous.Prelude
import Data.List ( unfoldr )
--------------------------------------------------------------------------------
-- | Generate a circle centered at the given point and with the given radius
-- using the <midpoint circle algorithm
-- https://en.wikipedia.org/wiki/Midpoint_circle_algorithm>.
--
-- Code taken from <https://rosettacode.org/wiki/Bitmap/Midpoint_circle_algorithm#Haskell>
circle :: (Num i, Ord i)
=> (i, i) -- ^ center
-> i -- ^ radius
-> [(i, i)]
circle (x, y) radius
-- Four initial points, plus the generated points
= (x, y + radius) : (x, y - radius) : (x + radius, y) : (x - radius, y) : points
where
-- Creates the (x, y) octet offsets, then maps them to absolute points in all octets.
points = concatMap generatePoints $ unfoldr step initialValues
generatePoints (x, y)
= [ (x `xop` x', y `yop` y')
| (x', y') <- [(x, y), (y, x)]
, xop <- [(+), (-)]
, yop <- [(+), (-)]
]
initialValues = (1 - radius, 1, (-2) * radius, 0, radius)
step (f, ddf_x, ddf_y, x, y)
| x >= y = Nothing
| otherwise = Just ((x', y'), (f', ddf_x', ddf_y', x', y'))
where
(f', ddf_y', y') | f >= 0 = (f + ddf_y' + ddf_x', ddf_y + 2, y - 1)
| otherwise = (f + ddf_x, ddf_y, y)
ddf_x' = ddf_x + 2
x' = x + 1
-- | Draw a line between two points using Bresenham's line drawing algorithm
--
-- Code taken from <https://wiki.haskell.org/Bresenham%27s_line_drawing_algorithm>
line :: (Num i, Ord i) => (i, i) -> (i, i) -> [(i, i)]
line pa@(xa, ya) pb@(xb, yb)
= (if maySwitch pa < maySwitch pb then id else reverse) points
where
points = map maySwitch . unfoldr go $ (x, y, 0)
steep = abs (yb - ya) > abs (xb - xa)
maySwitch = if steep then swap else id
[(x, y), (x, y)] = sort [maySwitch pa, maySwitch pb]
δx = x - x
δy = abs (y - y)
ystep = if y < y then 1 else -1
go (xTemp, yTemp, err)
| xTemp > x = Nothing
| otherwise = Just ((xTemp, yTemp), (xTemp + 1, newY, newError))
where
tempError = err + δy
(newY, newError) = if (2 * tempError) >= δx
then (yTemp + ystep, tempError - δx)
else (yTemp, tempError)

View file

@ -6,6 +6,7 @@ import qualified Xanthous.GameSpec
import qualified Xanthous.Generators.UtilSpec import qualified Xanthous.Generators.UtilSpec
import qualified Xanthous.MessageSpec import qualified Xanthous.MessageSpec
import qualified Xanthous.OrphansSpec import qualified Xanthous.OrphansSpec
import qualified Xanthous.Util.GraphicsSpec
main :: IO () main :: IO ()
main = defaultMain test main = defaultMain test
@ -19,4 +20,5 @@ test = testGroup "Xanthous"
, Xanthous.MessageSpec.test , Xanthous.MessageSpec.test
, Xanthous.OrphansSpec.test , Xanthous.OrphansSpec.test
, Xanthous.DataSpec.test , Xanthous.DataSpec.test
, Xanthous.Util.GraphicsSpec.test
] ]

View file

@ -11,8 +11,12 @@ main :: IO ()
main = defaultMain test main = defaultMain test
test :: TestTree test :: TestTree
test = testGroup "Xanthous.Data.EntityMap" test = localOption (QuickCheckTests 20)
$ testGroup "Xanthous.Data.EntityMap"
[ testBatch $ monoid @(EntityMap Int) mempty [ testBatch $ monoid @(EntityMap Int) mempty
, testGroup "Deduplicate"
[ testBatch $ monoid @(Deduplicate Int) mempty
]
, testGroup "Eq laws" , testGroup "Eq laws"
[ testProperty "reflexivity" $ \(em :: EntityMap Int) -> [ testProperty "reflexivity" $ \(em :: EntityMap Int) ->
em == em em == em

View file

@ -0,0 +1,39 @@
module Xanthous.Util.GraphicsSpec (main, test) where
--------------------------------------------------------------------------------
import Test.Prelude hiding (head)
--------------------------------------------------------------------------------
import Xanthous.Util.Graphics
import Xanthous.Util
import Data.List (head)
--------------------------------------------------------------------------------
main :: IO ()
main = defaultMain test
test :: TestTree
test = testGroup "Xanthous.Util.Graphics"
[ testGroup "circle"
[ testCase "radius 12, origin 0"
$ (sort . unique @[] @[_]) (circle @Int (0, 0) 12)
@?= (sort . unique) (
let quadrant =
[ (0, 12) , (1, 12) , (2, 12) , (3, 12)
, (4, 12) , (5, 11) , (6, 11) , (7, 10)
, (8, 9) , (9, 9) , (9, 8) , (10, 7)
, (11, 6) , (11, 5) , (12, 4) , (12, 3)
, (12, 2) , (12, 1) , (12, 0)
]
in quadrant
<> (quadrant <&> _1 %~ negate)
<> (quadrant <&> _2 %~ negate)
<> (quadrant <&> both %~ negate)
)
]
, testGroup "line"
[ testProperty "starts and ends at the start and end points" $ \start end ->
let = line @Int start end
in counterexample ("line: " <> show )
$ length > 2 ==> (head === start) .&&. (head (reverse ) === end)
]
]

View file

@ -4,7 +4,7 @@ cabal-version: 1.12
-- --
-- see: https://github.com/sol/hpack -- see: https://github.com/sol/hpack
-- --
-- hash: a79caccff8895730c394c19244f068830759636d17f55f3b6d1d8a9ebe43ecdd -- hash: 86b7d3047b95fc65f4c6489a21e8c89883981c8c5bd552b5ea83aaf70de8a7cf
name: xanthous name: xanthous
version: 0.1.0.0 version: 0.1.0.0
@ -34,6 +34,7 @@ library
Xanthous.Command Xanthous.Command
Xanthous.Data Xanthous.Data
Xanthous.Data.EntityMap Xanthous.Data.EntityMap
Xanthous.Data.EntityMap.Graphics
Xanthous.Entities Xanthous.Entities
Xanthous.Entities.Arbitrary Xanthous.Entities.Arbitrary
Xanthous.Entities.Character Xanthous.Entities.Character
@ -55,6 +56,7 @@ library
Xanthous.Random Xanthous.Random
Xanthous.Resource Xanthous.Resource
Xanthous.Util Xanthous.Util
Xanthous.Util.Graphics
other-modules: other-modules:
Paths_xanthous Paths_xanthous
hs-source-dirs: hs-source-dirs:
@ -102,6 +104,7 @@ executable xanthous
Xanthous.Command Xanthous.Command
Xanthous.Data Xanthous.Data
Xanthous.Data.EntityMap Xanthous.Data.EntityMap
Xanthous.Data.EntityMap.Graphics
Xanthous.Entities Xanthous.Entities
Xanthous.Entities.Arbitrary Xanthous.Entities.Arbitrary
Xanthous.Entities.Character Xanthous.Entities.Character
@ -123,6 +126,7 @@ executable xanthous
Xanthous.Random Xanthous.Random
Xanthous.Resource Xanthous.Resource
Xanthous.Util Xanthous.Util
Xanthous.Util.Graphics
Paths_xanthous Paths_xanthous
hs-source-dirs: hs-source-dirs:
src src
@ -174,6 +178,7 @@ test-suite test
Xanthous.Generators.UtilSpec Xanthous.Generators.UtilSpec
Xanthous.MessageSpec Xanthous.MessageSpec
Xanthous.OrphansSpec Xanthous.OrphansSpec
Xanthous.Util.GraphicsSpec
Paths_xanthous Paths_xanthous
hs-source-dirs: hs-source-dirs:
test test