Skip to content

Commit

Permalink
More memories
Browse files Browse the repository at this point in the history
  • Loading branch information
halogenandtoast committed Dec 23, 2024
1 parent 50c56f1 commit 15cd971
Show file tree
Hide file tree
Showing 11 changed files with 117 additions and 10 deletions.
Original file line number Diff line number Diff line change
@@ -1,15 +1,40 @@
module Arkham.Enemy.Cards.MemoryOfATerribleDiscovery (memoryOfATerribleDiscovery) where

import Arkham.Ability
import Arkham.Asset.Cards qualified as Assets
import Arkham.Enemy.Cards qualified as Cards
import Arkham.Enemy.Import.Lifted
import Arkham.Enemy.Import.Lifted hiding (EnemyAttacks, EnemyDefeated)
import Arkham.Helpers.Story
import Arkham.Matcher
import Arkham.Story.Cards qualified as Stories

newtype MemoryOfATerribleDiscovery = MemoryOfATerribleDiscovery EnemyAttrs
deriving anyclass (IsEnemy, HasModifiersFor)
deriving newtype (Show, Eq, ToJSON, FromJSON, Entity, HasAbilities)
deriving newtype (Show, Eq, ToJSON, FromJSON, Entity)

memoryOfATerribleDiscovery :: EnemyCard MemoryOfATerribleDiscovery
memoryOfATerribleDiscovery = enemy MemoryOfATerribleDiscovery Cards.memoryOfATerribleDiscovery (3, PerPlayer 4, 3) (1, 1)
memoryOfATerribleDiscovery =
enemyWith MemoryOfATerribleDiscovery Cards.memoryOfATerribleDiscovery (3, PerPlayer 4, 3) (1, 1)
$ preyL
.~ Prey (ControlsAsset $ assetIs Assets.averyClaypoolAntarcticGuide)

instance HasAbilities MemoryOfATerribleDiscovery where
getAbilities (MemoryOfATerribleDiscovery a) =
extend
a
[ restricted a 1 OnSameLocation $ parleyAction (AddFrostTokenCost 1)
, mkAbility a 2 $ forced $ EnemyDefeated #when You ByAny (be a)
]

instance RunMessage MemoryOfATerribleDiscovery where
runMessage msg (MemoryOfATerribleDiscovery attrs) = runQueueT $ case msg of
runMessage msg e@(MemoryOfATerribleDiscovery attrs) = runQueueT $ case msg of
UseThisAbility _iid (isSource attrs -> True) 1 -> do
nonAttackEnemyDamage (attrs.ability 1) 4 attrs.id
pure e
UseThisAbility iid (isSource attrs -> True) 2 -> do
flipOverBy iid (attrs.ability 2) attrs
pure e
Flip iid _ (isTarget attrs -> True) -> do
readStory iid attrs Stories.memoryOfATerribleDiscovery
pure e
_ -> MemoryOfATerribleDiscovery <$> liftRunMessage msg attrs
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,9 @@ instance HasAbilities MemoryOfAnAlienTranslation where
getAbilities (MemoryOfAnAlienTranslation a) =
extend
a
[ mkAbility a 1 $ freeReaction $ EnemyExhausts #after (be a)
[ restricted a 1 (thisExists a $ EnemyAt LocationWithAttachment)
$ freeReaction
$ EnemyExhausts #after (be a)
, mkAbility a 2 $ forced $ EnemyDefeated #when You ByAny (be a)
]

Expand Down
Original file line number Diff line number Diff line change
@@ -1,15 +1,41 @@
module Arkham.Enemy.Cards.MemoryOfAnUnrequitedLove (memoryOfAnUnrequitedLove) where

import Arkham.Ability
import Arkham.Asset.Cards qualified as Assets
import Arkham.Enemy.Cards qualified as Cards
import Arkham.Enemy.Import.Lifted
import Arkham.Enemy.Import.Lifted hiding (DiscoverClues, EnemyDefeated)
import Arkham.Helpers.Story
import Arkham.Helpers.Window
import Arkham.Matcher
import Arkham.Story.Cards qualified as Stories

newtype MemoryOfAnUnrequitedLove = MemoryOfAnUnrequitedLove EnemyAttrs
deriving anyclass (IsEnemy, HasModifiersFor)
deriving newtype (Show, Eq, ToJSON, FromJSON, Entity, HasAbilities)
deriving newtype (Show, Eq, ToJSON, FromJSON, Entity)

memoryOfAnUnrequitedLove :: EnemyCard MemoryOfAnUnrequitedLove
memoryOfAnUnrequitedLove = enemy MemoryOfAnUnrequitedLove Cards.memoryOfAnUnrequitedLove (4, PerPlayer 3, 3) (1, 1)
memoryOfAnUnrequitedLove =
enemyWith MemoryOfAnUnrequitedLove Cards.memoryOfAnUnrequitedLove (4, PerPlayer 3, 3) (1, 1)
$ preyL
.~ Prey (ControlsAsset $ assetIs Assets.drAmyKenslerProfessorOfBiology)

instance HasAbilities MemoryOfAnUnrequitedLove where
getAbilities (MemoryOfAnUnrequitedLove a) =
extend
a
[ mkAbility a 1 $ freeReaction $ DiscoverClues #after You (locationWithEnemy a) (atLeast 1)
, mkAbility a 2 $ forced $ EnemyDefeated #when You ByAny (be a)
]

instance RunMessage MemoryOfAnUnrequitedLove where
runMessage msg (MemoryOfAnUnrequitedLove attrs) = runQueueT $ case msg of
runMessage msg e@(MemoryOfAnUnrequitedLove attrs) = runQueueT $ case msg of
UseCardAbility _iid (isSource attrs -> True) 1 (discoveredClues -> n) _ -> do
nonAttackEnemyDamage (attrs.ability 1) n attrs.id
pure e
UseThisAbility iid (isSource attrs -> True) 2 -> do
flipOverBy iid (attrs.ability 2) attrs
pure e
Flip iid _ (isTarget attrs -> True) -> do
readStory iid attrs Stories.memoryOfAnUnrequitedLove
pure e
_ -> MemoryOfAnUnrequitedLove <$> liftRunMessage msg attrs
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ instance HasAbilities MemoryOfAnUnspeakableEvil where
getAbilities (MemoryOfAnUnspeakableEvil a) =
extend
a
[ restricted a 1 (thisExists a ExhaustedEnemy)
[ restricted a 1 OnSameLocation
$ ActionAbility [#parley] (ActionCost 2 <> ShuffleTopOfScenarioDeckIntoYourDeck 3 TekeliliDeck)
, mkAbility a 2 $ forced $ EnemyDefeated #when You ByAny (be a)
]
Expand Down
14 changes: 14 additions & 0 deletions backend/arkham-api/library/Arkham/Game.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1543,6 +1543,14 @@ getLocationsMatching lmatcher = do
flip filterM ls $ \l -> do
lmEvents <- select $ EventAttachedTo $ TargetIs $ toTarget l
pure . notNull $ List.intersect events lmEvents
LocationWithAttachment -> do
flip filterM ls $ \l -> do
orM
[ selectAny $ EventAttachedTo $ TargetIs $ toTarget l
, selectAny $ AssetAttachedTo $ TargetIs $ toTarget l
, selectAny $ TreacheryIsAttachedTo $ toTarget l
, selectAny $ EnemyAttachedTo $ TargetIs $ toTarget l
]
LocationWithInvestigator (InvestigatorWithId iid) -> do
mLocation <- field InvestigatorLocation iid
pure $ filter ((`elem` mLocation) . toId) ls
Expand Down Expand Up @@ -2908,6 +2916,12 @@ enemyMatcherFilter es matcher' = case matcher' of
MovingEnemy -> flip filterM es \enemy -> (== Just (toId enemy)) . view enemyMovingL <$> getGame
EvadingEnemy -> flip filterM es \enemy -> (== Just (toId enemy)) . view enemyEvadingL <$> getGame
EnemyWithVictory -> filterM (getHasVictoryPoints . toId) es
EnemyAttachedTo targetMatcher -> do
let
isValid a = case (enemyPlacement (toAttrs a)).attachedTo of
Just target -> targetMatches target targetMatcher
_ -> pure False
filterM isValid es
EnemyAttachedToAsset assetMatcher -> do
placements <- select assetMatcher
flip filterM es \enemy -> do
Expand Down
1 change: 1 addition & 0 deletions backend/arkham-api/library/Arkham/Game/Helpers.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3298,6 +3298,7 @@ locationMatches investigatorId source window locationId matcher' = do
Nothing -> pure False
Just shroud -> gameValueMatches shroud valueMatcher
Matcher.LocationWithAttachedEvent {} -> locationId <=~> matcher
Matcher.LocationWithAttachment {} -> locationId <=~> matcher
Matcher.LocationWithShroudLessThanOrEqualToLessThanEnemyMaybeField {} -> locationId <=~> matcher
Matcher.LocationWithMostClues locationMatcher ->
elem locationId
Expand Down
2 changes: 2 additions & 0 deletions backend/arkham-api/library/Arkham/Matcher/Enemy.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,7 @@ import {-# SOURCE #-} Arkham.Matcher.Event
import {-# SOURCE #-} Arkham.Matcher.Investigator
import {-# SOURCE #-} Arkham.Matcher.Location
import {-# SOURCE #-} Arkham.Matcher.Source
import {-# SOURCE #-} Arkham.Matcher.Target
import Arkham.Matcher.Value
import {-# SOURCE #-} Arkham.Modifier
import {-# SOURCE #-} Arkham.Placement
Expand Down Expand Up @@ -49,6 +50,7 @@ data EnemyMatcher
| EnemyWithToken Token
| EnemyAt LocationMatcher
| EnemyAttachedToAsset AssetMatcher
| EnemyAttachedTo TargetMatcher
| EnemyCanEnter LocationMatcher
| EnemyCanSpawnIn LocationMatcher
| EnemyCanMove
Expand Down
1 change: 1 addition & 0 deletions backend/arkham-api/library/Arkham/Matcher/Location.hs
Original file line number Diff line number Diff line change
Expand Up @@ -90,6 +90,7 @@ data LocationMatcher
| LocationCanBeEnteredBy EnemyId
| LocationWithAsset AssetMatcher
| LocationWithAttachedEvent EventMatcher
| LocationWithAttachment
| LocationWithCardsUnderneath CardListMatcher
| LocationWithInvestigator InvestigatorMatcher
| CanEnterLocation InvestigatorMatcher
Expand Down
12 changes: 12 additions & 0 deletions backend/arkham-api/library/Arkham/Matcher/Target.hs-boot
Original file line number Diff line number Diff line change
@@ -0,0 +1,12 @@
module Arkham.Matcher.Target where

import Arkham.Prelude

data TargetMatcher

instance Data TargetMatcher
instance Show TargetMatcher
instance Eq TargetMatcher
instance Ord TargetMatcher
instance ToJSON TargetMatcher
instance FromJSON TargetMatcher
Original file line number Diff line number Diff line change
@@ -1,5 +1,11 @@
module Arkham.Story.Cards.MemoryOfATerribleDiscovery (memoryOfATerribleDiscovery) where

import Arkham.Asset.Cards qualified as Assets
import Arkham.CampaignLog (PartnerStatus (Resolute))
import Arkham.CampaignLogKey
import Arkham.Campaigns.EdgeOfTheEarth.Helpers
import Arkham.Matcher
import Arkham.Scenarios.FatalMirage.Helpers
import Arkham.Story.Cards qualified as Cards
import Arkham.Story.Import.Lifted

Expand All @@ -13,5 +19,11 @@ memoryOfATerribleDiscovery = story MemoryOfATerribleDiscovery Cards.memoryOfATer
instance RunMessage MemoryOfATerribleDiscovery where
runMessage msg s@(MemoryOfATerribleDiscovery attrs) = runQueueT $ case msg of
ResolveStory _ ResolveIt story' | story' == toId attrs -> do
record ClaypoolHasConfrontedHisDemons
setPartnerStatus Assets.averyClaypoolAntarcticGuide Resolute
selectForMaybeM (assetIs Assets.averyClaypoolAntarcticGuide) \claypool ->
push $ ReplaceAsset claypool Assets.averyClaypoolAntarcticGuideResolute
addToVictory attrs
mayAdvance attrs
pure s
_ -> MemoryOfATerribleDiscovery <$> liftRunMessage msg attrs
Original file line number Diff line number Diff line change
@@ -1,5 +1,11 @@
module Arkham.Story.Cards.MemoryOfAnUnrequitedLove (memoryOfAnUnrequitedLove) where

import Arkham.Asset.Cards qualified as Assets
import Arkham.CampaignLog (PartnerStatus (Resolute))
import Arkham.CampaignLogKey
import Arkham.Campaigns.EdgeOfTheEarth.Helpers
import Arkham.Matcher
import Arkham.Scenarios.FatalMirage.Helpers
import Arkham.Story.Cards qualified as Cards
import Arkham.Story.Import.Lifted

Expand All @@ -13,5 +19,11 @@ memoryOfAnUnrequitedLove = story MemoryOfAnUnrequitedLove Cards.memoryOfAnUnrequ
instance RunMessage MemoryOfAnUnrequitedLove where
runMessage msg s@(MemoryOfAnUnrequitedLove attrs) = runQueueT $ case msg of
ResolveStory _ ResolveIt story' | story' == toId attrs -> do
record DrKenslerHasConfrontedHerDemons
setPartnerStatus Assets.drAmyKenslerProfessorOfBiology Resolute
selectForMaybeM (assetIs Assets.drAmyKenslerProfessorOfBiology) \drKensler ->
push $ ReplaceAsset drKensler Assets.drAmyKenslerProfessorOfBiologyResolute
addToVictory attrs
mayAdvance attrs
pure s
_ -> MemoryOfAnUnrequitedLove <$> liftRunMessage msg attrs

0 comments on commit 15cd971

Please sign in to comment.