dovin-3.0: A proof assistant for Magic: The Gathering puzzles.
Safe HaskellNone
LanguageHaskell2010

Dovin.V3

Description

V3 introduces a new effects system that is incompatible with V2 effects. V3 effects are more flexible and better align with the layer system. It also adds some new card properties.

  • withEffect has a new, more flexible API.
  • withEffectWhen added as a version of withEffect that allows customization of then the effect should apply (by default they apply when card is in play).
  • withCMC to set converted mana cost on cards.
  • addEffect to apply an effect to a card. In combination with effectPTAdjust this replaces altering cardStrengthModifier directly, which is now removed.
  • Added a suite of `effect*` builders for effects.
  • Added cardOwner property to cards, and withOwner fluid builder to set it.
Synopsis

Documentation

view :: MonadReader s m => Getting a s a -> m a #

View the value pointed to by a Getter, Iso or Lens or the result of folding over all the results of a Fold or Traversal that points at a monoidal value.

view . toid
>>> view (to f) a
f a
>>> view _2 (1,"hello")
"hello"
>>> view (to succ) 5
6
>>> view (_2._1) ("hello",("world","!!!"))
"world"

As view is commonly used to access the target of a Getter or obtain a monoidal summary of the targets of a Fold, It may be useful to think of it as having one of these more restricted signatures:

view ::             Getter s a     -> s -> a
view :: Monoid m => Fold s m       -> s -> m
view ::             Iso' s a       -> s -> a
view ::             Lens' s a      -> s -> a
view :: Monoid m => Traversal' s m -> s -> m

In a more general setting, such as when working with a Monad transformer stack you can use:

view :: MonadReader s m             => Getter s a     -> m a
view :: (MonadReader s m, Monoid a) => Fold s a       -> m a
view :: MonadReader s m             => Iso' s a       -> m a
view :: MonadReader s m             => Lens' s a      -> m a
view :: (MonadReader s m, Monoid a) => Traversal' s a -> m a

data Step Source #

Constructors

Step 

newtype BaseCard Source #

Constructors

BaseCard Card 

Instances

Instances details
Eq BaseCard Source # 
Instance details

Defined in Dovin.Types

Show BaseCard Source # 
Instance details

Defined in Dovin.Types

data EffectDuration Source #

Constructors

EndOfTurn 

data Phase Source #

A phase or step in a turn. Phases and steps are not distinguished between because haven't seen a need to.

Instances

Instances details
Eq Phase Source # 
Instance details

Defined in Dovin.Types

Methods

(==) :: Phase -> Phase -> Bool #

(/=) :: Phase -> Phase -> Bool #

Ord Phase Source # 
Instance details

Defined in Dovin.Types

Methods

compare :: Phase -> Phase -> Ordering #

(<) :: Phase -> Phase -> Bool #

(<=) :: Phase -> Phase -> Bool #

(>) :: Phase -> Phase -> Bool #

(>=) :: Phase -> Phase -> Bool #

max :: Phase -> Phase -> Phase #

min :: Phase -> Phase -> Phase #

Show Phase Source # 
Instance details

Defined in Dovin.Types

Methods

showsPrec :: Int -> Phase -> ShowS #

show :: Phase -> String #

showList :: [Phase] -> ShowS #

data Target Source #

Constructors

TargetPlayer Player

Target a player, use targetPlayer to construct.

TargetCard CardName

Target a card, use targetCard to construct.

Instances

Instances details
Eq Target Source # 
Instance details

Defined in Dovin.Types

Methods

(==) :: Target -> Target -> Bool #

(/=) :: Target -> Target -> Bool #

Show Target Source # 
Instance details

Defined in Dovin.Types

data LayeredEffectDefinition Source #

Constructors

LayeredEffectDefinition 

Fields

data Layer Source #

Constructors

Layer1A

Copiable effects

Layer1B

Face down spells and permanents

Layer2

Control-changing effects

Layer3

Text changing effects

Layer4

Type changing effects

Layer5

Color changing effects

Layer6

Ability changing effects

Layer7A

P/T from CDAs

Layer7B

P/T from setting

Layer7C

P/T adjustments (inc. counters)

Layer7D

P/T Switching

LayerOther

Other game rule affecting effects

Instances

Instances details
Bounded Layer Source # 
Instance details

Defined in Dovin.Types

Enum Layer Source # 
Instance details

Defined in Dovin.Types

Eq Layer Source # 
Instance details

Defined in Dovin.Types

Methods

(==) :: Layer -> Layer -> Bool #

(/=) :: Layer -> Layer -> Bool #

Ord Layer Source # 
Instance details

Defined in Dovin.Types

Methods

compare :: Layer -> Layer -> Ordering #

(<) :: Layer -> Layer -> Bool #

(<=) :: Layer -> Layer -> Bool #

(>) :: Layer -> Layer -> Bool #

(>=) :: Layer -> Layer -> Bool #

max :: Layer -> Layer -> Layer #

min :: Layer -> Layer -> Layer #

Show Layer Source # 
Instance details

Defined in Dovin.Types

Methods

showsPrec :: Int -> Layer -> ShowS #

show :: Layer -> String #

showList :: [Layer] -> ShowS #

data Location Source #

Constructors

Hand 
Graveyard 
Play 
Stack 
Exile 
Deck 

Instances

Instances details
Eq Location Source # 
Instance details

Defined in Dovin.Types

Ord Location Source # 
Instance details

Defined in Dovin.Types

Show Location Source # 
Instance details

Defined in Dovin.Types

data Player Source #

Constructors

Active 
Opponent 

Instances

Instances details
Eq Player Source # 
Instance details

Defined in Dovin.Types

Methods

(==) :: Player -> Player -> Bool #

(/=) :: Player -> Player -> Bool #

Ord Player Source # 
Instance details

Defined in Dovin.Types

Show Player Source # 
Instance details

Defined in Dovin.Types

Generic Player Source # 
Instance details

Defined in Dovin.Types

Associated Types

type Rep Player :: Type -> Type #

Methods

from :: Player -> Rep Player x #

to :: Rep Player x -> Player #

Hashable Player Source # 
Instance details

Defined in Dovin.Types

Methods

hashWithSalt :: Int -> Player -> Int #

hash :: Player -> Int #

type Rep Player Source # 
Instance details

Defined in Dovin.Types

type Rep Player = D1 ('MetaData "Player" "Dovin.Types" "dovin-3.0-D8jAg3rtI8467M8j4unCKt" 'False) (C1 ('MetaCons "Active" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Opponent" 'PrefixI 'False) (U1 :: Type -> Type))

data Color Source #

Constructors

Red 
Green 
Blue 
Black 
White 

Instances

Instances details
Eq Color Source # 
Instance details

Defined in Dovin.Types

Methods

(==) :: Color -> Color -> Bool #

(/=) :: Color -> Color -> Bool #

Ord Color Source # 
Instance details

Defined in Dovin.Types

Methods

compare :: Color -> Color -> Ordering #

(<) :: Color -> Color -> Bool #

(<=) :: Color -> Color -> Bool #

(>) :: Color -> Color -> Bool #

(>=) :: Color -> Color -> Bool #

max :: Color -> Color -> Color #

min :: Color -> Color -> Color #

Show Color Source # 
Instance details

Defined in Dovin.Types

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

manaPoolFor :: Functor f => Player -> ([Char] -> f [Char]) -> Board -> f Board Source #

run :: (Step -> Formatter) -> GameMonad () -> IO () Source #

numbered :: Int -> CardName -> CardName Source #

Return a card name suffixed by the given number.

modifyCard :: ASetter Card Card a b -> (a -> b) -> CardName -> GameMonad () Source #

as :: Player -> GameMonad () -> GameMonad () Source #

Perform action as the specified player.

withAttribute :: String -> GameMonad () -> GameMonad () Source #

Add an attribute to the created card, as identified by a string. Attributes with that special meaning to Dovin built-ins (such as flying) are defined in Dovin.Attributes.

withAttributes :: [String] -> GameMonad () -> GameMonad () Source #

Helper version of withAttribute for adding multiple attributes at a time.

withEffectWhen Source #

Arguments

:: EffectMonad Bool

Effect only applies when this returns true

-> EffectMonad CardMatcher

The set of cards to apply the effect to

-> [LayeredEffectPart]

The effect to apply

-> EffectName

Human-readable description, cosmetic only.

-> GameMonad () 
-> GameMonad () 

A more flexible version of withEffect that allows customization of then the effect should apply.

withCMC :: Int -> GameMonad () -> GameMonad () Source #

Set the converted mana cost of the created card.

withLocation :: Location -> GameMonad () -> GameMonad () Source #

Place the created card into a specific location.

withOwner :: Player -> GameMonad () -> GameMonad () Source #

Set the owner for the created card. If not specified, defaults to the owner of the card location.

withPlusOneCounters :: Int -> GameMonad () -> GameMonad () Source #

Set the number of +1/+1 counters of the created card.

withMinusOneCounters :: Int -> GameMonad () -> GameMonad () Source #

Set the number of -1/-1 counters of the created card.

addMana :: ManaString -> GameMonad () Source #

Add mana to actor's mana pool.

addMana "2RG"
Validates
  • Mana specification is valid.
Effects
  • Mana pool is increased.

cast :: ManaPool -> CardName -> GameMonad () Source #

Casts a card from actor's hand. See castFromLocation for specification.

cast "R" "Shock"
Validates
  • Card exists in hand.

castFromLocation :: CardLocation -> ManaPool -> CardName -> GameMonad () Source #

Move a card to the stack, spending the specified mana. If not tracking mana, use the empty string to cast for no mana. Typically you will want to resolve after casting. For the common case of casting from hand, see cast. See spendMana for additional mana validations and effects.

castFromLocation "1B" "Oathsworn Vampire" >> resolveTop
Validates
Effects

counter :: CardName -> GameMonad () Source #

Remove a spell from the stack.

counter "Shock"
Validates
  • Card is on stack.
  • Card is not a triggered or activated ability.
Effects
  • Card is moved to graveyard. (See move for alternate effects.)

flashback :: ManaPool -> CardName -> GameMonad () Source #

Cast a card from actor's graveyard, exiling it when it leaves the stack. See castFromLocation for further specification.

flashback "R" "Shock"

Does not validate whether the card actually has a flashback cost. If important, use a wrapper function in your solution:

flashbackSnapped mana castName = do
  validate (matchAttribute "snapcastered") castName
  flashback mana castName
Validates
  • Card is in actor's graveyard.
Effects

jumpstart :: ManaPool -> CardName -> CardName -> GameMonad () Source #

Cast a card from active player's graveyard, discarding a card in addition to its mana cost, exiling it when it leaves the stack. See castFromLocation for further specification.

jumpstart "R" "Mountain" "Shock"
Validates
  • Card is in actor's graveyard.
  • Discard card is in actor's hand.
Effects

resolve :: CardName -> GameMonad () Source #

Resolves a card on the stack.

cast "R" "Shock" >> resolve "Shock"
Validates
  • Stack is not empty.
  • Card is on top of stack.
Effects

resolveTop :: GameMonad () Source #

Resolves the top card of the stack. Use this for simple cast-and-resolve scenarios. For more complicated stack states, prefer resolve with a named spell to ensure the expected one is resolving.

Validates
  • Stack is not empty.
Effects
  • If spell, move card to graveyard of owner.
  • If permanent, move card to play area of owner.
  • If trigger, remove card.
  • See move for possible alternate effects, depending on card attributes.

resolveMentor :: CardName -> CardName -> ExceptT String (ReaderT Env (StateT Board (WriterT [Step] Identity))) () Source #

Resolves a trigger created by triggerMentor. Adds +1/+1 to target card if still a valid mentor target.

resolveMentor "Goblin 1" "Legion Warboss"
Validates
  • Mentor trigger is top of stack.
  • Target card is attacking.
  • Target card has less power than source card.
Effects
  • Target card gets +1/+1.
  • Trigger is removed from top of stack.

sacrifice :: CardName -> GameMonad () Source #

Sacrifice a permanent.

sacrifice "Soldier"
Validates
  • Permanent controlled by current actor.
  • Permanent is in play.
Effects
  • Card is moved to graveyard. See move for possible alternate effects.

splice :: CardName -> ManaString -> CardName -> GameMonad () Source #

Splices a spell on to a previously cast arcane spell.

splice "Goryo's Vengeance" "2RR" "Through the Breach"
Validates
  • Target spell is arcane.
  • Target spell is on stack.
  • Spliced spell is in hand.
  • See spendMana for additional validations.
Effects

tapForMana :: ManaString -> CardName -> GameMonad () Source #

Combination of tap and addMana, see them for specification.

transitionTo :: Phase -> GameMonad () Source #

Transition to a new game phase or step.

transitionTo DeclareAttackers
Validates
  • The new phase would occur after the current phase in a normal turn.
Effects
  • Empty the mana pool.
  • Transition to new phase.

transitionToForced :: Phase -> GameMonad () Source #

Equivalent to transitionTo except it skips all validation. Useful when an effect has modified the normal order of phases, such as adding an extra combat step.

trigger :: CardName -> CardName -> GameMonad () Source #

Triggers an effect of a permanent. Typically you will want to resolve after triggering.

trigger "Draw Card" "Dawn of Hope" >> resolveTop
Validates
  • Card is in play or graveyard.
  • Card is cotrolled by actor.
Effects

triggerMentor :: CardName -> CardName -> GameMonad () Source #

Triggers a mentor effect from an attacking creature, targeting another attacking creature with lesser power. Typically you will want to resolveMentor after triggering.

triggerMentor "Goblin 1" "Legion Warboss"
Validates
  • Source card has attacking and mentor attributes.
  • Target card is attacking.
  • Target card has less power than source card.
Effects
  • A triggered card is placed on the stack.

with :: CardName -> (CardName -> GameMonad ()) -> GameMonad () Source #

Helper function to provide a scoped let.

with "Angel" $ \cn -> target cn >> destroy cn

move :: CardLocation -> CardLocation -> CardName -> GameMonad () Source #

Move a card from one location to another.

move (Opponent, Play) (Active, Play) "Angel"
Validates
  • Card exists in source location.
  • Destination is not stack (use a cast variant instead).
  • Destination does not match source.
  • If card has token attribute, source is in play. (Removing token once they have left play is handled by runStateBasedActions.)
  • If card has copy attribute, source is the stack. (Removing token once they have left play is handled by runStateBasedActions.)
Effects
  • Card moved to destination location.
  • If card is leaving play, remove all damage, counters, and gained attributes.
  • If card has exileWhenLeaveStack attribute, move to exile and remove exileWhenLeaveStack instead.
  • If card has undying, is moving from play to graveyard, and has no +1/+1 counters, add a +1/+1 counter instead. (Note: undying should move card to graveyard then back to play for owner, but since neither triggers nor owner tracking are implemented, this simplification is valid.)
  • If card is entering play or changing controller, add summoned attribute.

target :: CardName -> GameMonad () Source #

Target a permanent.

Validates
  • Card is in play.
  • If card belongs to opponent, does not have hexproof.

targetInLocation :: CardLocation -> CardName -> GameMonad () Source #

Target a card in a non-play location.

Validates
  • Card is in zone.

activate :: CardName -> ManaPool -> CardName -> GameMonad () Source #

Activate an ability of a permanent. See spendMana for additional mana validations and effects. Typically you will want to resolve after activating.

activate "Create Soldier" "3W" "Dawn of Hope" >> resolveTop
Validates
  • Card is in play or graveyard.
  • Card is controlled by actor.
Effects

activatePlaneswalker :: CardName -> Int -> CardName -> GameMonad () Source #

Activate a loyalty ability of a planeswalker. Typically you will want to resolve after activating.

activatePlaneswalker2 "Get a card" (-1) "Karn, Scion of Urza" >> resolveTop
Validates
  • Card is in play.
  • Card has enough loyalty.
Effects
  • Card loyalty is adjusted.

See activate for additional validations and effects.

attackWith :: [CardName] -> GameMonad () Source #

Start an attack with the given creatures.

attackWith ["Fanatical Firebrand"]
Validates
Effects

combatDamage :: [CardName] -> CardName -> GameMonad () Source #

Apply combat damage between an attacker and blockers, using a simple damage assignment algorithm. For more complex assignments, use damage directly.

combatDamage ["Spirit 1", "Spirit 2"] "Angel"

See damage for other validations and effects.

Validates
  • Attacker has attribute attacking.
  • Attacker and blockers are in play.
  • Attacker controlled by current actor.
  • Blockers have attribute creature.
Effects
  • Damage is dealt to blockers in order given, with the final blocker receiving any left over damage.
  • If no blockers, damage is dealt to opposing player.
  • If attacker has trample, any remaining damage is dealt to opposing player.

copySpell :: CardName -> CardName -> ExceptT String (ReaderT Env (StateT Board (WriterT [Step] Identity))) () Source #

Copy a spell on the stack, adding it to top of stack.

copySpell "Snap Copy" "Snap"
Validates
  • Card is on stack.
Effects
  • New card is on top of stack.

damage Source #

Arguments

:: (Card -> Int)

A function that returns the amount of damage to apply, given the source card.

-> Target

Target to apply damage to

-> CardName

Source card

-> GameMonad () 

Applies damage from a source to a target.

damage (const 2) (targetPlayer Opponent) "Shock"
Validates
  • Source exists.
  • Damage is not less than zero.
  • If targeting a card, target is in play and is either a creature or a planeswalker.
Effects
  • Adds damage to the target.
  • If target is a planeswalker, remove loyalty counters instead.
  • If source has deathtouch and target is a creature and damage is non-zero, add deathtouched attribute to target.
  • If source has lifelink, controller of source gains life equal to damage dealt.
  • Note runStateBasedActions handles actual destruction (if applicable) of creatures and planeswalkers.

destroy :: CardName -> GameMonad () Source #

Destroy a permanent.

Validates
Effects
  • Card is moved to graveyard. See move for possible alternate effects.

discard :: CardName -> GameMonad () Source #

Discard a card from the active player's hand.

discard "Mountain"
Validates
  • Card exists in active player's hand.
Effects
  • Card moved to graveyard.

exert :: CardName -> GameMonad () Source #

Exert a card. Works best when card has an associated effect that applies when exerted attribute is present.

withAttributes [flying]
  $ withEffect
      (matchInPlay <> matchAttribute exerted)
      (    matchLocation . view cardLocation
        <> const (matchAttribute creature)
      )
      (pure . over cardStrengthModifier (mkStrength (1, 1) <>))
  $ addCreature (2, 2) "Tah-Crop Elite"
attackWith ["Tah-Crop Elite"]
exert "Tah-Crop Elite"
Validates
Effects

exile :: CardName -> GameMonad () Source #

Move a card to the Exile zone.

exile "Bridge from Below"

See moveTo for validations and effects.

fight :: CardName -> CardName -> GameMonad () Source #

Have one card fight another (each deals damage to the other).

Validates
  • Card is in play.
  • Card is a creature.
Effects
  • Each card has damage dealt to it equal to the other's power. A creature fighting itself will take twice its power in damage.
  • Note runStateBasedActions handles actual destruction (if applicable) of creatures.

modifyStrength :: (Int, Int) -> CardName -> GameMonad () Source #

Modify the strength of a card in play. It will be reset to base when the card leaves play.

modifyStrength (-2, -2) "Soldier"
Validates
  • Card is in play.
  • Card is a creature.
Effects
  • Changes the strength modifier for the card.

moveTo :: Location -> CardName -> GameMonad () Source #

Move card to location with same controller.

moveTo Graveyard "Forest"
Validates
  • Card exists.
Effects
  • Card is moved to location.
  • See move for possible alternate effects, depending on card

spendMana :: ManaString -> GameMonad () Source #

Remove mana from the pool. Colored mana will be removed first, then extra mana of any type will be removed to match the colorless required.

spendMana "2RG"
Validates
  • Mana specification is valid.
  • Sufficient mana exists in pool.
Effects
  • Mana pool is reduced.

tap :: CardName -> GameMonad () Source #

Taps a card.

Validates
  • Card is in play.
  • Card is not tapped.
  • If creature, is not summoned or has haste.
Effects
  • Card gains tapped attribute.

untap :: CardName -> GameMonad () Source #

Untaps a card.

Validates
  • Card is in play.
  • Card is tapped.
Effects
  • Card loses tapped attribute.

validate :: CardMatcher -> CardName -> GameMonad () Source #

Validate that a card matches a matcher.

validate (matchAttribute "pirate") "Angrath's Marauders"
Validates
  • Card matches matcher.

validateRemoved :: CardName -> GameMonad () Source #

Validates that a card is no longer present in the game. Particularly helpful for checking destruction of tokens.

validateRemoved "Angel"
Validates
  • Name does not refer to a card.

validatePhase :: Phase -> GameMonad () Source #

Validates that the game is in a particular phase.

validatePhase BeginCombat
Validates
  • Game is in the given phase.

validateCanCastSorcery :: GameMonad () Source #

Validates that a sorcery is able to be cast.

Validates
  • Stack is empty.
  • In a main phase.

validateLife :: Int -> Player -> GameMonad () Source #

Validates a player has a specific life total.

validateLife 0 Opponent
Validates
  • Player life equals amount.

withStateBasedActions :: GameMonad a -> GameMonad a Source #

Pause running of state-based actions for the duration of the action, running them at the end.

runStateBasedActions :: GameMonad () Source #

Run state-based actions. These include:

  • If a creature does not have indestructible, and has damage exceeding toughess or deathtouched attribute, destroy it.
  • If a card is a token and is not in play, remove it.
  • If a card is a copy and is not on the stack, remove it.

These are run implicitly at the end of each step, so it's not usually needed to call this explicitly. Even then, using withStateBasedActions is usually preferred.

Running state-based actions can in turn trigger more state-based actions. This method loops until no more are generated, which has the potential for non-termination for pathological game states.

step :: String -> GameMonad a -> GameMonad a Source #

Define a high-level step in the proof. A proof typically consists on multiple steps. Each step is a human-readable description, then a definition of that step using actions. If a step fails, no subsequent steps will be run. runStateBasedActions is implicitly called at the end of each step. Nested step invocations execute the nested action but have no other effects - generally they should be avoided.

fork :: String -> GameMonad () -> GameMonad () Source #

Branch off a labeled alternate line. Steps inside the fork will be reported at the end of the main line output.

gainLife :: Int -> GameMonad () Source #

Increments life total for current actor.

as Opponent $ gainLife 1
Effects
  • Increases life total by amount

loseLife :: Int -> GameMonad () Source #

Decrements life total for current actor.

as Opponent $ loseLife 1
Effects
  • Decreases life total by amount

setLife :: Int -> GameMonad () Source #

Sets life total for current actor.

as Opponent $ setLife 1
Effects
  • Sets life total to amount

addEffect :: LayeredEffectPart -> CardName -> GameMonad () Source #

Adds an "until end of turn" effect to a card. Note in practice, since turns aren't modeled, the effect will stay around until the end of the solution.

addEffect (effectPTSet 1 1) "Soldier"
Effects
  • Adds a new "until end of turn" effect to the card with the current timestamp.

withEffect Source #

Arguments

:: EffectMonad CardMatcher

The set of cards to apply the effect to

-> [LayeredEffectPart]

The effect to apply

-> EffectName

Human-readable description, cosmetic only.

-> GameMonad () 
-> GameMonad () 

Add an effect to the created card. The effect will only apply when the card is in play.

effectPTSetF :: (Card -> EffectMonad (Int, Int)) -> LayeredEffectPart Source #

Layer 7B effect to set the power and toughness of a creature.

effectPTAdjustF :: (Card -> EffectMonad (Int, Int)) -> LayeredEffectPart Source #

Layer 7C effect to adjust the power and toughness of a creature.

effectAddAbility :: CardAttribute -> LayeredEffectPart Source #

Layer 6 effect to add an ability to a card. In practice, it adds adds a new CardAttribute.

effectNoAbilities :: LayeredEffectPart Source #

Layer 6 effect to remove all abilities from a card. This doesn't temporary abilities added by addEffect.

effectAddType :: CardAttribute -> LayeredEffectPart Source #

Layer 4 effect to add a type to a card. Since card types are modeled explicitly, it instead adds a new CardAttribute.

enabledInPlay :: EffectMonad Bool Source #

Effect enabled definition to apply when a card is in play.

askSelf :: EffectMonad Card Source #

The card that is generating the effect being applied.

viewSelf :: Getting b Card b -> ReaderT (Board, Card) Identity b Source #

Apply a lens to askSelf.

askCards :: CardMatcher -> EffectMonad [Card] Source #

Return cards fitting the given matcher.