{-# Language QuasiQuotes #-}
module Main where
import Advent.Format (format)
import Advent.Search (astar, AStep(..))
main :: IO ()
IO ()
main =
do (Int
hp,Int
dmg) <- [format|2015 22 Hit Points: %u%nDamage: %u%n|]
Int -> IO ()
forall a. Show a => a -> IO ()
print (GameState -> Int
runSim (Int -> Int -> GameState
initialState Int
hp Int
dmg))
Int -> IO ()
forall a. Show a => a -> IO ()
print (GameState -> Int
runSim (Int -> Int -> GameState
initialState Int
hp Int
dmg) { difficulty = 1 })
runSim :: GameState -> Int
runSim :: GameState -> Int
runSim GameState
s = [Int] -> Int
forall a. HasCallStack => [a] -> a
head [Int
cost | (GameState
s1, Int
cost) <- (GameState -> [AStep GameState]) -> GameState -> [(GameState, Int)]
forall a. Ord a => (a -> [AStep a]) -> a -> [(a, Int)]
astar GameState -> [AStep GameState]
advance GameState
s, GameState -> Bool
bossDead GameState
s1]
data Spell = Recharge | Poison | Shield | Drain | MagicMissile
deriving Spell -> Spell -> Bool
(Spell -> Spell -> Bool) -> (Spell -> Spell -> Bool) -> Eq Spell
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Spell -> Spell -> Bool
== :: Spell -> Spell -> Bool
$c/= :: Spell -> Spell -> Bool
/= :: Spell -> Spell -> Bool
Eq
spellDamage :: Spell -> Int
spellDamage :: Spell -> Int
spellDamage Spell
spell =
case Spell
spell of
Spell
MagicMissile -> Int
4
Spell
Drain -> Int
2
Spell
_ -> Int
0
spellHeal :: Spell -> Int
spellHeal :: Spell -> Int
spellHeal Spell
spell =
case Spell
spell of
Spell
Drain -> Int
2
Spell
_ -> Int
0
spellCost :: Spell -> Int
spellCost :: Spell -> Int
spellCost Spell
s =
case Spell
s of
Spell
Recharge -> Int
229
Spell
Poison -> Int
173
Spell
Shield -> Int
113
Spell
Drain -> Int
73
Spell
MagicMissile -> Int
53
data GameState = GameState
{ GameState -> Int
manaPool
, GameState -> Int
poisonTimer
, GameState -> Int
rechargeTimer
, GameState -> Int
shieldTimer
, GameState -> Int
playerHp
, GameState -> Int
bossHp, GameState -> Int
bossDamage, GameState -> Int
difficulty :: !Int
}
deriving (GameState -> GameState -> Bool
(GameState -> GameState -> Bool)
-> (GameState -> GameState -> Bool) -> Eq GameState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GameState -> GameState -> Bool
== :: GameState -> GameState -> Bool
$c/= :: GameState -> GameState -> Bool
/= :: GameState -> GameState -> Bool
Eq, Eq GameState
Eq GameState =>
(GameState -> GameState -> Ordering)
-> (GameState -> GameState -> Bool)
-> (GameState -> GameState -> Bool)
-> (GameState -> GameState -> Bool)
-> (GameState -> GameState -> Bool)
-> (GameState -> GameState -> GameState)
-> (GameState -> GameState -> GameState)
-> Ord GameState
GameState -> GameState -> Bool
GameState -> GameState -> Ordering
GameState -> GameState -> GameState
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: GameState -> GameState -> Ordering
compare :: GameState -> GameState -> Ordering
$c< :: GameState -> GameState -> Bool
< :: GameState -> GameState -> Bool
$c<= :: GameState -> GameState -> Bool
<= :: GameState -> GameState -> Bool
$c> :: GameState -> GameState -> Bool
> :: GameState -> GameState -> Bool
$c>= :: GameState -> GameState -> Bool
>= :: GameState -> GameState -> Bool
$cmax :: GameState -> GameState -> GameState
max :: GameState -> GameState -> GameState
$cmin :: GameState -> GameState -> GameState
min :: GameState -> GameState -> GameState
Ord, Int -> GameState -> ShowS
[GameState] -> ShowS
GameState -> String
(Int -> GameState -> ShowS)
-> (GameState -> String)
-> ([GameState] -> ShowS)
-> Show GameState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GameState -> ShowS
showsPrec :: Int -> GameState -> ShowS
$cshow :: GameState -> String
show :: GameState -> String
$cshowList :: [GameState] -> ShowS
showList :: [GameState] -> ShowS
Show)
initialState :: Int -> Int -> GameState
initialState :: Int -> Int -> GameState
initialState Int
hp Int
dmg = GameState
{ manaPool :: Int
manaPool = Int
500
, poisonTimer :: Int
poisonTimer = Int
0
, rechargeTimer :: Int
rechargeTimer = Int
0
, shieldTimer :: Int
shieldTimer = Int
0
, playerHp :: Int
playerHp = Int
50
, bossHp :: Int
bossHp = Int
hp
, bossDamage :: Int
bossDamage = Int
dmg
, difficulty :: Int
difficulty = Int
0
}
stepTimers :: GameState -> GameState
stepTimers :: GameState -> GameState
stepTimers GameState
s = GameState
s
{ manaPool = manaPool s +
if rechargeTimer s > 0 then 101 else 0
, bossHp = bossHp s -
if poisonTimer s > 0 then 3 else 0
, poisonTimer = dec (poisonTimer s)
, rechargeTimer = dec (rechargeTimer s)
, shieldTimer = dec (shieldTimer s)
}
bossAttack :: GameState -> GameState
bossAttack :: GameState -> GameState
bossAttack GameState
s = GameState
s { playerHp = playerHp s - effectiveAttack }
where
effectiveAttack :: Int
effectiveAttack = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
1 (GameState -> Int
bossDamage GameState
s Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
armor)
armor :: Int
armor | GameState -> Int
shieldTimer GameState
s Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 = Int
7
| Bool
otherwise = Int
0
applyDifficulty :: GameState -> GameState
applyDifficulty :: GameState -> GameState
applyDifficulty GameState
s = GameState
s { playerHp = playerHp s - difficulty s }
advance :: GameState -> [AStep GameState]
advance :: GameState -> [AStep GameState]
advance GameState
s =
[ GameState -> Int -> Int -> AStep GameState
forall a. a -> Int -> Int -> AStep a
AStep GameState
s5 (Spell -> Int
spellCost Spell
spell) Int
0
| GameState
s1 <- GameState
s GameState -> (GameState -> GameState) -> [GameState]
--> GameState -> GameState
stepTimers (GameState -> GameState)
-> (GameState -> GameState) -> GameState -> GameState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GameState -> GameState
applyDifficulty
, Spell
spell <- GameState -> [Spell]
availableSpells GameState
s1
, GameState
s2 <- GameState
s1 GameState -> (GameState -> GameState) -> [GameState]
--> Spell -> GameState -> GameState
applySpell Spell
spell
, GameState
s3 <- GameState
s2 GameState -> (GameState -> GameState) -> [GameState]
--> GameState -> GameState
stepTimers
, GameState
s4 <- GameState
s3 GameState -> (GameState -> GameState) -> [GameState]
--> GameState -> GameState
bossAttack
, GameState
s5 <- GameState
s4 GameState -> (GameState -> GameState) -> [GameState]
--> GameState -> GameState
forall a. a -> a
id
]
infix 1 -->
(-->) :: GameState -> (GameState -> GameState) -> [GameState]
GameState
s --> :: GameState -> (GameState -> GameState) -> [GameState]
--> GameState -> GameState
k
| GameState -> Bool
playerDead GameState
s = []
| GameState -> Bool
bossDead GameState
s = [GameState
s]
| Bool
otherwise = [GameState -> GameState
k GameState
s]
applySpell :: Spell -> GameState -> GameState
applySpell :: Spell -> GameState -> GameState
applySpell Spell
spell GameState
s =
GameState
s { manaPool = manaPool s - spellCost spell
, rechargeTimer = if spell == Recharge then 5 else rechargeTimer s
, poisonTimer = if spell == Poison then 6 else poisonTimer s
, shieldTimer = if spell == Shield then 6 else shieldTimer s
, bossHp = bossHp s - spellDamage spell
, playerHp = playerHp s + spellHeal spell
}
availableSpells :: GameState -> [Spell]
availableSpells :: GameState -> [Spell]
availableSpells GameState
s =
(Spell -> Bool) -> [Spell] -> [Spell]
forall a. (a -> Bool) -> [a] -> [a]
filter (\Spell
spell -> Spell -> Int
spellCost Spell
spell Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= GameState -> Int
manaPool GameState
s)
([Spell] -> [Spell]) -> [Spell] -> [Spell]
forall a b. (a -> b) -> a -> b
$ [Spell
Poison | GameState -> Int
poisonTimer GameState
s Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0]
[Spell] -> [Spell] -> [Spell]
forall a. [a] -> [a] -> [a]
++ [Spell
Recharge | GameState -> Int
rechargeTimer GameState
s Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0]
[Spell] -> [Spell] -> [Spell]
forall a. [a] -> [a] -> [a]
++ [Spell
Shield | GameState -> Int
shieldTimer GameState
s Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0]
[Spell] -> [Spell] -> [Spell]
forall a. [a] -> [a] -> [a]
++ [Spell
MagicMissile, Spell
Drain]
dec :: Int -> Int
dec :: Int -> Int
dec Int
x | Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
1 = Int
0
dec Int
x = Int
xInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1
bossDead :: GameState -> Bool
bossDead :: GameState -> Bool
bossDead GameState
s = GameState -> Int
bossHp GameState
s Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0
playerDead :: GameState -> Bool
playerDead :: GameState -> Bool
playerDead GameState
s = GameState -> Int
playerHp GameState
s Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0