module Content.ModeKind
(
groupNamesSingleton, groupNames
,
content
#ifdef EXPOSE_INTERNAL
, pattern RAID, pattern BRAWL, pattern LONG, pattern CRAWL, pattern FOGGY, pattern SHOOTOUT, pattern PERILOUS, pattern HUNT, pattern NIGHT, pattern ESCAPE, 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 Content.CaveKind hiding (content, groupNames, groupNamesSingleton)
import Content.ItemKindActor
import Content.ModeKindPlayer
import Game.LambdaHack.Content.CaveKind (CaveKind, pattern DEFAULT_RANDOM)
import Game.LambdaHack.Content.ModeKind
import Game.LambdaHack.Core.Dice
import Game.LambdaHack.Definition.Defs
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
ESCAPE, 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, ESCAPE, 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 = [GroupName ModeKind
NO_CONFIRMS]
pattern $bRAID :: GroupName ModeKind
$mRAID :: forall r. GroupName ModeKind -> (Void# -> r) -> (Void# -> r) -> r
RAID = GroupName "raid"
pattern $bBRAWL :: GroupName ModeKind
$mBRAWL :: forall r. GroupName ModeKind -> (Void# -> r) -> (Void# -> r) -> r
BRAWL = GroupName "brawl"
pattern $bLONG :: GroupName ModeKind
$mLONG :: forall r. GroupName ModeKind -> (Void# -> r) -> (Void# -> r) -> r
LONG = GroupName "long crawl"
pattern $bCRAWL :: GroupName ModeKind
$mCRAWL :: forall r. GroupName ModeKind -> (Void# -> r) -> (Void# -> r) -> r
CRAWL = GroupName "crawl"
pattern $bFOGGY :: GroupName ModeKind
$mFOGGY :: forall r. GroupName ModeKind -> (Void# -> r) -> (Void# -> r) -> r
FOGGY = GroupName "foggy shootout"
pattern $bSHOOTOUT :: GroupName ModeKind
$mSHOOTOUT :: forall r. GroupName ModeKind -> (Void# -> r) -> (Void# -> r) -> r
SHOOTOUT = GroupName "shootout"
pattern $bPERILOUS :: GroupName ModeKind
$mPERILOUS :: forall r. GroupName ModeKind -> (Void# -> r) -> (Void# -> r) -> r
PERILOUS = GroupName "perilous hunt"
pattern $bHUNT :: GroupName ModeKind
$mHUNT :: forall r. GroupName ModeKind -> (Void# -> r) -> (Void# -> r) -> r
HUNT = GroupName "hunt"
pattern $bNIGHT :: GroupName ModeKind
$mNIGHT :: forall r. GroupName ModeKind -> (Void# -> r) -> (Void# -> r) -> r
NIGHT = GroupName "night escape"
pattern $bESCAPE :: GroupName ModeKind
$mESCAPE :: forall r. GroupName ModeKind -> (Void# -> r) -> (Void# -> r) -> r
ESCAPE = GroupName "escape"
pattern $bBURNING :: GroupName ModeKind
$mBURNING :: forall r. GroupName ModeKind -> (Void# -> r) -> (Void# -> r) -> r
BURNING = GroupName "burning zoo"
pattern $bZOO :: GroupName ModeKind
$mZOO :: forall r. GroupName ModeKind -> (Void# -> r) -> (Void# -> r) -> r
ZOO = GroupName "zoo"
pattern $bRANGED :: GroupName ModeKind
$mRANGED :: forall r. GroupName ModeKind -> (Void# -> r) -> (Void# -> r) -> r
RANGED = GroupName "ranged ambush"
pattern $bAMBUSH :: GroupName ModeKind
$mAMBUSH :: forall r. GroupName ModeKind -> (Void# -> r) -> (Void# -> r) -> r
AMBUSH = GroupName "ambush"
pattern $bSAFARI :: GroupName ModeKind
$mSAFARI :: forall r. GroupName ModeKind -> (Void# -> r) -> (Void# -> r) -> r
SAFARI = GroupName "safari"
pattern $bDIG :: GroupName ModeKind
$mDIG :: forall r. GroupName ModeKind -> (Void# -> r) -> (Void# -> r) -> r
DIG = GroupName "dig"
pattern $bSEE :: GroupName ModeKind
$mSEE :: forall r. GroupName ModeKind -> (Void# -> r) -> (Void# -> r) -> r
SEE = GroupName "see"
pattern $bSHORT :: GroupName ModeKind
$mSHORT :: forall r. GroupName ModeKind -> (Void# -> r) -> (Void# -> r) -> r
SHORT = GroupName "short"
pattern $bCRAWL_EMPTY :: GroupName ModeKind
$mCRAWL_EMPTY :: forall r. GroupName ModeKind -> (Void# -> r) -> (Void# -> r) -> r
CRAWL_EMPTY = GroupName "crawlEmpty"
pattern $bCRAWL_SURVIVAL :: GroupName ModeKind
$mCRAWL_SURVIVAL :: forall r. GroupName ModeKind -> (Void# -> r) -> (Void# -> r) -> r
CRAWL_SURVIVAL = GroupName "crawlSurvival"
pattern $bSAFARI_SURVIVAL :: GroupName ModeKind
$mSAFARI_SURVIVAL :: forall r. GroupName ModeKind -> (Void# -> r) -> (Void# -> r) -> r
SAFARI_SURVIVAL = GroupName "safariSurvival"
pattern $bBATTLE :: GroupName ModeKind
$mBATTLE :: forall r. GroupName ModeKind -> (Void# -> r) -> (Void# -> r) -> r
BATTLE = GroupName "battle"
pattern $bBATTLE_DEFENSE :: GroupName ModeKind
$mBATTLE_DEFENSE :: forall r. GroupName ModeKind -> (Void# -> r) -> (Void# -> r) -> r
BATTLE_DEFENSE = GroupName "battleDefense"
pattern $bBATTLE_SURVIVAL :: GroupName ModeKind
$mBATTLE_SURVIVAL :: forall r. GroupName ModeKind -> (Void# -> r) -> (Void# -> r) -> r
BATTLE_SURVIVAL = GroupName "battleSurvival"
pattern $bDEFENSE :: GroupName ModeKind
$mDEFENSE :: forall r. GroupName ModeKind -> (Void# -> r) -> (Void# -> r) -> r
DEFENSE = GroupName "defense"
pattern $bDEFENSE_EMPTY :: GroupName ModeKind
$mDEFENSE_EMPTY :: forall r. GroupName ModeKind -> (Void# -> r) -> (Void# -> r) -> r
DEFENSE_EMPTY = GroupName "defenseEmpty"
content :: [ModeKind]
content :: [ModeKind]
content =
[ModeKind
raid, ModeKind
brawl, ModeKind
crawl, ModeKind
shootout, ModeKind
hunt, ModeKind
escape, 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
screensaverEscape, ModeKind
screensaverZoo, ModeKind
screensaverAmbush, ModeKind
screensaverSafari]
raid, brawl, crawl, shootout, hunt, escape, zoo, ambush, safari, dig, see, short, crawlEmpty, crawlSurvival, safariSurvival, battle, battleDefense, battleSurvival, defense, defenseEmpty, screensaverRaid, screensaverBrawl, screensaverCrawl, screensaverShootout, screensaverHunt, screensaverEscape, screensaverZoo, screensaverAmbush, screensaverSafari :: ModeKind
raid :: ModeKind
raid = $WModeKind :: Char
-> Text
-> Freqs ModeKind
-> Bool
-> Roster
-> Caves
-> [(Outcome, Text)]
-> Text
-> Text
-> Text
-> Text
-> ModeKind
ModeKind
{ msymbol :: Char
msymbol = 'r'
, mname :: Text
mname = "raid (tutorial, 1)"
, mfreq :: Freqs ModeKind
mfreq = [(GroupName ModeKind
RAID, 1), (GroupName ModeKind
CAMPAIGN_SCENARIO, 1)]
, mtutorial :: Bool
mtutorial = Bool
True
, mroster :: Roster
mroster = Roster
rosterRaid
, mcaves :: Caves
mcaves = Caves
cavesRaid
, mendMsg :: [(Outcome, Text)]
mendMsg = [ (Outcome
Killed, "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, "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, "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 "\n"
[ "* One level only"
, "* Two heroes vs. Spawned enemies"
, "* Gather gold"
, "* Find exit and escape ASAP"
]
, mdesc :: Text
mdesc = "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 = "In addition to initiating the (loose) game plot, this adventure provides an introductory tutorial. Relax, explore, gather loot, find the exit and escape. With some luck, you won't even need to fight anything."
, mhint :: Text
mhint = "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 = $WModeKind :: Char
-> Text
-> Freqs ModeKind
-> Bool
-> Roster
-> Caves
-> [(Outcome, Text)]
-> Text
-> Text
-> Text
-> Text
-> ModeKind
ModeKind
{ msymbol :: Char
msymbol = 'k'
, mname :: Text
mname = "brawl (tutorial, 2)"
, mfreq :: Freqs ModeKind
mfreq = [(GroupName ModeKind
BRAWL, 1), (GroupName ModeKind
CAMPAIGN_SCENARIO, 1)]
, mtutorial :: Bool
mtutorial = Bool
True
, mroster :: Roster
mroster = Roster
rosterBrawl
, mcaves :: Caves
mcaves = Caves
cavesBrawl
, mendMsg :: [(Outcome, Text)]
mendMsg = [ (Outcome
Killed, "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, "That's settled: local compactness *is* necessary for relative completeness, given the assumptions.") ]
, mrules :: Text
mrules = Text -> [Text] -> Text
T.intercalate "\n"
[ "* One level only"
, "* Three heroes vs. Three human enemies"
, "* Minimize losses"
, "* Incapacitate all enemies ASAP"
]
, mdesc :: Text
mdesc = "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."
, mreason :: Text
mreason = "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 = "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.\nObserve 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.\nIf 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 = $WModeKind :: Char
-> Text
-> Freqs ModeKind
-> Bool
-> Roster
-> Caves
-> [(Outcome, Text)]
-> Text
-> Text
-> Text
-> Text
-> ModeKind
ModeKind
{ msymbol :: Char
msymbol = 'c'
, mname :: Text
mname = "long crawl (main)"
, mfreq :: Freqs ModeKind
mfreq = [(GroupName ModeKind
LONG, 1), (GroupName ModeKind
CRAWL, 1), (GroupName ModeKind
CAMPAIGN_SCENARIO, 1)]
, mtutorial :: Bool
mtutorial = Bool
False
, mroster :: Roster
mroster = Roster
rosterCrawl
, mcaves :: Caves
mcaves = Caves
cavesCrawl
, mendMsg :: [(Outcome, Text)]
mendMsg = [ (Outcome
Killed, "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? 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?")
, (Outcome
Escape, "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 "\n"
[ "* Many levels"
, "* Three heroes vs. Spawned enemies"
, "* Gather gold, gems and elixirs"
, "* Find exit and escape ASAP"
]
, mdesc :: Text
mdesc = "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 = "This is the main, longest and most replayable scenario of the game."
, mhint :: Text
mhint = "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."
}
shootout :: ModeKind
shootout = $WModeKind :: Char
-> Text
-> Freqs ModeKind
-> Bool
-> Roster
-> Caves
-> [(Outcome, Text)]
-> Text
-> Text
-> Text
-> Text
-> ModeKind
ModeKind
{ msymbol :: Char
msymbol = 's'
, mname :: Text
mname = "foggy shootout (3)"
, mfreq :: Freqs ModeKind
mfreq = [(GroupName ModeKind
FOGGY, 1), (GroupName ModeKind
SHOOTOUT, 1), (GroupName ModeKind
CAMPAIGN_SCENARIO, 1)]
, mtutorial :: Bool
mtutorial = Bool
False
, mroster :: Roster
mroster = Roster
rosterShootout
, mcaves :: Caves
mcaves = Caves
cavesShootout
, mendMsg :: [(Outcome, Text)]
mendMsg = []
, mrules :: Text
mrules = Text -> [Text] -> Text
T.intercalate "\n"
[ "* One level only"
, "* Three heroes vs. Three human enemies"
, "* Minimize losses"
, "* Incapacitate all enemies ASAP"
]
, mdesc :: Text
mdesc = "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 = "This adventure teaches the ranged combat skill in the simplified setup of fully symmetric battle."
, mhint :: Text
mhint = "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."
}
hunt :: ModeKind
hunt = $WModeKind :: Char
-> Text
-> Freqs ModeKind
-> Bool
-> Roster
-> Caves
-> [(Outcome, Text)]
-> Text
-> Text
-> Text
-> Text
-> ModeKind
ModeKind
{ msymbol :: Char
msymbol = 'h'
, mname :: Text
mname = "perilous hunt (4)"
, mfreq :: Freqs ModeKind
mfreq = [(GroupName ModeKind
PERILOUS, 1), (GroupName ModeKind
HUNT, 1), (GroupName ModeKind
CAMPAIGN_SCENARIO, 1)]
, mtutorial :: Bool
mtutorial = Bool
False
, mroster :: Roster
mroster = Roster
rosterHunt
, mcaves :: Caves
mcaves = Caves
cavesHunt
, mendMsg :: [(Outcome, Text)]
mendMsg = []
, mrules :: Text
mrules = Text -> [Text] -> Text
T.intercalate "\n"
[ "* One level only"
, "* Seven heroes vs. Seven human enemies capable of concurrent attacks"
, "* Minimize losses"
, "* Incapacitate all enemies ASAP"
]
, mdesc :: Text
mdesc = "Who is the hunter and who is the prey? The only criterion is last man standing when the chase ends."
, mreason :: Text
mreason = "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 = "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 rougly 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 any."
}
escape :: ModeKind
escape = $WModeKind :: Char
-> Text
-> Freqs ModeKind
-> Bool
-> Roster
-> Caves
-> [(Outcome, Text)]
-> Text
-> Text
-> Text
-> Text
-> ModeKind
ModeKind
{ msymbol :: Char
msymbol = 'e'
, mname :: Text
mname = "night escape (5)"
, mfreq :: Freqs ModeKind
mfreq = [(GroupName ModeKind
NIGHT, 1), (GroupName ModeKind
ESCAPE, 1), (GroupName ModeKind
CAMPAIGN_SCENARIO, 1)]
, mtutorial :: Bool
mtutorial = Bool
False
, mroster :: Roster
mroster = Roster
rosterEscape
, mcaves :: Caves
mcaves = Caves
cavesEscape
, mendMsg :: [(Outcome, Text)]
mendMsg = []
, mrules :: Text
mrules = Text -> [Text] -> Text
T.intercalate "\n"
[ "* One level only"
, "* Three heroes vs. Seven human enemies capable of concurrent attacks"
, "* Minimize losses"
, "* Gather gems"
, "* Find exit and escape ASAP"
]
, mdesc :: Text
mdesc = "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 = "The focus of this installment is on stealthy exploration under the threat of numerically superior enemy."
, mhint :: Text
mhint = ""
}
zoo :: ModeKind
zoo = $WModeKind :: Char
-> Text
-> Freqs ModeKind
-> Bool
-> Roster
-> Caves
-> [(Outcome, Text)]
-> Text
-> Text
-> Text
-> Text
-> ModeKind
ModeKind
{ msymbol :: Char
msymbol = 'b'
, mname :: Text
mname = "burning zoo (6)"
, mfreq :: Freqs ModeKind
mfreq = [(GroupName ModeKind
BURNING, 1), (GroupName ModeKind
ZOO, 1), (GroupName ModeKind
CAMPAIGN_SCENARIO, 1)]
, mtutorial :: Bool
mtutorial = Bool
False
, mroster :: Roster
mroster = Roster
rosterZoo
, mcaves :: Caves
mcaves = Caves
cavesZoo
, mendMsg :: [(Outcome, Text)]
mendMsg = []
, mrules :: Text
mrules = Text -> [Text] -> Text
T.intercalate "\n"
[ "* One level only"
, "* Five heroes vs. Many enemies"
, "* Minimize losses"
, "* Incapacitate all enemies ASAP"
]
, mdesc :: Text
mdesc = "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 = "This is a crowd control exercise, at night, with a raging fire."
, mhint :: Text
mhint = "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."
}
ambush :: ModeKind
ambush = $WModeKind :: Char
-> Text
-> Freqs ModeKind
-> Bool
-> Roster
-> Caves
-> [(Outcome, Text)]
-> Text
-> Text
-> Text
-> Text
-> ModeKind
ModeKind
{ msymbol :: Char
msymbol = 'm'
, mname :: Text
mname = "ranged ambush (7)"
, mfreq :: Freqs ModeKind
mfreq = [(GroupName ModeKind
RANGED, 1), (GroupName ModeKind
AMBUSH, 1), (GroupName ModeKind
CAMPAIGN_SCENARIO, 1)]
, mtutorial :: Bool
mtutorial = Bool
False
, mroster :: Roster
mroster = Roster
rosterAmbush
, mcaves :: Caves
mcaves = Caves
cavesAmbush
, mendMsg :: [(Outcome, Text)]
mendMsg = []
, mrules :: Text
mrules = Text -> [Text] -> Text
T.intercalate "\n"
[ "* One level only"
, "* Three heroes with concurrent attacks vs. Unidentified foes"
, "* Minimize losses"
, "* Assert control of the situation ASAP"
]
, mdesc :: Text
mdesc = "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 = "In this adventure, finally, your heroes are able to all use ranged attacks at once, given enough ammunition."
, mhint :: Text
mhint = ""
}
safari :: ModeKind
safari = $WModeKind :: Char
-> Text
-> Freqs ModeKind
-> Bool
-> Roster
-> Caves
-> [(Outcome, Text)]
-> Text
-> Text
-> Text
-> Text
-> ModeKind
ModeKind
{ msymbol :: Char
msymbol = 'f'
, mname :: Text
mname = "safari"
, mfreq :: Freqs ModeKind
mfreq = [(GroupName ModeKind
SAFARI, 1)]
, mtutorial :: Bool
mtutorial = Bool
False
, mroster :: Roster
mroster = Roster
rosterSafari
, mcaves :: Caves
mcaves = Caves
cavesSafari
, mendMsg :: [(Outcome, Text)]
mendMsg = []
, mrules :: Text
mrules = Text -> [Text] -> Text
T.intercalate "\n"
[ "* Three levels"
, "* Many teammates capable of concurrent action vs. Many enemies"
, "* Minimize losses"
, "* Find exit and escape ASAP"
]
, mdesc :: Text
mdesc = "\"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 = "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 = ""
}
dig :: ModeKind
dig = $WModeKind :: Char
-> Text
-> Freqs ModeKind
-> Bool
-> Roster
-> Caves
-> [(Outcome, Text)]
-> Text
-> Text
-> Text
-> Text
-> ModeKind
ModeKind
{ msymbol :: Char
msymbol = 'd'
, mname :: Text
mname = "dig"
, mfreq :: Freqs ModeKind
mfreq = [(GroupName ModeKind
DIG, 1)]
, mtutorial :: Bool
mtutorial = Bool
False
, mroster :: Roster
mroster = Roster
rosterCrawlEmpty
, mcaves :: Caves
mcaves = Caves
cavesDig
, mendMsg :: [(Outcome, Text)]
mendMsg = []
, mrules :: Text
mrules = ""
, mdesc :: Text
mdesc = "Delve deeper!"
, mreason :: Text
mreason = ""
, mhint :: Text
mhint = ""
}
see :: ModeKind
see = $WModeKind :: Char
-> Text
-> Freqs ModeKind
-> Bool
-> Roster
-> Caves
-> [(Outcome, Text)]
-> Text
-> Text
-> Text
-> Text
-> ModeKind
ModeKind
{ msymbol :: Char
msymbol = 'a'
, mname :: Text
mname = "see"
, mfreq :: Freqs ModeKind
mfreq = [(GroupName ModeKind
SEE, 1)]
, mtutorial :: Bool
mtutorial = Bool
False
, mroster :: Roster
mroster = Roster
rosterCrawlEmpty
, mcaves :: Caves
mcaves = Caves
cavesSee
, mendMsg :: [(Outcome, Text)]
mendMsg = []
, mrules :: Text
mrules = ""
, mdesc :: Text
mdesc = "See all!"
, mreason :: Text
mreason = ""
, mhint :: Text
mhint = ""
}
short :: ModeKind
short = $WModeKind :: Char
-> Text
-> Freqs ModeKind
-> Bool
-> Roster
-> Caves
-> [(Outcome, Text)]
-> Text
-> Text
-> Text
-> Text
-> ModeKind
ModeKind
{ msymbol :: Char
msymbol = 's'
, mname :: Text
mname = "short"
, mfreq :: Freqs ModeKind
mfreq = [(GroupName ModeKind
SHORT, 1)]
, mtutorial :: Bool
mtutorial = Bool
False
, mroster :: Roster
mroster = Roster
rosterCrawlEmpty
, mcaves :: Caves
mcaves = Caves
cavesShort
, mendMsg :: [(Outcome, Text)]
mendMsg = []
, mrules :: Text
mrules = ""
, mdesc :: Text
mdesc = "See all short scenarios!"
, mreason :: Text
mreason = ""
, mhint :: Text
mhint = ""
}
crawlEmpty :: ModeKind
crawlEmpty = $WModeKind :: Char
-> Text
-> Freqs ModeKind
-> Bool
-> Roster
-> Caves
-> [(Outcome, Text)]
-> Text
-> Text
-> Text
-> Text
-> ModeKind
ModeKind
{ msymbol :: Char
msymbol = 'c'
, mname :: Text
mname = "crawl empty"
, mfreq :: Freqs ModeKind
mfreq = [(GroupName ModeKind
CRAWL_EMPTY, 1)]
, mtutorial :: Bool
mtutorial = Bool
False
, mroster :: Roster
mroster = Roster
rosterCrawlEmpty
, mcaves :: Caves
mcaves = Caves
cavesCrawlEmpty
, mendMsg :: [(Outcome, Text)]
mendMsg = []
, mrules :: Text
mrules = ""
, mdesc :: Text
mdesc = "Enjoy the extra legroom."
, mreason :: Text
mreason = ""
, mhint :: Text
mhint = ""
}
crawlSurvival :: ModeKind
crawlSurvival = $WModeKind :: Char
-> Text
-> Freqs ModeKind
-> Bool
-> Roster
-> Caves
-> [(Outcome, Text)]
-> Text
-> Text
-> Text
-> Text
-> ModeKind
ModeKind
{ msymbol :: Char
msymbol = 'd'
, mname :: Text
mname = "crawl survival"
, mfreq :: Freqs ModeKind
mfreq = [(GroupName ModeKind
CRAWL_SURVIVAL, 1)]
, mtutorial :: Bool
mtutorial = Bool
False
, mroster :: Roster
mroster = Roster
rosterCrawlSurvival
, mcaves :: Caves
mcaves = Caves
cavesCrawl
, mendMsg :: [(Outcome, Text)]
mendMsg = []
, mrules :: Text
mrules = ""
, mdesc :: Text
mdesc = "Lure the human intruders deeper and deeper."
, mreason :: Text
mreason = ""
, mhint :: Text
mhint = ""
}
safariSurvival :: ModeKind
safariSurvival = $WModeKind :: Char
-> Text
-> Freqs ModeKind
-> Bool
-> Roster
-> Caves
-> [(Outcome, Text)]
-> Text
-> Text
-> Text
-> Text
-> ModeKind
ModeKind
{ msymbol :: Char
msymbol = 'u'
, mname :: Text
mname = "safari survival"
, mfreq :: Freqs ModeKind
mfreq = [(GroupName ModeKind
SAFARI_SURVIVAL, 1)]
, mtutorial :: Bool
mtutorial = Bool
False
, mroster :: Roster
mroster = Roster
rosterSafariSurvival
, mcaves :: Caves
mcaves = Caves
cavesSafari
, mendMsg :: [(Outcome, Text)]
mendMsg = []
, mrules :: Text
mrules = ""
, mdesc :: Text
mdesc = "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 = ""
, mhint :: Text
mhint = ""
}
battle :: ModeKind
battle = $WModeKind :: Char
-> Text
-> Freqs ModeKind
-> Bool
-> Roster
-> Caves
-> [(Outcome, Text)]
-> Text
-> Text
-> Text
-> Text
-> ModeKind
ModeKind
{ msymbol :: Char
msymbol = 'b'
, mname :: Text
mname = "battle"
, mfreq :: Freqs ModeKind
mfreq = [(GroupName ModeKind
BATTLE, 1)]
, mtutorial :: Bool
mtutorial = Bool
False
, mroster :: Roster
mroster = Roster
rosterBattle
, mcaves :: Caves
mcaves = Caves
cavesBattle
, mendMsg :: [(Outcome, Text)]
mendMsg = []
, mrules :: Text
mrules = ""
, mdesc :: Text
mdesc = "Odds are stacked against those that unleash the horrors of abstraction."
, mreason :: Text
mreason = ""
, mhint :: Text
mhint = ""
}
battleDefense :: ModeKind
battleDefense = $WModeKind :: Char
-> Text
-> Freqs ModeKind
-> Bool
-> Roster
-> Caves
-> [(Outcome, Text)]
-> Text
-> Text
-> Text
-> Text
-> ModeKind
ModeKind
{ msymbol :: Char
msymbol = 'f'
, mname :: Text
mname = "battle defense"
, mfreq :: Freqs ModeKind
mfreq = [(GroupName ModeKind
BATTLE_DEFENSE, 1)]
, mtutorial :: Bool
mtutorial = Bool
False
, mroster :: Roster
mroster = Roster
rosterBattleDefense
, mcaves :: Caves
mcaves = Caves
cavesBattle
, mendMsg :: [(Outcome, Text)]
mendMsg = []
, mrules :: Text
mrules = ""
, mdesc :: Text
mdesc = "Odds are stacked for those that breathe mathematics."
, mreason :: Text
mreason = ""
, mhint :: Text
mhint = ""
}
battleSurvival :: ModeKind
battleSurvival = $WModeKind :: Char
-> Text
-> Freqs ModeKind
-> Bool
-> Roster
-> Caves
-> [(Outcome, Text)]
-> Text
-> Text
-> Text
-> Text
-> ModeKind
ModeKind
{ msymbol :: Char
msymbol = 'i'
, mname :: Text
mname = "battle survival"
, mfreq :: Freqs ModeKind
mfreq = [(GroupName ModeKind
BATTLE_SURVIVAL, 1)]
, mtutorial :: Bool
mtutorial = Bool
False
, mroster :: Roster
mroster = Roster
rosterBattleSurvival
, mcaves :: Caves
mcaves = Caves
cavesBattle
, mendMsg :: [(Outcome, Text)]
mendMsg = []
, mrules :: Text
mrules = ""
, mdesc :: Text
mdesc = "Odds are stacked for those that ally with the strongest."
, mreason :: Text
mreason = ""
, mhint :: Text
mhint = ""
}
defense :: ModeKind
defense = $WModeKind :: Char
-> Text
-> Freqs ModeKind
-> Bool
-> Roster
-> Caves
-> [(Outcome, Text)]
-> Text
-> Text
-> Text
-> Text
-> ModeKind
ModeKind
{ msymbol :: Char
msymbol = 'e'
, mname :: Text
mname = "defense"
, mfreq :: Freqs ModeKind
mfreq = [(GroupName ModeKind
DEFENSE, 1)]
, mtutorial :: Bool
mtutorial = Bool
False
, mroster :: Roster
mroster = Roster
rosterDefense
, mcaves :: Caves
mcaves = Caves
cavesCrawl
, mendMsg :: [(Outcome, Text)]
mendMsg = []
, mrules :: Text
mrules = ""
, mdesc :: Text
mdesc = "Don't let human interlopers defile your abstract secrets and flee unpunished!"
, mreason :: Text
mreason = "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 = ""
}
defenseEmpty :: ModeKind
defenseEmpty = $WModeKind :: Char
-> Text
-> Freqs ModeKind
-> Bool
-> Roster
-> Caves
-> [(Outcome, Text)]
-> Text
-> Text
-> Text
-> Text
-> ModeKind
ModeKind
{ msymbol :: Char
msymbol = 'e'
, mname :: Text
mname = "defense empty"
, mfreq :: Freqs ModeKind
mfreq = [(GroupName ModeKind
DEFENSE_EMPTY, 1)]
, mtutorial :: Bool
mtutorial = Bool
False
, mroster :: Roster
mroster = Roster
rosterDefenseEmpty
, mcaves :: Caves
mcaves = Caves
cavesCrawlEmpty
, mendMsg :: [(Outcome, Text)]
mendMsg = []
, mrules :: Text
mrules = ""
, mdesc :: Text
mdesc = "Lord over empty halls."
, mreason :: Text
mreason = ""
, mhint :: Text
mhint = ""
}
screensaverRaid :: ModeKind
screensaverRaid = AutoLeader -> ModeKind -> ModeKind
screensave (Bool -> Bool -> AutoLeader
AutoLeader Bool
False Bool
False) (ModeKind -> ModeKind) -> ModeKind -> ModeKind
forall a b. (a -> b) -> a -> b
$ ModeKind
raid
{ mname :: Text
mname = "auto-raid (1)"
, mfreq :: Freqs ModeKind
mfreq = [(GroupName ModeKind
INSERT_COIN, 2), (GroupName ModeKind
NO_CONFIRMS, 1)]
}
screensaverBrawl :: ModeKind
screensaverBrawl = AutoLeader -> ModeKind -> ModeKind
screensave (Bool -> Bool -> AutoLeader
AutoLeader Bool
False Bool
False) (ModeKind -> ModeKind) -> ModeKind -> ModeKind
forall a b. (a -> b) -> a -> b
$ ModeKind
brawl
{ mname :: Text
mname = "auto-brawl (2)"
, mfreq :: Freqs ModeKind
mfreq = [(GroupName ModeKind
NO_CONFIRMS, 1)]
}
screensaverCrawl :: ModeKind
screensaverCrawl = AutoLeader -> ModeKind -> ModeKind
screensave (Bool -> Bool -> AutoLeader
AutoLeader Bool
False Bool
False) (ModeKind -> ModeKind) -> ModeKind -> ModeKind
forall a b. (a -> b) -> a -> b
$ ModeKind
crawl
{ mname :: Text
mname = "auto-crawl (long)"
, mfreq :: Freqs ModeKind
mfreq = [(GroupName ModeKind
NO_CONFIRMS, 1)]
}
screensaverShootout :: ModeKind
screensaverShootout = AutoLeader -> ModeKind -> ModeKind
screensave (Bool -> Bool -> AutoLeader
AutoLeader Bool
False Bool
False) (ModeKind -> ModeKind) -> ModeKind -> ModeKind
forall a b. (a -> b) -> a -> b
$ ModeKind
shootout
{ mname :: Text
mname = "auto-shootout (3)"
, mfreq :: Freqs ModeKind
mfreq = [(GroupName ModeKind
INSERT_COIN, 2), (GroupName ModeKind
NO_CONFIRMS, 1)]
}
screensaverHunt :: ModeKind
screensaverHunt = AutoLeader -> ModeKind -> ModeKind
screensave (Bool -> Bool -> AutoLeader
AutoLeader Bool
False Bool
False) (ModeKind -> ModeKind) -> ModeKind -> ModeKind
forall a b. (a -> b) -> a -> b
$ ModeKind
hunt
{ mname :: Text
mname = "auto-hunt (4)"
, mfreq :: Freqs ModeKind
mfreq = [(GroupName ModeKind
INSERT_COIN, 2), (GroupName ModeKind
NO_CONFIRMS, 1)]
}
screensaverEscape :: ModeKind
screensaverEscape = AutoLeader -> ModeKind -> ModeKind
screensave (Bool -> Bool -> AutoLeader
AutoLeader Bool
False Bool
False) (ModeKind -> ModeKind) -> ModeKind -> ModeKind
forall a b. (a -> b) -> a -> b
$ ModeKind
escape
{ mname :: Text
mname = "auto-escape (5)"
, mfreq :: Freqs ModeKind
mfreq = [(GroupName ModeKind
INSERT_COIN, 2), (GroupName ModeKind
NO_CONFIRMS, 1)]
}
screensaverZoo :: ModeKind
screensaverZoo = AutoLeader -> ModeKind -> ModeKind
screensave (Bool -> Bool -> AutoLeader
AutoLeader Bool
False Bool
False) (ModeKind -> ModeKind) -> ModeKind -> ModeKind
forall a b. (a -> b) -> a -> b
$ ModeKind
zoo
{ mname :: Text
mname = "auto-zoo (6)"
, mfreq :: Freqs ModeKind
mfreq = [(GroupName ModeKind
NO_CONFIRMS, 1)]
}
screensaverAmbush :: ModeKind
screensaverAmbush = AutoLeader -> ModeKind -> ModeKind
screensave (Bool -> Bool -> AutoLeader
AutoLeader Bool
False Bool
False) (ModeKind -> ModeKind) -> ModeKind -> ModeKind
forall a b. (a -> b) -> a -> b
$ ModeKind
ambush
{ mname :: Text
mname = "auto-ambush (7)"
, mfreq :: Freqs ModeKind
mfreq = [(GroupName ModeKind
NO_CONFIRMS, 1)]
}
screensaverSafari :: ModeKind
screensaverSafari = AutoLeader -> ModeKind -> ModeKind
screensave (Bool -> Bool -> AutoLeader
AutoLeader Bool
False Bool
True) (ModeKind -> ModeKind) -> ModeKind -> ModeKind
forall a b. (a -> b) -> a -> b
$ ModeKind
safari
{ mname :: Text
mname = "auto-safari"
, mfreq :: Freqs ModeKind
mfreq = [(GroupName ModeKind
INSERT_COIN, 1), (GroupName ModeKind
NO_CONFIRMS, 1)]
}
teamCompetitor, teamCivilian :: TeamContinuity
teamCompetitor :: TeamContinuity
teamCompetitor = Int -> TeamContinuity
TeamContinuity 2
teamCivilian :: TeamContinuity
teamCivilian = Int -> TeamContinuity
TeamContinuity 3
rosterRaid, rosterBrawl, rosterCrawl, rosterShootout, rosterHunt, rosterEscape, rosterZoo, rosterAmbush, rosterSafari, rosterCrawlEmpty, rosterCrawlSurvival, rosterSafariSurvival, rosterBattle, rosterBattleDefense, rosterBattleSurvival, rosterDefense, rosterDefenseEmpty :: Roster
rosterRaid :: Roster
rosterRaid = $WRoster :: [(Player, Maybe TeamContinuity, [(Int, Dice, GroupName ItemKind)])]
-> [(Text, Text)] -> [(Text, Text)] -> Roster
Roster
{ rosterList :: [(Player, Maybe TeamContinuity, [(Int, Dice, GroupName ItemKind)])]
rosterList = [ ( Player
playerHero {fhiCondPoly :: HiCondPoly
fhiCondPoly = HiCondPoly
hiHeroShort}
, TeamContinuity -> Maybe TeamContinuity
forall a. a -> Maybe a
Just TeamContinuity
teamExplorer
, [(-2, 2, GroupName ItemKind
HERO)] )
, ( Player
playerAntiHero { fname :: Text
fname = "Indigo Founder"
, fhiCondPoly :: HiCondPoly
fhiCondPoly = HiCondPoly
hiHeroShort }
, TeamContinuity -> Maybe TeamContinuity
forall a. a -> Maybe a
Just TeamContinuity
teamCompetitor
, [(-2, 1, GroupName ItemKind
HERO)] )
, ( Player
playerAnimal
, Maybe TeamContinuity
forall a. Maybe a
Nothing
, [(-2, 2, GroupName ItemKind
ANIMAL)] )
, (Player
playerHorror, Maybe TeamContinuity
forall a. Maybe a
Nothing, []) ]
, rosterEnemy :: [(Text, Text)]
rosterEnemy = [ ("Explorer", "Animal Kingdom")
, ("Explorer", "Horror Den")
, ("Indigo Founder", "Animal Kingdom")
, ("Indigo Founder", "Horror Den") ]
, rosterAlly :: [(Text, Text)]
rosterAlly = [] }
rosterBrawl :: Roster
rosterBrawl = $WRoster :: [(Player, Maybe TeamContinuity, [(Int, Dice, GroupName ItemKind)])]
-> [(Text, Text)] -> [(Text, Text)] -> Roster
Roster
{ rosterList :: [(Player, Maybe TeamContinuity, [(Int, Dice, GroupName ItemKind)])]
rosterList = [ ( Player
playerHero { fcanEscape :: Bool
fcanEscape = Bool
False
, fhiCondPoly :: HiCondPoly
fhiCondPoly = HiCondPoly
hiHeroMedium }
, TeamContinuity -> Maybe TeamContinuity
forall a. a -> Maybe a
Just TeamContinuity
teamExplorer
, [(-2, 3, GroupName ItemKind
BRAWLER_HERO)] )
, ( Player
playerAntiHero { fname :: Text
fname = "Indigo Researcher"
, fcanEscape :: Bool
fcanEscape = Bool
False
, fhiCondPoly :: HiCondPoly
fhiCondPoly = HiCondPoly
hiHeroMedium }
, TeamContinuity -> Maybe TeamContinuity
forall a. a -> Maybe a
Just TeamContinuity
teamCompetitor
, [(-2, 3, GroupName ItemKind
BRAWLER_HERO)] )
, (Player
playerHorror, Maybe TeamContinuity
forall a. Maybe a
Nothing, []) ]
, rosterEnemy :: [(Text, Text)]
rosterEnemy = [ ("Explorer", "Indigo Researcher")
, ("Explorer", "Horror Den")
, ("Indigo Researcher", "Horror Den") ]
, rosterAlly :: [(Text, Text)]
rosterAlly = [] }
rosterCrawl :: Roster
rosterCrawl = $WRoster :: [(Player, Maybe TeamContinuity, [(Int, Dice, GroupName ItemKind)])]
-> [(Text, Text)] -> [(Text, Text)] -> Roster
Roster
{ rosterList :: [(Player, Maybe TeamContinuity, [(Int, Dice, GroupName ItemKind)])]
rosterList = [ ( Player
playerHero
, TeamContinuity -> Maybe TeamContinuity
forall a. a -> Maybe a
Just TeamContinuity
teamExplorer
, [(-1, 3, GroupName ItemKind
HERO)] )
, ( Player
playerMonster
, Maybe TeamContinuity
forall a. Maybe a
Nothing
, [(-4, 1, GroupName ItemKind
SCOUT_MONSTER), (-4, 3, GroupName ItemKind
MONSTER)] )
, ( Player
playerAnimal
, Maybe TeamContinuity
forall a. Maybe a
Nothing
,
[ (-1, 1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 2, GroupName ItemKind
ANIMAL)
, (-10, 100, GroupName ItemKind
MOBILE_ANIMAL) ] ) ]
, rosterEnemy :: [(Text, Text)]
rosterEnemy = [ ("Explorer", "Monster Hive")
, ("Explorer", "Animal Kingdom") ]
, rosterAlly :: [(Text, Text)]
rosterAlly = [("Monster Hive", "Animal Kingdom")] }
rosterShootout :: Roster
rosterShootout = $WRoster :: [(Player, Maybe TeamContinuity, [(Int, Dice, GroupName ItemKind)])]
-> [(Text, Text)] -> [(Text, Text)] -> Roster
Roster
{ rosterList :: [(Player, Maybe TeamContinuity, [(Int, Dice, GroupName ItemKind)])]
rosterList = [ ( Player
playerHero { fcanEscape :: Bool
fcanEscape = Bool
False
, fhiCondPoly :: HiCondPoly
fhiCondPoly = HiCondPoly
hiHeroMedium }
, TeamContinuity -> Maybe TeamContinuity
forall a. a -> Maybe a
Just TeamContinuity
teamExplorer
, [(-5, 2, GroupName ItemKind
RANGER_HERO), (-5, 1, GroupName ItemKind
SCOUT_HERO)] )
, ( Player
playerAntiHero { fname :: Text
fname = "Indigo Researcher"
, fcanEscape :: Bool
fcanEscape = Bool
False
, fhiCondPoly :: HiCondPoly
fhiCondPoly = HiCondPoly
hiHeroMedium }
, TeamContinuity -> Maybe TeamContinuity
forall a. a -> Maybe a
Just TeamContinuity
teamCompetitor
, [(-5, 2, GroupName ItemKind
RANGER_HERO), (-5, 1, GroupName ItemKind
SCOUT_HERO)] )
, (Player
playerHorror, Maybe TeamContinuity
forall a. Maybe a
Nothing, []) ]
, rosterEnemy :: [(Text, Text)]
rosterEnemy = [ ("Explorer", "Indigo Researcher")
, ("Explorer", "Horror Den")
, ("Indigo Researcher", "Horror Den") ]
, rosterAlly :: [(Text, Text)]
rosterAlly = [] }
rosterHunt :: Roster
rosterHunt = $WRoster :: [(Player, Maybe TeamContinuity, [(Int, Dice, GroupName ItemKind)])]
-> [(Text, Text)] -> [(Text, Text)] -> Roster
Roster
{ rosterList :: [(Player, Maybe TeamContinuity, [(Int, Dice, GroupName ItemKind)])]
rosterList = [ ( Player
playerHero { fcanEscape :: Bool
fcanEscape = Bool
False
, fhiCondPoly :: HiCondPoly
fhiCondPoly = HiCondPoly
hiHeroMedium }
, TeamContinuity -> Maybe TeamContinuity
forall a. a -> Maybe a
Just TeamContinuity
teamExplorer
, [(-6, 7, GroupName ItemKind
SOLDIER_HERO)] )
, ( Player
playerAntiHero { fname :: Text
fname = "Indigo Researcher"
, fcanEscape :: Bool
fcanEscape = Bool
False
, fhiCondPoly :: HiCondPoly
fhiCondPoly = HiCondPoly
hiHeroMedium }
, TeamContinuity -> Maybe TeamContinuity
forall a. a -> Maybe a
Just TeamContinuity
teamCompetitor
, [(-6, 6, GroupName ItemKind
AMBUSHER_HERO), (-6, 1, GroupName ItemKind
SCOUT_HERO)] )
, (Player
playerHorror, Maybe TeamContinuity
forall a. Maybe a
Nothing, []) ]
, rosterEnemy :: [(Text, Text)]
rosterEnemy = [ ("Explorer", "Indigo Researcher")
, ("Explorer", "Horror Den")
, ("Indigo Researcher", "Horror Den") ]
, rosterAlly :: [(Text, Text)]
rosterAlly = [] }
rosterEscape :: Roster
rosterEscape = $WRoster :: [(Player, Maybe TeamContinuity, [(Int, Dice, GroupName ItemKind)])]
-> [(Text, Text)] -> [(Text, Text)] -> Roster
Roster
{ rosterList :: [(Player, Maybe TeamContinuity, [(Int, Dice, GroupName ItemKind)])]
rosterList = [ ( Player
playerAntiHero { fname :: Text
fname = "Indigo Researcher"
, fcanEscape :: Bool
fcanEscape = Bool
False
, fneverEmpty :: Bool
fneverEmpty = Bool
False
, fhiCondPoly :: HiCondPoly
fhiCondPoly = HiCondPoly
hiHeroMedium }
, TeamContinuity -> Maybe TeamContinuity
forall a. a -> Maybe a
Just TeamContinuity
teamCompetitor
, [(-7, 6, GroupName ItemKind
AMBUSHER_HERO), (-7, 1, GroupName ItemKind
SCOUT_HERO)] )
, ( Player
playerHero {fhiCondPoly :: HiCondPoly
fhiCondPoly = HiCondPoly
hiHeroMedium}
, TeamContinuity -> Maybe TeamContinuity
forall a. a -> Maybe a
Just TeamContinuity
teamExplorer
, [(-7, 2, GroupName ItemKind
ESCAPIST_HERO), (-7, 1, GroupName ItemKind
SCOUT_HERO)] )
, (Player
playerHorror, Maybe TeamContinuity
forall a. Maybe a
Nothing, []) ]
, rosterEnemy :: [(Text, Text)]
rosterEnemy = [ ("Explorer", "Indigo Researcher")
, ("Explorer", "Horror Den")
, ("Indigo Researcher", "Horror Den") ]
, rosterAlly :: [(Text, Text)]
rosterAlly = [] }
rosterZoo :: Roster
rosterZoo = $WRoster :: [(Player, Maybe TeamContinuity, [(Int, Dice, GroupName ItemKind)])]
-> [(Text, Text)] -> [(Text, Text)] -> Roster
Roster
{ rosterList :: [(Player, Maybe TeamContinuity, [(Int, Dice, GroupName ItemKind)])]
rosterList = [ ( Player
playerHero { fcanEscape :: Bool
fcanEscape = Bool
False
, fhiCondPoly :: HiCondPoly
fhiCondPoly = HiCondPoly
hiHeroLong }
, TeamContinuity -> Maybe TeamContinuity
forall a. a -> Maybe a
Just TeamContinuity
teamExplorer
, [(-8, 5, GroupName ItemKind
SOLDIER_HERO)] )
, ( Player
playerAnimal {fneverEmpty :: Bool
fneverEmpty = Bool
True}
, Maybe TeamContinuity
forall a. Maybe a
Nothing
, [(-8, 100, GroupName ItemKind
MOBILE_ANIMAL)] )
, (Player
playerHorror, Maybe TeamContinuity
forall a. Maybe a
Nothing, []) ]
, rosterEnemy :: [(Text, Text)]
rosterEnemy = [ ("Explorer", "Animal Kingdom")
, ("Explorer", "Horror Den") ]
, rosterAlly :: [(Text, Text)]
rosterAlly = [] }
rosterAmbush :: Roster
rosterAmbush = $WRoster :: [(Player, Maybe TeamContinuity, [(Int, Dice, GroupName ItemKind)])]
-> [(Text, Text)] -> [(Text, Text)] -> Roster
Roster
{ rosterList :: [(Player, Maybe TeamContinuity, [(Int, Dice, GroupName ItemKind)])]
rosterList = [ ( Player
playerHero { fcanEscape :: Bool
fcanEscape = Bool
False
, fhiCondPoly :: HiCondPoly
fhiCondPoly = HiCondPoly
hiHeroMedium }
, TeamContinuity -> Maybe TeamContinuity
forall a. a -> Maybe a
Just TeamContinuity
teamExplorer
, [(-9, 5, GroupName ItemKind
AMBUSHER_HERO), (-9, 1, GroupName ItemKind
SCOUT_HERO)] )
, ( Player
playerAntiHero { fname :: Text
fname = "Indigo Researcher"
, fcanEscape :: Bool
fcanEscape = Bool
False
, fhiCondPoly :: HiCondPoly
fhiCondPoly = HiCondPoly
hiHeroMedium }
, TeamContinuity -> Maybe TeamContinuity
forall a. a -> Maybe a
Just TeamContinuity
teamCompetitor
, [(-9, 12, GroupName ItemKind
SOLDIER_HERO)] )
, (Player
playerHorror, Maybe TeamContinuity
forall a. Maybe a
Nothing, []) ]
, rosterEnemy :: [(Text, Text)]
rosterEnemy = [ ("Explorer", "Indigo Researcher")
, ("Explorer", "Horror Den")
, ("Indigo Researcher", "Horror Den") ]
, rosterAlly :: [(Text, Text)]
rosterAlly = [] }
rosterSafari :: Roster
rosterSafari = $WRoster :: [(Player, Maybe TeamContinuity, [(Int, Dice, GroupName ItemKind)])]
-> [(Text, Text)] -> [(Text, Text)] -> Roster
Roster
{ rosterList :: [(Player, Maybe TeamContinuity, [(Int, Dice, GroupName ItemKind)])]
rosterList = [ ( Player
playerMonsterTourist
, Maybe TeamContinuity
forall a. Maybe a
Nothing
, [(-4, 15, GroupName ItemKind
MONSTER)] )
, ( Player
playerHunamConvict
, TeamContinuity -> Maybe TeamContinuity
forall a. a -> Maybe a
Just TeamContinuity
teamCivilian
, [(-4, 2, GroupName ItemKind
CIVILIAN)] )
, ( Player
playerAnimalMagnificent
, Maybe TeamContinuity
forall a. Maybe a
Nothing
, [(-7, 15, GroupName ItemKind
MOBILE_ANIMAL)] )
, ( Player
playerAnimalExquisite
, Maybe TeamContinuity
forall a. Maybe a
Nothing
, [(-10, 20, GroupName ItemKind
MOBILE_ANIMAL)] ) ]
, rosterEnemy :: [(Text, Text)]
rosterEnemy = [ ("Monster Tourist Office", "Hunam Convict")
, ( "Monster Tourist Office"
, "Animal Magnificent Specimen Variety" )
, ( "Monster Tourist Office"
, "Animal Exquisite Herds and Packs Galore" )
, ( "Animal Magnificent Specimen Variety"
, "Hunam Convict" )
, ( "Hunam Convict"
, "Animal Exquisite Herds and Packs Galore" ) ]
, rosterAlly :: [(Text, Text)]
rosterAlly = [ ( "Animal Magnificent Specimen Variety"
, "Animal Exquisite Herds and Packs Galore" ) ] }
rosterCrawlEmpty :: Roster
rosterCrawlEmpty = $WRoster :: [(Player, Maybe TeamContinuity, [(Int, Dice, GroupName ItemKind)])]
-> [(Text, Text)] -> [(Text, Text)] -> Roster
Roster
{ rosterList :: [(Player, Maybe TeamContinuity, [(Int, Dice, GroupName ItemKind)])]
rosterList = [ ( Player
playerHero
, TeamContinuity -> Maybe TeamContinuity
forall a. a -> Maybe a
Just TeamContinuity
teamExplorer
, [(-1, 1, GroupName ItemKind
HERO)] )
, (Player
playerHorror, Maybe TeamContinuity
forall a. Maybe a
Nothing, []) ]
, rosterEnemy :: [(Text, Text)]
rosterEnemy = []
, rosterAlly :: [(Text, Text)]
rosterAlly = [] }
rosterCrawlSurvival :: Roster
rosterCrawlSurvival = Roster
rosterCrawl
{ rosterList :: [(Player, Maybe TeamContinuity, [(Int, Dice, GroupName ItemKind)])]
rosterList = [ ( Player
playerAntiHero
, TeamContinuity -> Maybe TeamContinuity
forall a. a -> Maybe a
Just TeamContinuity
teamExplorer
, [(-1, 3, GroupName ItemKind
HERO)] )
, ( Player
playerMonster
, Maybe TeamContinuity
forall a. Maybe a
Nothing
, [(-4, 1, GroupName ItemKind
SCOUT_MONSTER), (-4, 3, GroupName ItemKind
MONSTER)] )
, ( Player
playerAnimal {fhasUI :: Bool
fhasUI = Bool
True}
, Maybe TeamContinuity
forall a. Maybe a
Nothing
,
[ (-1, 1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 2, GroupName ItemKind
ANIMAL)
, (-10, 100, GroupName ItemKind
MOBILE_ANIMAL) ] ) ] }
rosterSafariSurvival :: Roster
rosterSafariSurvival = Roster
rosterSafari
{ rosterList :: [(Player, Maybe TeamContinuity, [(Int, Dice, GroupName ItemKind)])]
rosterList = [ ( Player
playerMonsterTourist
{ fleaderMode :: LeaderMode
fleaderMode = AutoLeader -> LeaderMode
LeaderAI (AutoLeader -> LeaderMode) -> AutoLeader -> LeaderMode
forall a b. (a -> b) -> a -> b
$ Bool -> Bool -> AutoLeader
AutoLeader Bool
True Bool
True
, fhasUI :: Bool
fhasUI = Bool
False }
, Maybe TeamContinuity
forall a. Maybe a
Nothing
, [(-4, 15, GroupName ItemKind
MONSTER)] )
, ( Player
playerHunamConvict
, TeamContinuity -> Maybe TeamContinuity
forall a. a -> Maybe a
Just TeamContinuity
teamCivilian
, [(-4, 3, GroupName ItemKind
CIVILIAN)] )
, ( Player
playerAnimalMagnificent
{ fleaderMode :: LeaderMode
fleaderMode = AutoLeader -> LeaderMode
LeaderUI (AutoLeader -> LeaderMode) -> AutoLeader -> LeaderMode
forall a b. (a -> b) -> a -> b
$ Bool -> Bool -> AutoLeader
AutoLeader Bool
True Bool
False
, fhasUI :: Bool
fhasUI = Bool
True }
, Maybe TeamContinuity
forall a. Maybe a
Nothing
, [(-7, 20, GroupName ItemKind
MOBILE_ANIMAL)] )
, ( Player
playerAnimalExquisite
, Maybe TeamContinuity
forall a. Maybe a
Nothing
, [(-10, 30, GroupName ItemKind
MOBILE_ANIMAL)] ) ] }
rosterBattle :: Roster
rosterBattle = $WRoster :: [(Player, Maybe TeamContinuity, [(Int, Dice, GroupName ItemKind)])]
-> [(Text, Text)] -> [(Text, Text)] -> Roster
Roster
{ rosterList :: [(Player, Maybe TeamContinuity, [(Int, Dice, GroupName ItemKind)])]
rosterList = [ ( Player
playerHero { fcanEscape :: Bool
fcanEscape = Bool
False
, fhiCondPoly :: HiCondPoly
fhiCondPoly = HiCondPoly
hiHeroLong }
, TeamContinuity -> Maybe TeamContinuity
forall a. a -> Maybe a
Just TeamContinuity
teamExplorer
, [(-5, 5, GroupName ItemKind
SOLDIER_HERO)] )
, ( Player
playerMonster {fneverEmpty :: Bool
fneverEmpty = Bool
True}
, Maybe TeamContinuity
forall a. Maybe a
Nothing
, [(-5, 35, GroupName ItemKind
MOBILE_MONSTER)] )
, ( Player
playerAnimal {fneverEmpty :: Bool
fneverEmpty = Bool
True}
, Maybe TeamContinuity
forall a. Maybe a
Nothing
, [(-5, 30, GroupName ItemKind
MOBILE_ANIMAL)] ) ]
, rosterEnemy :: [(Text, Text)]
rosterEnemy = [ ("Explorer", "Monster Hive")
, ("Explorer", "Animal Kingdom") ]
, rosterAlly :: [(Text, Text)]
rosterAlly = [("Monster Hive", "Animal Kingdom")] }
rosterBattleDefense :: Roster
rosterBattleDefense = Roster
rosterBattle
{ rosterList :: [(Player, Maybe TeamContinuity, [(Int, Dice, GroupName ItemKind)])]
rosterList = [ ( Player
playerHero { fcanEscape :: Bool
fcanEscape = Bool
False
, fhiCondPoly :: HiCondPoly
fhiCondPoly = HiCondPoly
hiHeroLong
, fleaderMode :: LeaderMode
fleaderMode =
AutoLeader -> LeaderMode
LeaderAI (AutoLeader -> LeaderMode) -> AutoLeader -> LeaderMode
forall a b. (a -> b) -> a -> b
$ Bool -> Bool -> AutoLeader
AutoLeader Bool
False Bool
False
, fhasUI :: Bool
fhasUI = Bool
False }
, TeamContinuity -> Maybe TeamContinuity
forall a. a -> Maybe a
Just TeamContinuity
teamExplorer
, [(-5, 5, GroupName ItemKind
SOLDIER_HERO)] )
, ( Player
playerMonster { fneverEmpty :: Bool
fneverEmpty = Bool
True
, fhasUI :: Bool
fhasUI = Bool
True }
, Maybe TeamContinuity
forall a. Maybe a
Nothing
, [(-5, 35, GroupName ItemKind
MOBILE_MONSTER)] )
, ( Player
playerAnimal {fneverEmpty :: Bool
fneverEmpty = Bool
True}
, Maybe TeamContinuity
forall a. Maybe a
Nothing
, [(-5, 30, GroupName ItemKind
MOBILE_ANIMAL)] ) ] }
rosterBattleSurvival :: Roster
rosterBattleSurvival = Roster
rosterBattle
{ rosterList :: [(Player, Maybe TeamContinuity, [(Int, Dice, GroupName ItemKind)])]
rosterList = [ ( Player
playerHero { fcanEscape :: Bool
fcanEscape = Bool
False
, fhiCondPoly :: HiCondPoly
fhiCondPoly = HiCondPoly
hiHeroLong
, fleaderMode :: LeaderMode
fleaderMode =
AutoLeader -> LeaderMode
LeaderAI (AutoLeader -> LeaderMode) -> AutoLeader -> LeaderMode
forall a b. (a -> b) -> a -> b
$ Bool -> Bool -> AutoLeader
AutoLeader Bool
False Bool
False
, fhasUI :: Bool
fhasUI = Bool
False }
, TeamContinuity -> Maybe TeamContinuity
forall a. a -> Maybe a
Just TeamContinuity
teamExplorer
, [(-5, 5, GroupName ItemKind
SOLDIER_HERO)] )
, ( Player
playerMonster {fneverEmpty :: Bool
fneverEmpty = Bool
True}
, Maybe TeamContinuity
forall a. Maybe a
Nothing
, [(-5, 35, GroupName ItemKind
MOBILE_MONSTER)] )
, ( Player
playerAnimal { fneverEmpty :: Bool
fneverEmpty = Bool
True
, fhasUI :: Bool
fhasUI = Bool
True }
, Maybe TeamContinuity
forall a. Maybe a
Nothing
, [(-5, 30, GroupName ItemKind
MOBILE_ANIMAL)] ) ] }
rosterDefense :: Roster
rosterDefense = Roster
rosterCrawl
{ rosterList :: [(Player, Maybe TeamContinuity, [(Int, Dice, GroupName ItemKind)])]
rosterList = [ ( Player
playerAntiHero
, TeamContinuity -> Maybe TeamContinuity
forall a. a -> Maybe a
Just TeamContinuity
teamExplorer
, [(-1, 3, GroupName ItemKind
HERO)] )
, ( Player
playerAntiMonster
, Maybe TeamContinuity
forall a. Maybe a
Nothing
, [(-4, 1, GroupName ItemKind
SCOUT_MONSTER), (-4, 3, GroupName ItemKind
MONSTER)] )
, ( Player
playerAnimal
, Maybe TeamContinuity
forall a. Maybe a
Nothing
, [ (-1, 1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 2, GroupName ItemKind
ANIMAL)
, (-10, 100, GroupName ItemKind
MOBILE_ANIMAL) ] ) ] }
rosterDefenseEmpty :: Roster
rosterDefenseEmpty = Roster
rosterCrawl
{ rosterList :: [(Player, Maybe TeamContinuity, [(Int, Dice, GroupName ItemKind)])]
rosterList = [ ( Player
playerAntiMonster {fneverEmpty :: Bool
fneverEmpty = Bool
True}
, Maybe TeamContinuity
forall a. Maybe a
Nothing
, [(-4, 1, GroupName ItemKind
SCOUT_MONSTER)] )
, (Player
playerHorror, Maybe TeamContinuity
forall a. Maybe a
Nothing, []) ]
, rosterEnemy :: [(Text, Text)]
rosterEnemy = []
, rosterAlly :: [(Text, Text)]
rosterAlly = [] }
cavesRaid, cavesBrawl, cavesCrawl, cavesShootout, cavesHunt, cavesEscape, cavesZoo, cavesAmbush, cavesSafari, cavesDig, cavesSee, cavesShort, cavesCrawlEmpty, cavesBattle :: Caves
cavesRaid :: Caves
cavesRaid = [([-2], [GroupName CaveKind
CAVE_RAID])]
cavesBrawl :: Caves
cavesBrawl = [([-2], [GroupName CaveKind
CAVE_BRAWL])]
listCrawl :: [([Int], [GroupName CaveKind])]
listCrawl :: Caves
listCrawl =
[ ([-1], [GroupName CaveKind
CAVE_OUTERMOST])
, ([-2], [GroupName CaveKind
CAVE_SHALLOW_ROGUE])
, ([-3], [GroupName CaveKind
CAVE_EMPTY])
, ([-4, -5, -6], [GroupName CaveKind
DEFAULT_RANDOM, GroupName CaveKind
CAVE_ROGUE, GroupName CaveKind
CAVE_ARENA])
, ([-7, -8], [GroupName CaveKind
CAVE_ROGUE, GroupName CaveKind
CAVE_SMOKING])
, ([-9], [GroupName CaveKind
CAVE_LABORATORY])
, ([-10], [GroupName CaveKind
CAVE_MINE]) ]
cavesCrawl :: Caves
cavesCrawl = Caves
listCrawl
cavesShootout :: Caves
cavesShootout = [([-5], [GroupName CaveKind
CAVE_SHOOTOUT])]
cavesHunt :: Caves
cavesHunt = [([-6], [GroupName CaveKind
CAVE_HUNT])]
cavesEscape :: Caves
cavesEscape = [([-7], [GroupName CaveKind
CAVE_ESCAPE])]
cavesZoo :: Caves
cavesZoo = [([-8], [GroupName CaveKind
CAVE_ZOO])]
cavesAmbush :: Caves
cavesAmbush = [([-9], [GroupName CaveKind
CAVE_AMBUSH])]
cavesSafari :: Caves
cavesSafari = [ ([-4], [GroupName CaveKind
CAVE_SAFARI_1])
, ([-7], [GroupName CaveKind
CAVE_SAFARI_2])
, ([-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)
[0, -10 ..]
(Int -> Caves -> [Caves]
forall a. Int -> a -> [a]
replicate 100 Caves
listCrawl)
renumberCaves :: Int -> ([Int], [GroupName CaveKind])
-> ([Int], [GroupName CaveKind])
renumberCaves :: Int
-> ([Int], [GroupName CaveKind]) -> ([Int], [GroupName CaveKind])
renumberCaves offset :: Int
offset (ns :: [Int]
ns, l :: [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 n :: a
n c :: 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 [-1, -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 10) [GroupName CaveKind]
allCaves
cavesShort :: Caves
cavesShort = let numberCaves :: a -> a -> ([a], [a])
numberCaves n :: a
n c :: 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 [-1, -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 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 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_ESCAPE, 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 = [([-5], [GroupName CaveKind
CAVE_BATTLE])]