Skip to content

Commit

Permalink
World.players now uses an IdList instead of IdMap
Browse files Browse the repository at this point in the history
  • Loading branch information
MedeaMelana committed Sep 3, 2012
1 parent dc0f477 commit 9691981
Show file tree
Hide file tree
Showing 4 changed files with 9 additions and 13 deletions.
6 changes: 3 additions & 3 deletions Engine.hs
Expand Up @@ -141,9 +141,9 @@ compileEffect :: OneShotEffect -> Engine ()
compileEffect (UntapPermanent ro) =
battlefield .^ listEl ro .^ tapStatus =: Just Untapped
compileEffect (DrawCard rp) = do
lib <- gets (players .^ mapEl rp .^ library)
lib <- gets (players .^ listEl rp .^ library)
case IdList.toList lib of
[] -> players .^ mapEl rp .^ failedCardDraw =: True
[] -> players .^ listEl rp .^ failedCardDraw =: True
(ro, _) : _ -> executeEffect (MoveObject (Library rp, ro) (Hand rp))
compileEffect (MoveObject rObject@(rFromZone, i) rToZone) = do
mObject <- lookupObject rObject
Expand All @@ -153,7 +153,7 @@ compileEffect (MoveObject rObject@(rFromZone, i) rToZone) = do
compileZoneRef rFromZone ~: IdList.remove i
compileZoneRef rToZone ~: IdList.cons object
compileEffect (ShuffleLibrary rPlayer) = do
let libraryLabel = players .^ mapEl rPlayer .^ library
let libraryLabel = players .^ listEl rPlayer .^ library
lib <- gets libraryLabel
lib' <- lift (IdList.shuffle lib)
puts libraryLabel lib'
Expand Down
6 changes: 5 additions & 1 deletion IdList.hs
Expand Up @@ -6,13 +6,17 @@ module IdList
import Prelude hiding (filter)
import qualified Prelude

import Control.Arrow (second)
import Control.Monad.Random (MonadRandom)
import System.Random.Shuffle (shuffleM)

type Id = Int

data IdList a = IdList [(Id, a)] Id

instance Functor IdList where
fmap = contents . fmap . second

empty :: IdList a
empty = IdList [] 0

Expand All @@ -32,7 +36,7 @@ remove i = contents (Prelude.filter (\(i', _) -> i /= i'))
cons :: a -> IdList a -> IdList a
cons x (IdList ixs i) = IdList ((i, x) : ixs) (succ i)

contents :: ([(Id, a)] -> [(Id, a)]) -> IdList a -> IdList a
contents :: ([(Id, a)] -> [(Id, b)]) -> IdList a -> IdList b
contents f (IdList ixs i) = IdList (f ixs) i

toList :: IdList a -> [(Id, a)]
Expand Down
5 changes: 0 additions & 5 deletions Labels.hs
Expand Up @@ -4,23 +4,18 @@ module Labels where

import IdList (Id, IdList)
import qualified IdList
import Types

import Prelude hiding ((.), id)
import Control.Category (Category(..), (>>>))
import Control.Monad.State (MonadState)
import Data.Label.Pure ((:->), lens)
import Data.Label.PureM
import qualified Data.IntMap as IntMap
import Data.Maybe (fromJust)


listEl :: Id -> IdList a :-> a
listEl i = lens (fromJust . IdList.get i) (IdList.set i)

mapEl :: Id -> IdMap a :-> a
mapEl i = lens (IntMap.! i) (IntMap.insert i)

(.^) :: Category (~>) => a ~> b -> b ~> c -> a ~> c
(.^) = (>>>)

Expand Down
5 changes: 1 addition & 4 deletions Types.hs
Expand Up @@ -16,23 +16,20 @@ import Control.Monad.Identity
import Control.Monad.Operational
import Data.Label (mkLabels)
import Data.Label.Pure ((:->))
import Data.IntMap (IntMap)
import Data.Monoid
import Data.Set (Set)
import Data.Text (Text)


type Bag = []

type IdMap = IntMap

type PlayerRef = Id
type ObjectRef = (ZoneRef, Id)


-- | Current game situation.
data World = World
{ _players :: IdMap Player
{ _players :: IdList Player
, _activePlayer :: PlayerRef
, _activeStep :: Step
, _time :: Timestamp
Expand Down

0 comments on commit 9691981

Please sign in to comment.