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

Dovin.V2

Description

V2 makes the following changes from V1:

  • withLocation now only takes a Location, using the current actor for player.
  • Flips argument order for validate functions to be consistent with rest of API.
  • activate and trigger use the stack.
  • Fork has a saner API and reports properly.
  • formatter now takes a Step rather than an Int. view is re-exported since it will virtually always be required for normal formatters.
Synopsis

Documentation

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.

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.1-IFqEYjMDOrX6yiKW5Gzbyz" '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 #

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

withEffect Source #

Arguments

:: CardMatcher

A matcher that must apply to this card for this affect to apply. matchInPlay is a typical value.

-> (Card -> CardMatcher)

Given the current card, return a matcher that matches cards that this affect applies to.

-> (Card -> Identity Card)

Apply an effect to the given card.

-> GameMonad () 
-> GameMonad () 

Add an effect to the created card.