-- | Definitions of game mode kinds.
module Content.ModeKind
  ( -- * Group name patterns
    groupNamesSingleton, groupNames
  , -- * Content
    content
#ifdef EXPOSE_INTERNAL
  -- * Group name patterns
  , pattern RAID, pattern BRAWL, pattern LONG, pattern CRAWL, pattern FOGGY, pattern SHOOTOUT, pattern PERILOUS, pattern HUNT, pattern NIGHT, pattern FLIGHT, pattern BURNING, pattern ZOO, pattern RANGED, pattern AMBUSH, pattern SAFARI, pattern DIG, pattern SEE, pattern SHORT, pattern CRAWL_EMPTY, pattern CRAWL_SURVIVAL, pattern SAFARI_SURVIVAL, pattern BATTLE, pattern BATTLE_DEFENSE, pattern BATTLE_SURVIVAL, pattern DEFENSE, pattern DEFENSE_EMPTY
#endif
  ) where

import Prelude ()

import Game.LambdaHack.Core.Prelude

import qualified Data.Text as T

import Game.LambdaHack.Content.CaveKind (CaveKind, pattern DEFAULT_RANDOM)
import Game.LambdaHack.Content.FactionKind (Outcome (..))
import Game.LambdaHack.Content.ModeKind
import Game.LambdaHack.Core.Dice
import Game.LambdaHack.Definition.Defs
import Game.LambdaHack.Definition.DefsInternal

import Content.CaveKind hiding (content, groupNames, groupNamesSingleton)
import Content.FactionKind hiding (content, groupNames, groupNamesSingleton)
import Content.ItemKindActor

-- * Group name patterns

groupNamesSingleton :: [GroupName ModeKind]
groupNamesSingleton :: [GroupName ModeKind]
groupNamesSingleton =
       [GroupName ModeKind
RAID, GroupName ModeKind
BRAWL, GroupName ModeKind
LONG, GroupName ModeKind
CRAWL, GroupName ModeKind
FOGGY, GroupName ModeKind
SHOOTOUT, GroupName ModeKind
PERILOUS, GroupName ModeKind
HUNT, GroupName ModeKind
NIGHT, GroupName ModeKind
FLIGHT, GroupName ModeKind
BURNING, GroupName ModeKind
ZOO, GroupName ModeKind
RANGED, GroupName ModeKind
AMBUSH, GroupName ModeKind
SAFARI, GroupName ModeKind
DIG, GroupName ModeKind
SEE, GroupName ModeKind
SHORT, GroupName ModeKind
CRAWL_EMPTY, GroupName ModeKind
CRAWL_SURVIVAL, GroupName ModeKind
SAFARI_SURVIVAL, GroupName ModeKind
BATTLE, GroupName ModeKind
BATTLE_DEFENSE, GroupName ModeKind
BATTLE_SURVIVAL, GroupName ModeKind
DEFENSE, GroupName ModeKind
DEFENSE_EMPTY]

pattern RAID, BRAWL, LONG, CRAWL, FOGGY, SHOOTOUT, PERILOUS, HUNT, NIGHT, FLIGHT, BURNING, ZOO, RANGED, AMBUSH, SAFARI, DIG, SEE, SHORT, CRAWL_EMPTY, CRAWL_SURVIVAL, SAFARI_SURVIVAL, BATTLE, BATTLE_DEFENSE, BATTLE_SURVIVAL, DEFENSE, DEFENSE_EMPTY :: GroupName ModeKind

groupNames :: [GroupName ModeKind]
groupNames :: [GroupName ModeKind]
groupNames = []

pattern $mRAID :: forall {r}. GroupName ModeKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bRAID :: GroupName ModeKind
RAID = GroupName "raid"
pattern $mBRAWL :: forall {r}. GroupName ModeKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bBRAWL :: GroupName ModeKind
BRAWL = GroupName "brawl"
pattern $mLONG :: forall {r}. GroupName ModeKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bLONG :: GroupName ModeKind
LONG = GroupName "long crawl"
pattern $mCRAWL :: forall {r}. GroupName ModeKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bCRAWL :: GroupName ModeKind
CRAWL = GroupName "crawl"
pattern $mFOGGY :: forall {r}. GroupName ModeKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bFOGGY :: GroupName ModeKind
FOGGY = GroupName "foggy shootout"
pattern $mSHOOTOUT :: forall {r}. GroupName ModeKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bSHOOTOUT :: GroupName ModeKind
SHOOTOUT = GroupName "shootout"
pattern $mPERILOUS :: forall {r}. GroupName ModeKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bPERILOUS :: GroupName ModeKind
PERILOUS = GroupName "perilous hunt"
pattern $mHUNT :: forall {r}. GroupName ModeKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bHUNT :: GroupName ModeKind
HUNT = GroupName "hunt"
pattern $mNIGHT :: forall {r}. GroupName ModeKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bNIGHT :: GroupName ModeKind
NIGHT = GroupName "night flight"
pattern $mFLIGHT :: forall {r}. GroupName ModeKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bFLIGHT :: GroupName ModeKind
FLIGHT = GroupName "flight"
pattern $mBURNING :: forall {r}. GroupName ModeKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bBURNING :: GroupName ModeKind
BURNING = GroupName "burning zoo"
pattern $mZOO :: forall {r}. GroupName ModeKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bZOO :: GroupName ModeKind
ZOO = GroupName "zoo"
pattern $mRANGED :: forall {r}. GroupName ModeKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bRANGED :: GroupName ModeKind
RANGED = GroupName "ranged ambush"
pattern $mAMBUSH :: forall {r}. GroupName ModeKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bAMBUSH :: GroupName ModeKind
AMBUSH = GroupName "ambush"
pattern $mSAFARI :: forall {r}. GroupName ModeKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bSAFARI :: GroupName ModeKind
SAFARI = GroupName "safari"
pattern $mDIG :: forall {r}. GroupName ModeKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bDIG :: GroupName ModeKind
DIG = GroupName "dig"
pattern $mSEE :: forall {r}. GroupName ModeKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bSEE :: GroupName ModeKind
SEE = GroupName "see"
pattern $mSHORT :: forall {r}. GroupName ModeKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bSHORT :: GroupName ModeKind
SHORT = GroupName "short"
pattern $mCRAWL_EMPTY :: forall {r}. GroupName ModeKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bCRAWL_EMPTY :: GroupName ModeKind
CRAWL_EMPTY = GroupName "crawlEmpty"  -- only the first word matters
pattern $mCRAWL_SURVIVAL :: forall {r}. GroupName ModeKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bCRAWL_SURVIVAL :: GroupName ModeKind
CRAWL_SURVIVAL = GroupName "crawlSurvival"
pattern $mSAFARI_SURVIVAL :: forall {r}. GroupName ModeKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bSAFARI_SURVIVAL :: GroupName ModeKind
SAFARI_SURVIVAL = GroupName "safariSurvival"
pattern $mBATTLE :: forall {r}. GroupName ModeKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bBATTLE :: GroupName ModeKind
BATTLE = GroupName "battle"
pattern $mBATTLE_DEFENSE :: forall {r}. GroupName ModeKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bBATTLE_DEFENSE :: GroupName ModeKind
BATTLE_DEFENSE = GroupName "battleDefense"
pattern $mBATTLE_SURVIVAL :: forall {r}. GroupName ModeKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bBATTLE_SURVIVAL :: GroupName ModeKind
BATTLE_SURVIVAL = GroupName "battleSurvival"
pattern $mDEFENSE :: forall {r}. GroupName ModeKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bDEFENSE :: GroupName ModeKind
DEFENSE = GroupName "defense"
pattern $mDEFENSE_EMPTY :: forall {r}. GroupName ModeKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bDEFENSE_EMPTY :: GroupName ModeKind
DEFENSE_EMPTY = GroupName "defenseEmpty"

-- * Content

content :: [ModeKind]
content :: [ModeKind]
content =
  [ModeKind
raid, ModeKind
brawl, ModeKind
crawl, ModeKind
shootout, ModeKind
hunt, ModeKind
flight, ModeKind
zoo, ModeKind
ambush, ModeKind
safari, ModeKind
dig, ModeKind
see, ModeKind
short, ModeKind
crawlEmpty, ModeKind
crawlSurvival, ModeKind
safariSurvival, ModeKind
battle, ModeKind
battleDefense, ModeKind
battleSurvival, ModeKind
defense, ModeKind
defenseEmpty, ModeKind
screensaverRaid, ModeKind
screensaverBrawl, ModeKind
screensaverCrawl, ModeKind
screensaverShootout, ModeKind
screensaverHunt, ModeKind
screensaverFlight, ModeKind
screensaverZoo, ModeKind
screensaverAmbush, ModeKind
screensaverSafari]

raid,    brawl, crawl, shootout, hunt, flight, zoo, ambush, safari, dig, see, short, crawlEmpty, crawlSurvival, safariSurvival, battle, battleDefense, battleSurvival, defense, defenseEmpty, screensaverRaid, screensaverBrawl, screensaverCrawl, screensaverShootout, screensaverHunt, screensaverFlight, screensaverZoo, screensaverAmbush, screensaverSafari :: ModeKind

-- What other symmetric (two only-one-moves factions) and asymmetric vs crowd
-- scenarios make sense (e.g., are good for a tutorial or for standalone
-- extreme fun or are impossible as part of a crawl)?
-- sparse melee at night: no, shade ambush in brawl is enough
-- dense melee: no, keeping big party together is a chore and big enemy
--   party is less fun than huge enemy party
-- crowd melee in daylight: no, possible in crawl and at night is more fun
-- sparse ranged at night: no, less fun than dense and if no reaction fire,
--   just a camp fest or firing blindly
-- dense ranged in daylight: no, less fun than at night with flares
-- crowd ranged: no, fish in a barrel, less predictable and more fun inside
--   crawl, even without reaction fire

raid :: ModeKind
raid = ModeKind
  { mname :: Text
mname   = Text
"raid (tutorial, 1)"
  , mfreq :: Freqs ModeKind
mfreq   = [(GroupName ModeKind
RAID, Int
1), (GroupName ModeKind
CAMPAIGN_SCENARIO, Int
1)]
  , mtutorial :: Bool
mtutorial = Bool
True
  , mattract :: Bool
mattract = Bool
False
  , mroster :: Roster
mroster = Roster
rosterRaid
  , mcaves :: Caves
mcaves  = Caves
cavesRaid
  , mendMsg :: [(Outcome, Text)]
mendMsg = [ (Outcome
Killed, Text
"This expedition has gone wrong. However, scientific mind does not despair, but analyzes and corrects. Did you perchance awake one animal too many? Did you remember to try using all consumables at your disposal for your immediate survival? Did you choose a challenge with difficulty level within your means? Answer honestly, ponder wisely, experiment methodically.")
              , (Outcome
Defeated, Text
"Regrettably, the other team snatched the grant, while you were busy contemplating natural phenomena. Science is a competitive sport, as sad as it sounds. It's not enough to make a discovery, you have to get there first.")
              , (Outcome
Escape, Text
"You've got hold of the machine! Think of the hours of fun taking it apart and putting it back together again! That's a great first step on your quest to solve the typing problems of the world.") ]
  , mrules :: Text
mrules  = Text -> [Text] -> Text
T.intercalate Text
"\n"
      [ Text
"* One level only"
      , Text
"* Two heroes vs. Spawned enemies"
      , Text
"* Gather gold"
      , Text
"* Find a way out and escape ASAP"
      ]
  , mdesc :: Text
mdesc   = Text
"An incredibly advanced typing machine worth 100 gold is buried at the exit of this maze. Be the first to find it and fund a research team that makes typing accurate and dependable forever."
  , mreason :: Text
mreason = Text
"In addition to initiating the (loose) game plot, this adventure provides an introductory tutorial. Relax, explore, gather loot, find the way out and escape. With some luck, you won't even need to fight anything."
  , mhint :: Text
mhint   = Text
"You can't use gathered items in your next encounters, so trigger any consumables at will. Feel free to scout with only one of the heroes and keep the other one immobile, e.g., standing guard over the squad's shared inventory stash. If in grave danger, retreat with the scout to join forces with the guard. The more gold collected and the faster the victory, the higher your score in this encounter."
  }

brawl :: ModeKind
brawl = ModeKind  -- sparse melee in daylight, with shade for melee ambush
  { mname :: Text
mname   = Text
"brawl (tutorial, 2)"
  , mfreq :: Freqs ModeKind
mfreq   = [(GroupName ModeKind
BRAWL, Int
1), (GroupName ModeKind
CAMPAIGN_SCENARIO, Int
1)]
  , mtutorial :: Bool
mtutorial = Bool
True
  , mattract :: Bool
mattract = Bool
False
  , mroster :: Roster
mroster = Roster
rosterBrawl
  , mcaves :: Caves
mcaves  = Caves
cavesBrawl
  , mendMsg :: [(Outcome, Text)]
mendMsg = [ (Outcome
Killed, Text
"The inquisitive scholars turned out to be envious of our deep insight to the point of outright violence. It would still not result in such a defeat and recanting of our thesis if we figured out to use terrain to protect us from missiles or even completely hide our presence. It would also help if we honourably kept our ground together to the end, at the same time preventing the overwhelming enemy forces from brutishly ganging up on our modest-sized, though valiant, research team.")
              , (Outcome
Conquer, Text
"That's settled: local compactness *is* necessary for relative completeness, given the assumptions.") ]
  , mrules :: Text
mrules  = Text -> [Text] -> Text
T.intercalate Text
"\n"
      [ Text
"* One level only"
      , Text
"* Three heroes vs. Three human enemies"
      , Text
"* Minimize losses"
      , Text
"* Incapacitate all enemies ASAP"
      ]
  , mdesc :: Text
mdesc   = Text
"Your research team disagrees over a drink with some gentlemen scientists about premises of a relative completeness theorem and there's only one way to settle that."
      -- Not enough space with square fonts and also this is more of a hint than a flavour: Remember to keep your party together when opponents are spotted, or they might be tempted to silence solitary disputants one by one and so win the altercation.
  , mreason :: Text
mreason = Text
"In addition to advancing game plot, this encounter trains melee, squad formation and stealth. The battle is symmetric in goals (incapacitate all enemies) and in squad capabilities (only the pointman moves, others either melee or wait)."
  , mhint :: Text
mhint   =  Text -> [Text] -> Text
T.intercalate Text
"\n"
    [ Text
"Run a short distance with Shift or LMB, switch the pointman with Tab, repeat. In open terrain, if you keep distance between teammates, this resembles the leap frog infantry tactics. For best effects, end each sprint behind a cover or concealment."
    , Text
"Observe and mimic the enemies. If you can't see an enemy that apparently can see you, in reversed circumstances you would have the same advantage. Savour the relative fairness --- you won't find any in the main crawl adventure that follows."
    , Text
"If you get beaten repeatedly, try using all consumables you find. Ponder the hints from the defeat message, in particular the one about keeping your party together once the opponents are spotted. However, if you want to discover a winning tactics on your own, make sure to ignore any such tips until you succeed."
    ]
  }

crawl :: ModeKind
crawl = ModeKind
  { mname :: Text
mname   = Text
"long crawl (main)"
  , mfreq :: Freqs ModeKind
mfreq   = [(GroupName ModeKind
LONG, Int
1), (GroupName ModeKind
CRAWL, Int
1), (GroupName ModeKind
CAMPAIGN_SCENARIO, Int
1)]
  , mtutorial :: Bool
mtutorial = Bool
False
  , mattract :: Bool
mattract = Bool
False
  , mroster :: Roster
mroster = Roster
rosterCrawl
  , mcaves :: Caves
mcaves  = Caves
cavesCrawl
  , mendMsg :: [(Outcome, Text)]
mendMsg = [ (Outcome
Killed, Text
killedMsg)
              , (Outcome
Escape, Text
"It's better to live to tell the tale than to choke on more than one can swallow. There was no more exquisite cultural artifacts and glorious scientific wonders in these forbidding tunnels anyway. Or were there?") ]
  , mrules :: Text
mrules  = Text -> [Text] -> Text
T.intercalate Text
"\n"
      [ Text
"* Many levels"
      , Text
"* Three heroes vs. Spawned enemies"
      , Text
"* Gather gold, gems and elixirs"
      , Text
"* Find a way out and escape ASAP"
      ]
  , mdesc :: Text
mdesc   = Text
"Enjoy the peaceful seclusion of these cold austere tunnels, but don't let wanton curiosity, greed and the ever-creeping abstraction madness keep you down there for too long. If you find survivors (whole or perturbed or segmented) of the past scientific missions, exercise extreme caution and engage or ignore at your discretion."
  , mreason :: Text
mreason = Text
"This is the main, longest and most replayable scenario of the game. It's crucial that you gather the most interesting cultural artifacts such as gold, gems and elixirs. Equally importantly, you have to limit the permanent sanity deterioration of your scientific expedition members by minimizing the time they are exposed to the horrors of the underworld."
  , mhint :: Text
mhint   = Text
"If you keep dying, attempt the subsequent adventures as a breather (perhaps at lowered difficulty). They fill the gaps in the plot and teach particular skills that may come in handy and help you discover new tactics of your own or come up with a strategy for staving off the attrition. Also experimenting with the initial adventures may answer some questions you didn't have when you attempted them originally."
  }
 where
   killedMsg :: Text
killedMsg = Text -> [Text] -> Text
T.intercalate Text
"\n"
     [ Text
"To think that followers of science and agents of enlightenment would earn death as their reward! Where did we err in our ways? Perhaps nature should not have been disturbed so brashly and the fell beasts woken up from their slumber so eagerly?"
     , Text
"Perhaps the gathered items should have been used for scientific experiments on the spot rather than hoarded as if of base covetousness? Or perhaps the challenge, chosen freely but without the foreknowledge of the grisly difficulty, was insurmountable and forlorn from the start, despite the enormous power of educated reason at out disposal?"
     ]

-- The trajectory tip is important because of tactics of scout looking from
-- behind a bush and others hiding in mist. If no suitable bushes,
-- fire once and flee into mist or behind cover. Then whomever is out of LOS
-- range or inside mist can shoot at the last seen enemy locations,
-- adjusting aim according to sounds and incoming missile trajectories.
-- If the scout can't find bushes or glass building to set a lookout,
-- the other team members are more spotters and guardians than snipers
-- and that's their only role, so a small party makes sense.
shootout :: ModeKind
shootout = ModeKind  -- sparse ranged in daylight
  { mname :: Text
mname   = Text
"foggy shootout (3)"
  , mfreq :: Freqs ModeKind
mfreq   = [(GroupName ModeKind
FOGGY, Int
1), (GroupName ModeKind
SHOOTOUT, Int
1), (GroupName ModeKind
CAMPAIGN_SCENARIO, Int
1)]
  , mtutorial :: Bool
mtutorial = Bool
False
  , mattract :: Bool
mattract = Bool
False
  , mroster :: Roster
mroster = Roster
rosterShootout
  , mcaves :: Caves
mcaves  = Caves
cavesShootout
  , mendMsg :: [(Outcome, Text)]
mendMsg = [ (Outcome
Killed, Text
killedMsg)
              , (Outcome
Conquer, Text
"That was a good fight, with scientifically accurate application of missiles, cover and concealment. Not even skilled logicians can routinely deduce enemy position from the physical trajectory of their projectiles nor by firing without line of sight and interpreting auditory cues. However, while this steep hurdle is overcome, the dispute is not over yet.") ]
  , mrules :: Text
mrules  = Text -> [Text] -> Text
T.intercalate Text
"\n"
      [ Text
"* One level only"
      , Text
"* Three heroes vs. Three human enemies"
      , Text
"* Minimize losses"
      , Text
"* Incapacitate all enemies ASAP"
      ]
  , mdesc :: Text
mdesc   = Text
"Whose arguments are most striking and whose ideas fly fastest? Let's scatter up, attack the problems from different angles and find out."
  , mreason :: Text
mreason = Text
"This adventure teaches the ranged combat skill in the simplified setup of fully symmetric battle."
  , mhint :: Text
mhint   = Text
"Try to come up with the best squad formation for this tactical challenge. Don't despair if you run out of ammo, because if you aim truly, enemy has few hit points left at this point. In turn, when trying to avoid enemy projectiles, you can display the trajectory of any soaring entity by pointing it with the crosshair in aiming mode."
  }
 where
   killedMsg :: Text
killedMsg = Text -> [Text] -> Text
T.intercalate Text
"\n"
     [ Text
"This is a disgrace. What have we missed in our theoretic models of this fight? Did we miss a human lookout placed in a covered but unobstructed spot that lets the rest of the squad snipe from concealment or from a safe distance?"
     , Text
"Barring that, would we end up in a better shape even if we all hid and only fired blindly? We'd listen to impact sounds and wait vigilantly for incoming enemy missiles in order to register their trajectories and derive hints of enemy location. Apparently, ranged combat requires a change of pace and better planning than our previous simple but efficient calculations accustomed us to."
     ]

hunt :: ModeKind
hunt = ModeKind  -- melee vs ranged with reaction fire in daylight
  { mname :: Text
mname   = Text
"perilous hunt (4)"
  , mfreq :: Freqs ModeKind
mfreq   = [(GroupName ModeKind
PERILOUS, Int
1), (GroupName ModeKind
HUNT, Int
1), (GroupName ModeKind
CAMPAIGN_SCENARIO, Int
1)]
  , mtutorial :: Bool
mtutorial = Bool
False
  , mattract :: Bool
mattract = Bool
False
  , mroster :: Roster
mroster = Roster
rosterHunt
  , mcaves :: Caves
mcaves  = Caves
cavesHunt
  , mendMsg :: [(Outcome, Text)]
mendMsg = [ (Outcome
Killed, Text
"Leaving concealment might have not been rational enough, leaving cover is hard to justify on a scientific basis and wandering off on an area of a heated dispute is foolhardy. All this is doubly regrettable, given that our cold-hearted opponents supported their weak arguments with inexplicably effective telegraphy and triangulation equipment. And we so deserve a complete intellectual victory, if only we strove to lower the difficulty of this altercation instead of raising it.")
      -- this is in the middle of the scenario list and the mission is not tricky, so a subtle reminder about lowering difficulty, in case the player struggles
              , (Outcome
Conquer, Text
"We chased them off and proved our argument, like we knew that we would. It feels efficient to stick together and prevail. We taught them a lesson in rationality, despite their superior scientific equipment. Scientific truth prevails over brute force.") ]
  , mrules :: Text
mrules  = Text -> [Text] -> Text
T.intercalate Text
"\n"
      [ Text
"* One level only"
      , Text
"* Seven heroes vs. Seven human enemies capable of concurrent attacks"
      , Text
"* Minimize losses"
      , Text
"* Incapacitate all human enemies ASAP"
      ]
  , mdesc :: Text
mdesc   = Text
"Who is the hunter and who is the prey? The only criterion is last man standing when the chase for truth ends."
  , mreason :: Text
mreason = Text
"This adventure is quite a tactical challenge, because enemies are allowed to fling their ammo simultaneously at your team, which has no such ability."
  , mhint :: Text
mhint   = Text
"Try not to outshoot the enemy, but to instead focus more on melee tactics. A useful concept here is communication overhead. Any team member that is not waiting and spotting for everybody, but acts, e.g., melees or moves or manages items, slows down all other team members by roughly 10%, because they need to keep track of his actions. Therefore, if other heroes melee, consider carefully if it makes sense to come to their aid, slowing them while you move, or if it's better to stay put and monitor the perimeter. This is true for all factions and all actors on each level separately, except the pointman of each faction, if it has one."  -- this also eliminates lag in big battles and helps the player to focus on combat and not get distracted by distant team members frantically trying to reach the battleground in time
  }

flight :: ModeKind
flight = ModeKind  -- asymmetric ranged and stealth race at night
  { mname :: Text
mname   = Text
"night flight (5)"
  , mfreq :: Freqs ModeKind
mfreq   = [(GroupName ModeKind
NIGHT, Int
1), (GroupName ModeKind
FLIGHT, Int
1), (GroupName ModeKind
CAMPAIGN_SCENARIO, Int
1)]
  , mtutorial :: Bool
mtutorial = Bool
False
  , mattract :: Bool
mattract = Bool
False
  , mroster :: Roster
mroster = Roster
rosterFlight
  , mcaves :: Caves
mcaves  = Caves
cavesFlight
  , mendMsg :: [(Outcome, Text)]
mendMsg = [ (Outcome
Killed, Text
killedMsg)
              , (Outcome
Conquer, Text
"It was enough to reach the escape area marked by yellow '>' symbol. Spilling that much blood was risky. unnecessary and alerted the authorities. Having said that --- impressive indeed.") ]
  , mrules :: Text
mrules  = Text -> [Text] -> Text
T.intercalate Text
"\n"
      [ Text
"* One level only"
      , Text
"* Three heroes vs. Seven human enemies capable of concurrent attacks"
      , Text
"* Minimize losses"
      , Text
"* Gather gems"
      , Text
"* Find a way out and escape ASAP"
      ]
  , mdesc :: Text
mdesc   = Text
"Dwelling into dark matters is dangerous, so avoid the crowd of firebrand disputants, catch any gems of thought, find a way out and bring back a larger team to shed new light on the field."
  , mreason :: Text
mreason = Text
"The focus of this installment is on stealthy exploration under the threat of numerically superior enemy."
  , mhint :: Text
mhint   = Text
""
  }
 where
   killedMsg :: Text
killedMsg = Text -> [Text] -> Text
T.intercalate Text
"\n"
     [ Text
"Somebody must have tipped the enemies of free inquiry off. However, us walking along a lit trail, yelling, could have been a contributing factor. Also, it's worth noting that the torches prepared for this assault are best used as thrown makeshift flares."
     , Text
"On the other hand, equipping a lit torch makes one visible in the dark, regrettably but not quite unexpectedly to a scientific mind. Lastly, the goal of this foray was to definitely disengage from the fruitless dispute, via a way out marked by a yellow '>' sign, and to gather treasure that would support our future research. Not to harass every nearby scientific truth denier, as much as they do deserve it."
     ]

zoo :: ModeKind
zoo = ModeKind  -- asymmetric crowd melee at night
  { mname :: Text
mname   = Text
"burning zoo (6)"
  , mfreq :: Freqs ModeKind
mfreq   = [(GroupName ModeKind
BURNING, Int
1), (GroupName ModeKind
ZOO, Int
1), (GroupName ModeKind
CAMPAIGN_SCENARIO, Int
1)]
  , mtutorial :: Bool
mtutorial = Bool
False
  , mattract :: Bool
mattract = Bool
False
  , mroster :: Roster
mroster = Roster
rosterZoo
  , mcaves :: Caves
mcaves  = Caves
cavesZoo
  , mendMsg :: [(Outcome, Text)]
mendMsg = [ (Outcome
Killed, Text
"Against such an onslaught, only clever positioning, use of terrain and patient vigilance gives any chance of survival.")
              , (Outcome
Conquer, Text
"That was a grim harvest. Science demands sacrifices.") ]
  , mrules :: Text
mrules  = Text -> [Text] -> Text
T.intercalate Text
"\n"
      [ Text
"* One level only"
      , Text
"* Five heroes vs. Many enemies"
      , Text
"* Minimize losses"
      , Text
"* Incapacitate all enemies ASAP"
      ]
  , mdesc :: Text
mdesc   = Text
"The heat of the dispute reaches the nearby Wonders of Science and Nature exhibition, igniting greenery, nets and cages. Crazed animals must be dissuaded from ruining precious scientific equipment and setting back the otherwise fruitful exchange of ideas."
  , mreason :: Text
mreason = Text
"This is a crowd control exercise, at night, with a raging fire."
  , mhint :: Text
mhint   = Text
"Note that communication overhead, as explained in perilous hunt adventure hints, makes it impossible for any faction to hit your heroes by more than 10 normal speed actors each turn. However, this is still too much, so position is everything."
  }

-- The tactic is to sneak in the dark, highlight enemy with thrown torches
-- (and douse thrown enemy torches with blankets) and only if this fails,
-- actually scout using extended noctovision.
-- With reaction fire, larger team is more fun.
--
-- For now, while we have no shooters with timeout, massive ranged battles
-- without reaction fire don't make sense, because then usually only one hero
-- shoots (and often also scouts) and others just gather ammo.
ambush :: ModeKind
ambush = ModeKind  -- dense ranged with reaction fire vs melee at night
  { mname :: Text
mname   = Text
"ranged ambush (7)"
  , mfreq :: Freqs ModeKind
mfreq   = [(GroupName ModeKind
RANGED, Int
1), (GroupName ModeKind
AMBUSH, Int
1), (GroupName ModeKind
CAMPAIGN_SCENARIO, Int
1)]
  , mtutorial :: Bool
mtutorial = Bool
False
  , mattract :: Bool
mattract = Bool
False
  , mroster :: Roster
mroster = Roster
rosterAmbush
  , mcaves :: Caves
mcaves  = Caves
cavesAmbush
  , mendMsg :: [(Outcome, Text)]
mendMsg = [ (Outcome
Killed, Text
killedMsg)
              , (Outcome
Conquer, Text
"The new instant telegraphy equipment enabling simultaneous ranged attacks with indirect triangulation and aiming proved effective beyond expectation. Your ideas are safe, your research programme on track, your chartered company ready to launch and introduce progress and science into every household of the nation.") ]
  , mrules :: Text
mrules  = Text -> [Text] -> Text
T.intercalate Text
"\n"
      [ Text
"* One level only"
      , Text
"* Three heroes with concurrent attacks vs. Unidentified foes"
      , Text
"* Minimize losses"
      , Text
"* Assert control of the situation ASAP"
      ]
  , mdesc :: Text
mdesc   = Text
"Prevent hijacking of your ideas at all cost! Be stealthy, be observant, be aggressive. Fast execution is what makes or breaks a creative team."
  , mreason :: Text
mreason = Text
"In this adventure, finally, your heroes are able to all use ranged attacks at once, given enough ammunition."
  , mhint :: Text
mhint   = Text
"Beware of friendly fire, particularly from explosives. But you need no more hints. Go fulfill your destiny! For Science!"
  }
 where
   killedMsg :: Text
killedMsg = Text -> [Text] -> Text
T.intercalate Text
"\n"
     [ Text
"You turned out to be the prey, this time, not the hunter. In fact, you are not even in the hunters' league. When fighting against such odds, passively waiting for enemy to spring a trap is to no avail, because a professional team can sneak in darkness and ambush the ambushers."
     , Text
"Granted, good positioning is crucial, so that each squad member can overwatch the battlefield and fire opportunistically, using the recently recovered instant telegraphy equipment. However, there is no hope without active scouting, throwing lit objects and probing suspect areas with missiles while paying attention to sounds. And that may still not be enough."
     ]

safari :: ModeKind
safari = ModeKind  -- Easter egg available only via screensaver
  { mname :: Text
mname   = Text
"safari"
  , mfreq :: Freqs ModeKind
mfreq   = [(GroupName ModeKind
SAFARI, Int
1)]
  , mtutorial :: Bool
mtutorial = Bool
False
  , mattract :: Bool
mattract = Bool
False
  , mroster :: Roster
mroster = Roster
rosterSafari
  , mcaves :: Caves
mcaves  = Caves
cavesSafari
  , mendMsg :: [(Outcome, Text)]
mendMsg = []
  , mrules :: Text
mrules  = Text -> [Text] -> Text
T.intercalate Text
"\n"
      [ Text
"* Three levels"
      , Text
"* Many teammates capable of concurrent action vs. Many enemies"
      , Text
"* Minimize losses"
      , Text
"* Find a way out and escape ASAP"
      ]
  , mdesc :: Text
mdesc   = Text
"\"In this enactment you'll discover the joys of hunting the most exquisite of Earth's flora and fauna, both animal and semi-intelligent. Exit at the bottommost level.\" This is a drama script recovered from a monster nest debris."
  , mreason :: Text
mreason = Text
"This is an Easter egg. The default squad doctrine is that all team members follow the pointman, but it can be changed from the settings submenu of the main menu."
  , mhint :: Text
mhint   = Text
""
  }

-- * Testing modes

dig :: ModeKind
dig = ModeKind
  { mname :: Text
mname   = Text
"dig"
  , mfreq :: Freqs ModeKind
mfreq   = [(GroupName ModeKind
DIG, Int
1)]
  , mtutorial :: Bool
mtutorial = Bool
False
  , mattract :: Bool
mattract = Bool
False
  , mroster :: Roster
mroster = Roster
rosterCrawlEmpty
  , mcaves :: Caves
mcaves  = Caves
cavesDig
  , mendMsg :: [(Outcome, Text)]
mendMsg = []
  , mrules :: Text
mrules  = Text
""
  , mdesc :: Text
mdesc   = Text
"Delve deeper!"
  , mreason :: Text
mreason = Text
""
  , mhint :: Text
mhint   = Text
""
  }

see :: ModeKind
see = ModeKind
  { mname :: Text
mname   = Text
"see"
  , mfreq :: Freqs ModeKind
mfreq   = [(GroupName ModeKind
SEE, Int
1)]
  , mtutorial :: Bool
mtutorial = Bool
False
  , mattract :: Bool
mattract = Bool
False
  , mroster :: Roster
mroster = Roster
rosterCrawlEmpty
  , mcaves :: Caves
mcaves  = Caves
cavesSee
  , mendMsg :: [(Outcome, Text)]
mendMsg = []
  , mrules :: Text
mrules  = Text
""
  , mdesc :: Text
mdesc   = Text
"See all!"
  , mreason :: Text
mreason = Text
""
  , mhint :: Text
mhint   = Text
""
  }

short :: ModeKind
short = ModeKind
  { mname :: Text
mname   = Text
"short"
  , mfreq :: Freqs ModeKind
mfreq   = [(GroupName ModeKind
SHORT, Int
1)]
  , mtutorial :: Bool
mtutorial = Bool
False
  , mattract :: Bool
mattract = Bool
False
  , mroster :: Roster
mroster = Roster
rosterCrawlEmpty
  , mcaves :: Caves
mcaves  = Caves
cavesShort
  , mendMsg :: [(Outcome, Text)]
mendMsg = []
  , mrules :: Text
mrules  = Text
""
  , mdesc :: Text
mdesc   = Text
"See all short scenarios!"
  , mreason :: Text
mreason = Text
""
  , mhint :: Text
mhint   = Text
""
  }

crawlEmpty :: ModeKind
crawlEmpty = ModeKind
  { mname :: Text
mname   = Text
"crawl empty"
  , mfreq :: Freqs ModeKind
mfreq   = [(GroupName ModeKind
CRAWL_EMPTY, Int
1)]
  , mtutorial :: Bool
mtutorial = Bool
False
  , mattract :: Bool
mattract = Bool
False
  , mroster :: Roster
mroster = Roster
rosterCrawlEmpty
  , mcaves :: Caves
mcaves  = Caves
cavesCrawlEmpty
  , mendMsg :: [(Outcome, Text)]
mendMsg = []
  , mrules :: Text
mrules  = Text
""
  , mdesc :: Text
mdesc   = Text
"Enjoy the extra legroom."
  , mreason :: Text
mreason = Text
""
  , mhint :: Text
mhint   = Text
""
  }

crawlSurvival :: ModeKind
crawlSurvival = ModeKind
  { mname :: Text
mname   = Text
"crawl survival"
  , mfreq :: Freqs ModeKind
mfreq   = [(GroupName ModeKind
CRAWL_SURVIVAL, Int
1)]
  , mtutorial :: Bool
mtutorial = Bool
False
  , mattract :: Bool
mattract = Bool
False
  , mroster :: Roster
mroster = Roster
rosterCrawlSurvival
  , mcaves :: Caves
mcaves  = Caves
cavesCrawl
  , mendMsg :: [(Outcome, Text)]
mendMsg = []
  , mrules :: Text
mrules  = Text
""
  , mdesc :: Text
mdesc   = Text
"Lure the human intruders deeper and deeper."
  , mreason :: Text
mreason = Text
""
  , mhint :: Text
mhint   = Text
""
  }

safariSurvival :: ModeKind
safariSurvival = ModeKind
  { mname :: Text
mname   = Text
"safari survival"
  , mfreq :: Freqs ModeKind
mfreq   = [(GroupName ModeKind
SAFARI_SURVIVAL, Int
1)]
  , mtutorial :: Bool
mtutorial = Bool
False
  , mattract :: Bool
mattract = Bool
False
  , mroster :: Roster
mroster = Roster
rosterSafariSurvival
  , mcaves :: Caves
mcaves  = Caves
cavesSafari
  , mendMsg :: [(Outcome, Text)]
mendMsg = []
  , mrules :: Text
mrules  = Text
""
  , mdesc :: Text
mdesc   = Text
"In this enactment you'll discover the joys of being hunted among the most exquisite of Earth's flora and fauna, both animal and semi-intelligent."
  , mreason :: Text
mreason = Text
""
  , mhint :: Text
mhint   = Text
""
  }

battle :: ModeKind
battle = ModeKind
  { mname :: Text
mname   = Text
"battle"
  , mfreq :: Freqs ModeKind
mfreq   = [(GroupName ModeKind
BATTLE, Int
1)]
  , mtutorial :: Bool
mtutorial = Bool
False
  , mattract :: Bool
mattract = Bool
False
  , mroster :: Roster
mroster = Roster
rosterBattle
  , mcaves :: Caves
mcaves  = Caves
cavesBattle
  , mendMsg :: [(Outcome, Text)]
mendMsg = []
  , mrules :: Text
mrules  = Text
""
  , mdesc :: Text
mdesc   = Text
"Odds are stacked against those that unleash the horrors of abstraction."
  , mreason :: Text
mreason = Text
""
  , mhint :: Text
mhint   = Text
""
  }

battleDefense :: ModeKind
battleDefense = ModeKind
  { mname :: Text
mname   = Text
"battle defense"
  , mfreq :: Freqs ModeKind
mfreq   = [(GroupName ModeKind
BATTLE_DEFENSE, Int
1)]
  , mtutorial :: Bool
mtutorial = Bool
False
  , mattract :: Bool
mattract = Bool
False
  , mroster :: Roster
mroster = Roster
rosterBattleDefense
  , mcaves :: Caves
mcaves  = Caves
cavesBattle
  , mendMsg :: [(Outcome, Text)]
mendMsg = []
  , mrules :: Text
mrules  = Text
""
  , mdesc :: Text
mdesc   = Text
"Odds are stacked for those that breathe mathematics."
  , mreason :: Text
mreason = Text
""
  , mhint :: Text
mhint   = Text
""
  }

battleSurvival :: ModeKind
battleSurvival = ModeKind
  { mname :: Text
mname   = Text
"battle survival"
  , mfreq :: Freqs ModeKind
mfreq   = [(GroupName ModeKind
BATTLE_SURVIVAL, Int
1)]
  , mtutorial :: Bool
mtutorial = Bool
False
  , mattract :: Bool
mattract = Bool
False
  , mroster :: Roster
mroster = Roster
rosterBattleSurvival
  , mcaves :: Caves
mcaves  = Caves
cavesBattle
  , mendMsg :: [(Outcome, Text)]
mendMsg = []
  , mrules :: Text
mrules  = Text
""
  , mdesc :: Text
mdesc   = Text
"Odds are stacked for those that ally with the strongest."
  , mreason :: Text
mreason = Text
""
  , mhint :: Text
mhint   = Text
""
  }

defense :: ModeKind
defense = ModeKind  -- perhaps a real scenario in the future
  { mname :: Text
mname   = Text
"defense"
  , mfreq :: Freqs ModeKind
mfreq   = [(GroupName ModeKind
DEFENSE, Int
1)]
  , mtutorial :: Bool
mtutorial = Bool
False
  , mattract :: Bool
mattract = Bool
False
  , mroster :: Roster
mroster = Roster
rosterDefense
  , mcaves :: Caves
mcaves  = Caves
cavesCrawl
  , mendMsg :: [(Outcome, Text)]
mendMsg = []
  , mrules :: Text
mrules  = Text
""
  , mdesc :: Text
mdesc   = Text
"Don't let human interlopers defile your abstract secrets and flee unpunished!"
  , mreason :: Text
mreason = Text
"This is an initial sketch of the reversed crawl game mode. Play on high difficulty to avoid guaranteed victories against the pitiful humans."
  , mhint :: Text
mhint   = Text
""
  }

defenseEmpty :: ModeKind
defenseEmpty = ModeKind
  { mname :: Text
mname   = Text
"defense empty"
  , mfreq :: Freqs ModeKind
mfreq   = [(GroupName ModeKind
DEFENSE_EMPTY, Int
1)]
  , mtutorial :: Bool
mtutorial = Bool
False
  , mattract :: Bool
mattract = Bool
False
  , mroster :: Roster
mroster = Roster
rosterDefenseEmpty
  , mcaves :: Caves
mcaves  = Caves
cavesCrawlEmpty
  , mendMsg :: [(Outcome, Text)]
mendMsg = []
  , mrules :: Text
mrules  = Text
""
  , mdesc :: Text
mdesc   = Text
"Lord over empty halls."
  , mreason :: Text
mreason = Text
""
  , mhint :: Text
mhint   = Text
""
  }

-- * Screensaver modes

screensaverRaid :: ModeKind
screensaverRaid = ModeKind
raid
  { mname   = "auto-raid (1)"
  , mfreq   = [(INSERT_COIN, 2)]
  , mattract = True
  }

screensaverBrawl :: ModeKind
screensaverBrawl = ModeKind
brawl
  { mname   = "auto-brawl (2)"
  , mfreq   = []
  , mattract = True
  }

screensaverCrawl :: ModeKind
screensaverCrawl = ModeKind
crawl
  { mname   = "auto-crawl (long)"
  , mfreq   = []
  , mattract = True
  }

screensaverShootout :: ModeKind
screensaverShootout = ModeKind
shootout
  { mname   = "auto-shootout (3)"
  , mfreq   = [(INSERT_COIN, 2)]
  , mattract = True
  }

screensaverHunt :: ModeKind
screensaverHunt = ModeKind
hunt
  { mname   = "auto-hunt (4)"
  , mfreq   = [(INSERT_COIN, 2)]
  , mattract = True
  }

screensaverFlight :: ModeKind
screensaverFlight = ModeKind
flight
  { mname   = "auto-flight (5)"
  , mfreq   = [(INSERT_COIN, 2)]
  , mattract = True
  }

screensaverZoo :: ModeKind
screensaverZoo = ModeKind
zoo
  { mname   = "auto-zoo (6)"
  , mfreq   = []
  , mattract = True
  }

screensaverAmbush :: ModeKind
screensaverAmbush = ModeKind
ambush
  { mname   = "auto-ambush (7)"
  , mfreq   = []
  , mattract = True
  }

screensaverSafari :: ModeKind
screensaverSafari = ModeKind
safari
  { mname   = "auto-safari"
  , mfreq   = [(INSERT_COIN, 1)]
  , mattract = True
  }

rosterRaid, rosterBrawl, rosterCrawl, rosterShootout, rosterHunt, rosterFlight, rosterZoo, rosterAmbush, rosterSafari, rosterCrawlEmpty, rosterCrawlSurvival, rosterSafariSurvival, rosterBattle, rosterBattleDefense, rosterBattleSurvival, rosterDefense, rosterDefenseEmpty :: Roster

rosterRaid :: Roster
rosterRaid =
  [ ( GroupName FactionKind
ANIMAL_REPRESENTATIVE  -- starting over escape
    , [(-Int
2, Dice
2, GroupName ItemKind
ANIMAL)] )
  , ( GroupName FactionKind
EXPLORER_SHORT
    , [(-Int
2, Dice
2, GroupName ItemKind
HERO)] )
  , ( GroupName FactionKind
COMPETITOR_SHORT
    , [(-Int
2, Dice
1, GroupName ItemKind
HERO)] )
  , (GroupName FactionKind
HORROR_REPRESENTATIVE, []) ]  -- for summoned monsters

rosterBrawl :: Roster
rosterBrawl =
  [ ( GroupName FactionKind
EXPLORER_NO_ESCAPE
    , [(-Int
2, Dice
3, GroupName ItemKind
BRAWLER_HERO)] )
  , ( GroupName FactionKind
COMPETITOR_NO_ESCAPE
    , [(-Int
2, Dice
3, GroupName ItemKind
BRAWLER_HERO)] )
  , (GroupName FactionKind
HORROR_REPRESENTATIVE, []) ]

rosterCrawl :: Roster
rosterCrawl =
  [ ( GroupName FactionKind
ANIMAL_REPRESENTATIVE  -- starting over escape
    , -- Fun from the start to avoid empty initial level:
      [ (-Int
1, Dice
1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Dice
`d` Int
2, GroupName ItemKind
ANIMAL)
      -- Huge battle at the end:
      , (-Int
10, Dice
100, GroupName ItemKind
MOBILE_ANIMAL) ] )
  , ( GroupName FactionKind
EXPLORER_REPRESENTATIVE
        -- start on stairs so that stash is handy
    , [(-Int
1, Dice
3, GroupName ItemKind
HERO)] )
  , ( GroupName FactionKind
MONSTER_REPRESENTATIVE
    , [(-Int
4, Dice
1, GroupName ItemKind
SCOUT_MONSTER), (-Int
4, Dice
3, GroupName ItemKind
MONSTER)] ) ]

-- Exactly one scout gets a sight boost, to help the aggressor, because he uses
-- the scout for initial attack, while camper (on big enough maps)
-- can't guess where the attack would come and so can't position his single
-- scout to counter the stealthy advance.
rosterShootout :: Roster
rosterShootout =
  [ ( GroupName FactionKind
EXPLORER_NO_ESCAPE
    , [(-Int
5, Dice
2, GroupName ItemKind
RANGER_HERO), (-Int
5, Dice
1, GroupName ItemKind
SCOUT_HERO)] )
  , ( GroupName FactionKind
COMPETITOR_NO_ESCAPE
    , [(-Int
5, Dice
2, GroupName ItemKind
RANGER_HERO), (-Int
5, Dice
1, GroupName ItemKind
SCOUT_HERO)] )
  , (GroupName FactionKind
HORROR_REPRESENTATIVE, []) ]

rosterHunt :: Roster
rosterHunt =
  [ ( GroupName FactionKind
EXPLORER_NO_ESCAPE
    , [(-Int
6, Dice
7, GroupName ItemKind
SOLDIER_HERO)] )
  , ( GroupName FactionKind
COMPETITOR_NO_ESCAPE
    , [(-Int
6, Dice
6, GroupName ItemKind
AMBUSHER_HERO), (-Int
6, Dice
1, GroupName ItemKind
SCOUT_HERO)] )
  , (GroupName FactionKind
HORROR_REPRESENTATIVE, []) ]

rosterFlight :: Roster
rosterFlight =
  [ ( GroupName FactionKind
COMPETITOR_NO_ESCAPE  -- start on escape
    , [(-Int
7, Dice
6, GroupName ItemKind
AMBUSHER_HERO), (-Int
7, Dice
1, GroupName ItemKind
SCOUT_HERO)] )
  , ( GroupName FactionKind
EXPLORER_MEDIUM
    , [(-Int
7, Dice
2, GroupName ItemKind
ESCAPIST_HERO), (-Int
7, Dice
1, GroupName ItemKind
SCOUT_HERO)] )
      -- second on the list to let foes occupy the escape
  , (GroupName FactionKind
HORROR_REPRESENTATIVE, []) ]

rosterZoo :: Roster
rosterZoo =
  [ ( GroupName FactionKind
EXPLORER_TRAPPED
    , [(-Int
8, Dice
5, GroupName ItemKind
SOLDIER_HERO)] )
  , ( GroupName FactionKind
ANIMAL_CAPTIVE
    , [(-Int
8, Dice
100, GroupName ItemKind
MOBILE_ANIMAL)] )
  , (GroupName FactionKind
HORROR_REPRESENTATIVE, []) ]  -- for summoned monsters

rosterAmbush :: Roster
rosterAmbush =
  [ ( GroupName FactionKind
EXPLORER_NO_ESCAPE
    , [(-Int
9, Dice
5, GroupName ItemKind
AMBUSHER_HERO), (-Int
9, Dice
1, GroupName ItemKind
SCOUT_HERO)] )
  , ( GroupName FactionKind
COMPETITOR_NO_ESCAPE
    , [(-Int
9, Dice
12, GroupName ItemKind
SOLDIER_HERO)] )
  , (GroupName FactionKind
HORROR_REPRESENTATIVE, []) ]

-- No horrors faction needed, because spawned heroes land in civilian faction.
rosterSafari :: Roster
rosterSafari =
  [ ( GroupName FactionKind
MONSTER_TOURIST
    , [(-Int
4, Dice
15, GroupName ItemKind
MONSTER)] )
  , ( GroupName FactionKind
CONVICT_REPRESENTATIVE
    , [(-Int
4, Dice
2, GroupName ItemKind
CIVILIAN)] )
  , ( GroupName FactionKind
ANIMAL_MAGNIFICENT
    , [(-Int
7, Dice
15, GroupName ItemKind
MOBILE_ANIMAL)] )
  , ( GroupName FactionKind
ANIMAL_EXQUISITE  -- start on escape
    , [(-Int
10, Dice
20, GroupName ItemKind
MOBILE_ANIMAL)] ) ]

rosterCrawlEmpty :: Roster
rosterCrawlEmpty =
  [ ( GroupName FactionKind
EXPLORER_PACIFIST
    , [(-Int
1, Dice
1, GroupName ItemKind
HERO)] )
  , (GroupName FactionKind
HORROR_PACIFIST, []) ]
      -- for spawned and summoned monsters

rosterCrawlSurvival :: Roster
rosterCrawlSurvival =
  [ ( GroupName FactionKind
EXPLORER_AUTOMATED
    , [(-Int
1, Dice
3, GroupName ItemKind
HERO)] )
  , ( GroupName FactionKind
MONSTER_REPRESENTATIVE
    , [(-Int
4, Dice
1, GroupName ItemKind
SCOUT_MONSTER), (-Int
4, Dice
3, GroupName ItemKind
MONSTER)] )
  , ( GroupName FactionKind
ANIMAL_NARRATING
    , [(-Int
5, Dice
10, GroupName ItemKind
ANIMAL)] ) ]  -- explore unopposed for some time

rosterSafariSurvival :: Roster
rosterSafariSurvival =
  [ ( GroupName FactionKind
MONSTER_TOURIST_PASSIVE
    , [(-Int
4, Dice
15, GroupName ItemKind
MONSTER)] )
  , ( GroupName FactionKind
CONVICT_REPRESENTATIVE
    , [(-Int
4, Dice
3, GroupName ItemKind
CIVILIAN)] )
  , ( GroupName FactionKind
ANIMAL_MAGNIFICENT_NARRATING
    , [(-Int
7, Dice
20, GroupName ItemKind
MOBILE_ANIMAL)] )
  , ( GroupName FactionKind
ANIMAL_EXQUISITE
    , [(-Int
10, Dice
30, GroupName ItemKind
MOBILE_ANIMAL)] ) ]

rosterBattle :: Roster
rosterBattle =
  [ ( GroupName FactionKind
EXPLORER_TRAPPED
    , [(-Int
5, Dice
5, GroupName ItemKind
SOLDIER_HERO)] )
  , ( GroupName FactionKind
MONSTER_CAPTIVE
    , [(-Int
5, Dice
35, GroupName ItemKind
MOBILE_MONSTER)] )
  , ( GroupName FactionKind
ANIMAL_CAPTIVE
    , [(-Int
5, Dice
30, GroupName ItemKind
MOBILE_ANIMAL)] ) ]

rosterBattleDefense :: Roster
rosterBattleDefense =
  [ ( GroupName FactionKind
EXPLORER_AUTOMATED_TRAPPED
    , [(-Int
5, Dice
5, GroupName ItemKind
SOLDIER_HERO)] )
  , ( GroupName FactionKind
MONSTER_CAPTIVE_NARRATING
    , [(-Int
5, Dice
35, GroupName ItemKind
MOBILE_MONSTER)] )
  , ( GroupName FactionKind
ANIMAL_CAPTIVE
    , [(-Int
5, Dice
30, GroupName ItemKind
MOBILE_ANIMAL)] ) ]

rosterBattleSurvival :: Roster
rosterBattleSurvival =
  [ ( GroupName FactionKind
EXPLORER_AUTOMATED_TRAPPED
    , [(-Int
5, Dice
5, GroupName ItemKind
SOLDIER_HERO)] )
  , ( GroupName FactionKind
MONSTER_CAPTIVE
    , [(-Int
5, Dice
35, GroupName ItemKind
MOBILE_MONSTER)] )
  , ( GroupName FactionKind
ANIMAL_CAPTIVE_NARRATING
    , [(-Int
5, Dice
30, GroupName ItemKind
MOBILE_ANIMAL)] ) ]

rosterDefense :: Roster
rosterDefense =
  [ ( GroupName FactionKind
EXPLORER_AUTOMATED
    , [(-Int
1, Dice
3, GroupName ItemKind
HERO)] )
  , ( GroupName FactionKind
MONSTER_ANTI
    , [(-Int
4, Dice
1, GroupName ItemKind
SCOUT_MONSTER), (-Int
4, Dice
3, GroupName ItemKind
MONSTER)] )
  , ( GroupName FactionKind
ANIMAL_REPRESENTATIVE
    , [ (-Int
1, Dice
1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Dice
`d` Int
2, GroupName ItemKind
ANIMAL)
      , (-Int
10, Dice
100, GroupName ItemKind
MOBILE_ANIMAL) ] ) ]

rosterDefenseEmpty :: Roster
rosterDefenseEmpty =
  [ ( GroupName FactionKind
MONSTER_ANTI_PACIFIST
    , [(-Int
4, Dice
1, GroupName ItemKind
SCOUT_MONSTER)] )
  , (GroupName FactionKind
HORROR_PACIFIST, []) ]
      -- for spawned and summoned animals

cavesRaid, cavesBrawl, cavesCrawl, cavesShootout, cavesHunt, cavesFlight, cavesZoo, cavesAmbush, cavesSafari, cavesDig, cavesSee, cavesShort, cavesCrawlEmpty, cavesBattle :: Caves

cavesRaid :: Caves
cavesRaid = [([-Int
2], [GroupName CaveKind
CAVE_RAID])]

cavesBrawl :: Caves
cavesBrawl = [([-Int
2], [GroupName CaveKind
CAVE_BRAWL])]

listCrawl :: [([Int], [GroupName CaveKind])]
listCrawl :: Caves
listCrawl =
  [ ([-Int
1], [GroupName CaveKind
CAVE_OUTERMOST])
  , ([-Int
2], [GroupName CaveKind
CAVE_SHALLOW_ROGUE])
  , ([-Int
3], [GroupName CaveKind
CAVE_EMPTY])
  , ([-Int
4, -Int
5, -Int
6], [GroupName CaveKind
DEFAULT_RANDOM, GroupName CaveKind
CAVE_ROGUE, GroupName CaveKind
CAVE_ARENA])
  , ([-Int
7, -Int
8], [GroupName CaveKind
CAVE_ROGUE, GroupName CaveKind
CAVE_SMOKING])
  , ([-Int
9], [GroupName CaveKind
CAVE_LABORATORY])
  , ([-Int
10], [GroupName CaveKind
CAVE_MINE]) ]

cavesCrawl :: Caves
cavesCrawl = Caves
listCrawl

cavesShootout :: Caves
cavesShootout = [([-Int
5], [GroupName CaveKind
CAVE_SHOOTOUT])]

cavesHunt :: Caves
cavesHunt = [([-Int
6], [GroupName CaveKind
CAVE_HUNT])]

cavesFlight :: Caves
cavesFlight = [([-Int
7], [GroupName CaveKind
CAVE_FLIGHT])]

cavesZoo :: Caves
cavesZoo = [([-Int
8], [GroupName CaveKind
CAVE_ZOO])]

cavesAmbush :: Caves
cavesAmbush = [([-Int
9], [GroupName CaveKind
CAVE_AMBUSH])]

cavesSafari :: Caves
cavesSafari = [ ([-Int
4], [GroupName CaveKind
CAVE_SAFARI_1])
              , ([-Int
7], [GroupName CaveKind
CAVE_SAFARI_2])
              , ([-Int
10], [GroupName CaveKind
CAVE_SAFARI_3]) ]

cavesDig :: Caves
cavesDig = [Caves] -> Caves
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([Caves] -> Caves) -> [Caves] -> Caves
forall a b. (a -> b) -> a -> b
$ (Int -> Caves -> Caves) -> [Int] -> [Caves] -> [Caves]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith ((([Int], [GroupName CaveKind]) -> ([Int], [GroupName CaveKind]))
-> Caves -> Caves
forall a b. (a -> b) -> [a] -> [b]
map ((([Int], [GroupName CaveKind]) -> ([Int], [GroupName CaveKind]))
 -> Caves -> Caves)
-> (Int
    -> ([Int], [GroupName CaveKind]) -> ([Int], [GroupName CaveKind]))
-> Int
-> Caves
-> Caves
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int
-> ([Int], [GroupName CaveKind]) -> ([Int], [GroupName CaveKind])
renumberCaves)
                            [Int
0, -Int
10 ..]
                            (Int -> Caves -> [Caves]
forall a. Int -> a -> [a]
replicate Int
100 Caves
listCrawl)

renumberCaves :: Int -> ([Int], [GroupName CaveKind])
              -> ([Int], [GroupName CaveKind])
renumberCaves :: Int
-> ([Int], [GroupName CaveKind]) -> ([Int], [GroupName CaveKind])
renumberCaves Int
offset ([Int]
ns, [GroupName CaveKind]
l) = ((Int -> Int) -> [Int] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
offset) [Int]
ns, [GroupName CaveKind]
l)

cavesSee :: Caves
cavesSee = let numberCaves :: a -> a -> ([a], [a])
numberCaves a
n a
c = ([a
n], [a
c])
           in (Int -> GroupName CaveKind -> ([Int], [GroupName CaveKind]))
-> [Int] -> [GroupName CaveKind] -> Caves
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Int -> GroupName CaveKind -> ([Int], [GroupName CaveKind])
forall {a} {a}. a -> a -> ([a], [a])
numberCaves [-Int
1, -Int
2 ..]
              ([GroupName CaveKind] -> Caves) -> [GroupName CaveKind] -> Caves
forall a b. (a -> b) -> a -> b
$ (GroupName CaveKind -> [GroupName CaveKind])
-> [GroupName CaveKind] -> [GroupName CaveKind]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Int -> GroupName CaveKind -> [GroupName CaveKind]
forall a. Int -> a -> [a]
replicate Int
10) [GroupName CaveKind]
allCaves

cavesShort :: Caves
cavesShort = let numberCaves :: a -> a -> ([a], [a])
numberCaves a
n a
c = ([a
n], [a
c])
             in (Int -> GroupName CaveKind -> ([Int], [GroupName CaveKind]))
-> [Int] -> [GroupName CaveKind] -> Caves
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Int -> GroupName CaveKind -> ([Int], [GroupName CaveKind])
forall {a} {a}. a -> a -> ([a], [a])
numberCaves [-Int
1, -Int
2 ..]
                ([GroupName CaveKind] -> Caves) -> [GroupName CaveKind] -> Caves
forall a b. (a -> b) -> a -> b
$ (GroupName CaveKind -> [GroupName CaveKind])
-> [GroupName CaveKind] -> [GroupName CaveKind]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Int -> GroupName CaveKind -> [GroupName CaveKind]
forall a. Int -> a -> [a]
replicate Int
100) ([GroupName CaveKind] -> [GroupName CaveKind])
-> [GroupName CaveKind] -> [GroupName CaveKind]
forall a b. (a -> b) -> a -> b
$ Int -> [GroupName CaveKind] -> [GroupName CaveKind]
forall a. Int -> [a] -> [a]
take Int
7 [GroupName CaveKind]
allCaves

allCaves :: [GroupName CaveKind]
allCaves :: [GroupName CaveKind]
allCaves =
  [ GroupName CaveKind
CAVE_RAID, GroupName CaveKind
CAVE_BRAWL, GroupName CaveKind
CAVE_SHOOTOUT, GroupName CaveKind
CAVE_HUNT, GroupName CaveKind
CAVE_FLIGHT, GroupName CaveKind
CAVE_ZOO
  , GroupName CaveKind
CAVE_AMBUSH
  , GroupName CaveKind
CAVE_ROGUE, GroupName CaveKind
CAVE_LABORATORY, GroupName CaveKind
CAVE_EMPTY, GroupName CaveKind
CAVE_ARENA, GroupName CaveKind
CAVE_SMOKING
  , GroupName CaveKind
CAVE_NOISE, GroupName CaveKind
CAVE_MINE ]

cavesCrawlEmpty :: Caves
cavesCrawlEmpty = Caves
cavesCrawl

cavesBattle :: Caves
cavesBattle = [([-Int
5], [GroupName CaveKind
CAVE_BATTLE])]