Skip to content

Commit

Permalink
Fix Dirty Fighting (2)
Browse files Browse the repository at this point in the history
* Needed to use the correct code to detect the enemy of the skill test
* Also some random cleanup
  • Loading branch information
halogenandtoast committed Jan 25, 2025
1 parent 5613b84 commit b97e90e
Show file tree
Hide file tree
Showing 3 changed files with 16 additions and 17 deletions.
8 changes: 4 additions & 4 deletions backend/arkham-api/library/Arkham/Ability/Builder.hs
Original file line number Diff line number Diff line change
Expand Up @@ -47,12 +47,12 @@ newtype ActionAbilityBuilder a = ActionAbilityBuilder {runAbilityBuilder :: Abil
instance Functor ActionAbilityBuilder where
fmap :: (a -> b) -> ActionAbilityBuilder a -> ActionAbilityBuilder b
fmap f (ActionAbilityBuilder g) = ActionAbilityBuilder $ \ability ->
let (a, ability') = g (ability)
let (a, ability') = g ability
in (f a, ability')

instance Applicative ActionAbilityBuilder where
pure :: a -> ActionAbilityBuilder a
pure x = ActionAbilityBuilder $ \ability -> (x, ability)
pure x = ActionAbilityBuilder (x,)

(<*>) :: ActionAbilityBuilder (a -> b) -> ActionAbilityBuilder a -> ActionAbilityBuilder b
(ActionAbilityBuilder f) <*> (ActionAbilityBuilder g) = ActionAbilityBuilder $ \ability ->
Expand Down Expand Up @@ -104,7 +104,7 @@ extendRevealedAbilities
-> [Ability]
extendRevealedAbilities e action =
withBaseAbilities (toAttrs e)
$ guard ((toAttrs e).revealed)
$ guard (toAttrs e).revealed
*> runReader (execWriterT $ runAbilitiesBuilder action) e

revealedSide
Expand All @@ -113,4 +113,4 @@ revealedSide
-> AbilitiesBuilder e ()
revealedSide action = do
e <- ask
when ((toAttrs e).revealed) action
when (toAttrs e).revealed action
6 changes: 3 additions & 3 deletions backend/arkham-api/library/Arkham/Ability/Scripted/Builder.hs
Original file line number Diff line number Diff line change
Expand Up @@ -61,7 +61,7 @@ instance Functor (ActionAbilityBuilder e) where

instance Applicative (ActionAbilityBuilder e) where
pure :: a -> ActionAbilityBuilder e a
pure x = ActionAbilityBuilder $ \ab -> (x, ab)
pure x = ActionAbilityBuilder (x,)

(<*>) :: ActionAbilityBuilder e (a -> b) -> ActionAbilityBuilder e a -> ActionAbilityBuilder e b
(ActionAbilityBuilder f) <*> (ActionAbilityBuilder g) = ActionAbilityBuilder $ \ab ->
Expand Down Expand Up @@ -156,7 +156,7 @@ extendRevealedAbilities
-> AbilitiesBuilder e ()
-> [ScriptedAbility e]
extendRevealedAbilities e action =
guard ((toAttrs e).revealed)
guard (toAttrs e).revealed
*> runReader (execStateT (runAbilitiesBuilder action) []) e

revealedSide
Expand All @@ -165,7 +165,7 @@ revealedSide
-> AbilitiesBuilder e ()
revealedSide action = do
e <- ask
when ((toAttrs e).revealed) action
when (toAttrs e).revealed action

tell :: [ScriptedAbility e] -> StateT [ScriptedAbility e] (Reader e) ()
tell xs = modify (<> xs)
Expand Down
19 changes: 9 additions & 10 deletions backend/arkham-api/library/Arkham/Asset/Assets/DirtyFighting2.hs
Original file line number Diff line number Diff line change
@@ -1,10 +1,10 @@
module Arkham.Asset.Assets.DirtyFighting2 (dirtyFighting2, DirtyFighting2 (..)) where
module Arkham.Asset.Assets.DirtyFighting2 (dirtyFighting2) where

import Arkham.Ability
import Arkham.Asset.Cards qualified as Cards
import Arkham.Asset.Import.Lifted hiding (EnemyEvaded)
import Arkham.Helpers.Modifiers (ModifierType (..), maybeModified_)
import Arkham.Helpers.SkillTest (getSkillTestAction, getSkillTestTarget, isParley)
import Arkham.Helpers.SkillTest (getSkillTestAction, getSkillTestTargetedEnemy, isParley)
import Arkham.Helpers.Window (evadedEnemy)
import Arkham.Matcher

Expand All @@ -16,19 +16,18 @@ dirtyFighting2 :: AssetCard DirtyFighting2
dirtyFighting2 = asset DirtyFighting2 Cards.dirtyFighting2

instance HasModifiersFor DirtyFighting2 where
getModifiersFor (DirtyFighting2 a) = case a.controller of
Nothing -> pure mempty
Just iid -> maybeModified_ a iid do
EnemyTarget eid <- MaybeT getSkillTestTarget
liftGuardM $ eid <=~> ExhaustedEnemy
getModifiersFor (DirtyFighting2 a) = for_ a.controller \iid -> do
maybeModified_ a iid do
eid <- MaybeT getSkillTestTargetedEnemy
guardM $ eid <=~> ExhaustedEnemy
action <- MaybeT getSkillTestAction
liftGuardM $ orM [pure $ action `elem` [#fight, #evade, #parley], isParley]
guardM $ (action `elem` [#fight, #evade, #parley] ||) <$> isParley
pure [AnySkillValue 2]

instance HasAbilities DirtyFighting2 where
getAbilities (DirtyFighting2 a) =
[ restrictedAbility a 1 ControlsThis
$ ReactionAbility (EnemyEvaded #after You $ ignoreAloofFightOverride AnyEnemy) (exhaust a)
[ restricted a 1 ControlsThis
$ triggered (EnemyEvaded #after You $ ignoreAloofFightOverride AnyEnemy) (exhaust a)
]

instance RunMessage DirtyFighting2 where
Expand Down

0 comments on commit b97e90e

Please sign in to comment.