Skip to content

Commit

Permalink
PlayCard now takes an ObjectRef TyCard
Browse files Browse the repository at this point in the history
  • Loading branch information
MedeaMelana committed Mar 9, 2015
1 parent 4ce1d8d commit 36c88b5
Show file tree
Hide file tree
Showing 4 changed files with 27 additions and 8 deletions.
2 changes: 1 addition & 1 deletion Magic-CLI/src/Magic/Description.hs
Original file line number Diff line number Diff line change
Expand Up @@ -75,7 +75,7 @@ nullDesc world (Description (ViewT vt)) = Text.null (runReader vt world)
describePriorityAction :: PriorityAction -> Description
describePriorityAction a =
case a of
PlayCard ro@(zr, _) -> "Play from " <> describeZoneRef zr <> ": " <> describeObjectByRef ro
PlayCard ro@(zr, _) -> "Play from " <> describeZoneRef (Some zr) <> ": " <> describeObjectByRef (someObjectRef ro)
ActivateAbility (ro, i) -> "Activate ability " <> sh i <> " of " <> describeObjectByRef ro

describePayManaAction :: PayManaAction -> Description
Expand Down
21 changes: 20 additions & 1 deletion Magic/src/Magic/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@
{-# LANGUAGE GADTs #-}

module Magic.Core
( compileZoneRef, allObjects, askQuestion, debug, object, objectBase, objectPart, anyObject, player, isStackEmpty, viewObject, viewSomeObject, playerHand,
( compileZoneRef, allObjects, allCards, askQuestion, debug, object, objectBase, objectPart, anyObject, someObjectRef, player, isStackEmpty, viewObject, viewSomeObject, playerHand,
allRefsInSomeZone )
where

Expand Down Expand Up @@ -59,6 +59,22 @@ allObjects = do
<>
[ ((Some (Graveyard ip), i), c) | (i, CardObject c) <- IdList.toList (_graveyard p) ]

allCards :: View [(ObjectRef TyCard, Object)]
allCards = do
ips <- IdList.toList <$> asks players
sharedObjects <> (concat <$> for ips objectsForPlayer)
where
sharedObjects =
(map (\(i, CardObject c) -> ((Exile, i), c)) . IdList.toList <$> asks exile)
<>
(map (\(i, CardObject c) -> ((Command, i), c)) . IdList.toList <$> asks command)
objectsForPlayer (ip, p) = return $
[ ((Library ip, i), c) | (i, CardObject c) <- IdList.toList (_library p) ]
<>
[ ((Hand ip, i), c) | (i, CardObject c) <- IdList.toList (_hand p) ]
<>
[ ((Graveyard ip, i), c) | (i, CardObject c) <- IdList.toList (_graveyard p) ]

askQuestion :: (MonadInteract m, MonadView m) => PlayerRef -> Question a -> m a
askQuestion p q = do
world <- view ask
Expand Down Expand Up @@ -89,6 +105,9 @@ objectPart = lens getObjectPart modifyObjectPart
anyObject :: SomeObjectRef -> World -> Some ObjectOfType
anyObject = undefined

someObjectRef :: ObjectRef ty -> SomeObjectRef
someObjectRef (z, i) = (Some z, i)

player :: PlayerRef -> World :-> Player
player i = listEl i . players

Expand Down
10 changes: 5 additions & 5 deletions Magic/src/Magic/Engine.hs
Original file line number Diff line number Diff line change
Expand Up @@ -427,14 +427,14 @@ collectAvailableActivatedAbilities predicate p = do
payCostsOk <- lift (canPayTapCost (tapCost ability) r p)
when (predicate ability && ok && payCostsOk) (tell [(r, i)])

collectPlayableCards :: PlayerRef -> Engine [SomeObjectRef]
collectPlayableCards :: PlayerRef -> Engine [ObjectRef TyCard]
collectPlayableCards p = do
objects <- view allObjects
objects <- view allCards
execWriterT $ do
forM_ objects $ \(r,o) -> do
case get play o of
Just playAbility -> do
ok <- lift (shouldOfferActivation playAbility r p)
ok <- lift (shouldOfferActivation playAbility (someObjectRef r) p)
when ok (tell [r])
Nothing -> return ()

Expand All @@ -452,8 +452,8 @@ executePriorityAction :: PlayerRef -> PriorityAction -> Engine ()
executePriorityAction p a = do
case a of
PlayCard r -> do
Just ability <- gets (play . objectBase r)
activate (PriorityActionExecution a) ability r p
Just ability <- gets (play . objectPart . object r)
activate (PriorityActionExecution a) ability (someObjectRef r) p
ActivateAbility (r, i) -> do
abilities <- gets (activatedAbilities . objectBase r)
let ab = abilities !! i
Expand Down
2 changes: 1 addition & 1 deletion Magic/src/Magic/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -523,7 +523,7 @@ type ReplacementEffect =
type TriggeredAbilities = [Event] -> Contextual (View [Magic ()])

data PriorityAction
= PlayCard SomeObjectRef
= PlayCard (ObjectRef TyCard)
| ActivateAbility ActivatedAbilityRef
deriving Show

Expand Down

0 comments on commit 36c88b5

Please sign in to comment.