module Dovin.V1
  ( module Dovin.Runner
  , module Dovin.Actions
  , module Dovin.Attributes
  , module Dovin.Builder
  , module Dovin.Formatting
  , module Dovin.Helpers
  , module Dovin.Types
  , module Dovin.Matchers
  , validate
  , validateLife
  , withLocation
  , activate
  , trigger
  , fork
  , withEffect
  ) where

import Dovin.Runner
import Dovin.Actions hiding (validate, validateLife, activate, trigger, fork)
import qualified Dovin.Actions
import Dovin.Attributes
import Dovin.Builder hiding (withLocation, withEffect)
import Dovin.Formatting
import Dovin.Helpers
import Dovin.Types
import Dovin.Matchers
import Dovin.Effects (askSelf)

import Control.Monad (forM_)
import Control.Monad.State (put, get)
import Control.Monad.Reader (local)
import Control.Lens (set, view)
import Control.Monad.Identity (Identity, runIdentity)

-- | Validate that a card matches a matcher.
--
-- > validate "Angrath's Marauders" $ matchAttribute "pirate"
--
-- [Validates]
--
--   * Card matches matcher.
validate :: CardName -> CardMatcher -> GameMonad ()
validate :: CardName -> CardMatcher -> GameMonad ()
validate = (CardMatcher -> CardName -> GameMonad ())
-> CardName -> CardMatcher -> GameMonad ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip CardMatcher -> CardName -> GameMonad ()
Dovin.Actions.validate

-- | Validates a player has a specific life total.
--
-- > validateLife Opponent 0
--
-- [Validates]
--
--     * Player life equals amount.
validateLife :: Player -> Int -> GameMonad ()
validateLife :: Player -> Int -> GameMonad ()
validateLife = (Int -> Player -> GameMonad ()) -> Player -> Int -> GameMonad ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip Int -> Player -> GameMonad ()
Dovin.Actions.validateLife

-- | Set the location of the created card.
withLocation :: CardLocation -> GameMonad () -> GameMonad ()
withLocation :: CardLocation -> GameMonad () -> GameMonad ()
withLocation CardLocation
loc = (Env -> Env) -> GameMonad () -> GameMonad ()
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (ASetter Env Env CardLocation CardLocation
-> CardLocation -> Env -> Env
forall s t a b. ASetter s t a b -> b -> s -> t
set ((Card -> Identity Card) -> Env -> Identity Env
Lens' Env Card
envTemplate ((Card -> Identity Card) -> Env -> Identity Env)
-> ((CardLocation -> Identity CardLocation)
    -> Card -> Identity Card)
-> ASetter Env Env CardLocation CardLocation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CardLocation -> Identity CardLocation) -> Card -> Identity Card
Lens' Card CardLocation
cardLocation) CardLocation
loc)

activate :: CardName -> CardName -> GameMonad ()
activate CardName
mana CardName
targetName = do
  Card
card <- CardName -> CardMatcher -> GameMonad Card
requireCard CardName
targetName CardMatcher
forall a. Monoid a => a
mempty
  Player
actor <- Getting Player Env Player
-> ExceptT
     CardName
     (ReaderT Env (StateT Board (WriterT [Step] Identity)))
     Player
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Player Env Player
Lens' Env Player
envActor

  CardName -> CardMatcher -> GameMonad ()
validate CardName
targetName (CardMatcher -> GameMonad ()) -> CardMatcher -> GameMonad ()
forall a b. (a -> b) -> a -> b
$ Player -> CardMatcher
matchController Player
actor

  CardName -> GameMonad ()
spendMana CardName
mana

  () -> GameMonad ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

trigger :: CardName -> GameMonad ()
trigger CardName
targetName = do
  -- TODO: Technically some cards can trigger from other zones, figure out best
  -- way to represent.
  Card
card <- CardName -> CardMatcher -> GameMonad Card
requireCard CardName
targetName CardMatcher
matchInPlay

  () -> GameMonad ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

-- | Branch off to an alternate line.
fork :: [GameMonad ()] -> GameMonad ()
fork :: [GameMonad ()] -> GameMonad ()
fork [GameMonad ()]
options = do
  Board
b <- ExceptT
  CardName
  (ReaderT Env (StateT Board (WriterT [Step] Identity)))
  Board
forall s (m :: * -> *). MonadState s m => m s
get
  let cs :: (Maybe CardName, Int)
cs = Getting (Maybe CardName, Int) Board (Maybe CardName, Int)
-> Board -> (Maybe CardName, Int)
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Maybe CardName, Int) Board (Maybe CardName, Int)
Lens' Board (Maybe CardName, Int)
currentStep Board
b

  [GameMonad ()] -> (GameMonad () -> GameMonad ()) -> GameMonad ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [GameMonad ()]
options ((GameMonad () -> GameMonad ()) -> GameMonad ())
-> (GameMonad () -> GameMonad ()) -> GameMonad ()
forall a b. (a -> b) -> a -> b
$ \GameMonad ()
m -> do
    GameMonad ()
m
    Board -> GameMonad ()
forall s (m :: * -> *). MonadState s m => s -> m ()
put (Board -> GameMonad ()) -> Board -> GameMonad ()
forall a b. (a -> b) -> a -> b
$ ASetter Board Board (Maybe CardName, Int) (Maybe CardName, Int)
-> (Maybe CardName, Int) -> Board -> Board
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter Board Board (Maybe CardName, Int) (Maybe CardName, Int)
Lens' Board (Maybe CardName, Int)
currentStep (Maybe CardName, Int)
cs Board
b

-- | Add an effect to the created card.
withEffect ::
  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 ()
withEffect :: CardMatcher
-> (Card -> CardMatcher)
-> (Card -> Identity Card)
-> GameMonad ()
-> GameMonad ()
withEffect CardMatcher
applyCondition Card -> CardMatcher
matcher Card -> Identity Card
action = do
  let applyConditionV3 :: ReaderT EffectMonadEnv Identity Bool
applyConditionV3 = CardMatcher -> Card -> Bool
applyMatcher CardMatcher
applyCondition (Card -> Bool)
-> ReaderT EffectMonadEnv Identity Card
-> ReaderT EffectMonadEnv Identity Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT EffectMonadEnv Identity Card
askSelf
  let matcherV3 :: ReaderT EffectMonadEnv Identity CardMatcher
matcherV3 = Card -> CardMatcher
matcher (Card -> CardMatcher)
-> ReaderT EffectMonadEnv Identity Card
-> ReaderT EffectMonadEnv Identity CardMatcher
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT EffectMonadEnv Identity Card
askSelf
  let actionV3 :: [LayeredEffectPart]
actionV3 = [Layer
-> (Card -> ReaderT EffectMonadEnv Identity Card)
-> LayeredEffectPart
LayeredEffectPart Layer
LayerOther (Card -> ReaderT EffectMonadEnv Identity Card
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Card -> ReaderT EffectMonadEnv Identity Card)
-> (Card -> Card) -> Card -> ReaderT EffectMonadEnv Identity Card
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Identity Card -> Card
forall a. Identity a -> a
runIdentity (Identity Card -> Card) -> (Card -> Identity Card) -> Card -> Card
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Card -> Identity Card
action)]
  let name :: CardName
name = CardName
"legacy V2 effect"

  ReaderT EffectMonadEnv Identity Bool
-> ReaderT EffectMonadEnv Identity CardMatcher
-> [LayeredEffectPart]
-> CardName
-> GameMonad ()
-> GameMonad ()
withEffectWhen ReaderT EffectMonadEnv Identity Bool
applyConditionV3 ReaderT EffectMonadEnv Identity CardMatcher
matcherV3 [LayeredEffectPart]
actionV3 CardName
name