-- | Blast definitions.
module Content.ItemKindBlast
  ( -- * Group name patterns
    pattern S_FIRECRACKER, pattern S_VIOLENT_FRAGMENTATION, pattern S_FRAGMENTATION, pattern S_FOCUSED_FRAGMENTATION, pattern S_VIOLENT_CONCUSSION, pattern S_CONCUSSION, pattern S_FOCUSED_CONCUSSION, pattern S_VIOLENT_FLASH, pattern S_FOCUSED_FLASH, pattern S_GLASS_HAIL, pattern S_FOCUSED_GLASS_HAIL, pattern S_PHEROMONE, pattern S_CALMING_MIST, pattern S_DISTRESSING_ODOR, pattern S_HEALING_MIST, pattern S_HEALING_MIST_2, pattern S_WOUNDING_MIST, pattern S_DISTORTION, pattern S_SMOKE, pattern S_BOILING_WATER, pattern S_GLUE, pattern S_WASTE, pattern S_ANTI_SLOW_MIST, pattern S_ANTIDOTE_MIST, pattern S_SLEEP_MIST, pattern S_DENSE_SHOWER, pattern S_SPARSE_SHOWER, pattern S_MELEE_PROTECTIVE_BALM, pattern S_RANGE_PROTECTIVE_BALM, pattern S_DEFENSELESSNESS_RUNOUT, pattern S_RESOLUTION_DUST, pattern S_HASTE_SPRAY, pattern S_SLOWNESS_MIST, pattern S_EYE_DROP, pattern S_IRON_FILING, pattern S_SMELLY_DROPLET, pattern S_EYE_SHINE, pattern S_WHISKEY_SPRAY, pattern S_YOUTH_SPRINKLE, pattern S_POISON_CLOUD, pattern S_PING_PLASH, pattern S_VIOLENT_BURNING_OIL_2, pattern S_VIOLENT_BURNING_OIL_3, pattern S_VIOLENT_BURNING_OIL_4, pattern S_BURNING_OIL_2, pattern S_BURNING_OIL_3, pattern S_BURNING_OIL_4, pattern S_FOCUSED_BURNING_OIL_2, pattern S_FOCUSED_BURNING_OIL_3, pattern S_FOCUSED_BURNING_OIL_4
  , blastNoStatOf, blastBonusStatOf
  , pattern ARMOR_MISC
  , blastsGNSingleton, blastsGN
  , -- * Content
    blasts
  ) where

import Prelude ()

import Game.LambdaHack.Core.Prelude

import Content.ItemKindTemporary
import Game.LambdaHack.Content.ItemKind
import Game.LambdaHack.Core.Dice
import Game.LambdaHack.Definition.Ability
import Game.LambdaHack.Definition.Color
import Game.LambdaHack.Definition.Defs
import Game.LambdaHack.Definition.Flavour

-- * Group name patterns

blastsGNSingleton :: [GroupName ItemKind]
blastsGNSingleton :: [GroupName ItemKind]
blastsGNSingleton =
       [GroupName ItemKind
S_FIRECRACKER, GroupName ItemKind
S_VIOLENT_FRAGMENTATION, GroupName ItemKind
S_FRAGMENTATION, GroupName ItemKind
S_FOCUSED_FRAGMENTATION, GroupName ItemKind
S_VIOLENT_CONCUSSION, GroupName ItemKind
S_CONCUSSION, GroupName ItemKind
S_FOCUSED_CONCUSSION, GroupName ItemKind
S_VIOLENT_FLASH, GroupName ItemKind
S_FOCUSED_FLASH, GroupName ItemKind
S_GLASS_HAIL, GroupName ItemKind
S_FOCUSED_GLASS_HAIL, GroupName ItemKind
S_PHEROMONE, GroupName ItemKind
S_CALMING_MIST, GroupName ItemKind
S_DISTRESSING_ODOR, GroupName ItemKind
S_HEALING_MIST, GroupName ItemKind
S_HEALING_MIST_2, GroupName ItemKind
S_WOUNDING_MIST, GroupName ItemKind
S_DISTORTION, GroupName ItemKind
S_SMOKE, GroupName ItemKind
S_BOILING_WATER, GroupName ItemKind
S_GLUE, GroupName ItemKind
S_WASTE, GroupName ItemKind
S_ANTI_SLOW_MIST, GroupName ItemKind
S_ANTIDOTE_MIST, GroupName ItemKind
S_SLEEP_MIST, GroupName ItemKind
S_DENSE_SHOWER, GroupName ItemKind
S_SPARSE_SHOWER, GroupName ItemKind
S_MELEE_PROTECTIVE_BALM, GroupName ItemKind
S_RANGE_PROTECTIVE_BALM, GroupName ItemKind
S_DEFENSELESSNESS_RUNOUT, GroupName ItemKind
S_RESOLUTION_DUST, GroupName ItemKind
S_HASTE_SPRAY, GroupName ItemKind
S_SLOWNESS_MIST, GroupName ItemKind
S_EYE_DROP, GroupName ItemKind
S_IRON_FILING, GroupName ItemKind
S_SMELLY_DROPLET, GroupName ItemKind
S_EYE_SHINE, GroupName ItemKind
S_WHISKEY_SPRAY, GroupName ItemKind
S_YOUTH_SPRINKLE, GroupName ItemKind
S_POISON_CLOUD, GroupName ItemKind
S_PING_PLASH, GroupName ItemKind
S_VIOLENT_BURNING_OIL_2, GroupName ItemKind
S_VIOLENT_BURNING_OIL_3, GroupName ItemKind
S_VIOLENT_BURNING_OIL_4, GroupName ItemKind
S_BURNING_OIL_2, GroupName ItemKind
S_BURNING_OIL_3, GroupName ItemKind
S_BURNING_OIL_4, GroupName ItemKind
S_FOCUSED_BURNING_OIL_2, GroupName ItemKind
S_FOCUSED_BURNING_OIL_3, GroupName ItemKind
S_FOCUSED_BURNING_OIL_4]
  [GroupName ItemKind]
-> [GroupName ItemKind] -> [GroupName ItemKind]
forall a. [a] -> [a] -> [a]
++ (Int -> GroupName ItemKind) -> [Int] -> [GroupName ItemKind]
forall a b. (a -> b) -> [a] -> [b]
map Int -> GroupName ItemKind
firecrackerAt [1..4]
  [GroupName ItemKind]
-> [GroupName ItemKind] -> [GroupName ItemKind]
forall a. [a] -> [a] -> [a]
++ (GroupName ItemKind -> GroupName ItemKind)
-> [GroupName ItemKind] -> [GroupName ItemKind]
forall a b. (a -> b) -> [a] -> [b]
map GroupName ItemKind -> GroupName ItemKind
blastNoStatOf [GroupName ItemKind]
noStatGN
  [GroupName ItemKind]
-> [GroupName ItemKind] -> [GroupName ItemKind]
forall a. [a] -> [a] -> [a]
++ (GroupName ItemKind -> GroupName ItemKind)
-> [GroupName ItemKind] -> [GroupName ItemKind]
forall a b. (a -> b) -> [a] -> [b]
map GroupName ItemKind -> GroupName ItemKind
blastBonusStatOf [GroupName ItemKind]
bonusStatGN

pattern S_FIRECRACKER, S_VIOLENT_FRAGMENTATION, S_FRAGMENTATION, S_FOCUSED_FRAGMENTATION, S_VIOLENT_CONCUSSION, S_CONCUSSION, S_FOCUSED_CONCUSSION, S_VIOLENT_FLASH, S_FOCUSED_FLASH, S_GLASS_HAIL, S_FOCUSED_GLASS_HAIL, S_PHEROMONE, S_CALMING_MIST, S_DISTRESSING_ODOR, S_HEALING_MIST, S_HEALING_MIST_2, S_WOUNDING_MIST, S_DISTORTION, S_SMOKE, S_BOILING_WATER, S_GLUE, S_WASTE, S_ANTI_SLOW_MIST, S_ANTIDOTE_MIST, S_SLEEP_MIST, S_DENSE_SHOWER, S_SPARSE_SHOWER, S_MELEE_PROTECTIVE_BALM, S_RANGE_PROTECTIVE_BALM, S_DEFENSELESSNESS_RUNOUT, S_RESOLUTION_DUST, S_HASTE_SPRAY, S_SLOWNESS_MIST, S_EYE_DROP, S_IRON_FILING, S_SMELLY_DROPLET, S_EYE_SHINE, S_WHISKEY_SPRAY, S_YOUTH_SPRINKLE, S_POISON_CLOUD, S_PING_PLASH, S_VIOLENT_BURNING_OIL_2, S_VIOLENT_BURNING_OIL_3, S_VIOLENT_BURNING_OIL_4, S_BURNING_OIL_2, S_BURNING_OIL_3, S_BURNING_OIL_4, S_FOCUSED_BURNING_OIL_2, S_FOCUSED_BURNING_OIL_3, S_FOCUSED_BURNING_OIL_4 :: GroupName ItemKind

blastsGN :: [GroupName ItemKind]
blastsGN :: [GroupName ItemKind]
blastsGN =
       [GroupName ItemKind
ARMOR_MISC]

pattern ARMOR_MISC :: GroupName ItemKind

pattern $bS_FIRECRACKER :: GroupName ItemKind
$mS_FIRECRACKER :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_FIRECRACKER = GroupName "firecracker"
pattern $bS_VIOLENT_FRAGMENTATION :: GroupName ItemKind
$mS_VIOLENT_FRAGMENTATION :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_VIOLENT_FRAGMENTATION = GroupName "violent fragmentation"
pattern $bS_FRAGMENTATION :: GroupName ItemKind
$mS_FRAGMENTATION :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_FRAGMENTATION = GroupName "fragmentation"
pattern $bS_FOCUSED_FRAGMENTATION :: GroupName ItemKind
$mS_FOCUSED_FRAGMENTATION :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_FOCUSED_FRAGMENTATION = GroupName "focused fragmentation"
pattern $bS_VIOLENT_CONCUSSION :: GroupName ItemKind
$mS_VIOLENT_CONCUSSION :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_VIOLENT_CONCUSSION = GroupName "violent concussion"
pattern $bS_CONCUSSION :: GroupName ItemKind
$mS_CONCUSSION :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_CONCUSSION = GroupName "concussion"
pattern $bS_FOCUSED_CONCUSSION :: GroupName ItemKind
$mS_FOCUSED_CONCUSSION :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_FOCUSED_CONCUSSION = GroupName "focused concussion"
pattern $bS_VIOLENT_FLASH :: GroupName ItemKind
$mS_VIOLENT_FLASH :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_VIOLENT_FLASH = GroupName "violent flash"
pattern $bS_FOCUSED_FLASH :: GroupName ItemKind
$mS_FOCUSED_FLASH :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_FOCUSED_FLASH = GroupName "focused flash"
pattern $bS_GLASS_HAIL :: GroupName ItemKind
$mS_GLASS_HAIL :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_GLASS_HAIL = GroupName "glass hail"
pattern $bS_FOCUSED_GLASS_HAIL :: GroupName ItemKind
$mS_FOCUSED_GLASS_HAIL :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_FOCUSED_GLASS_HAIL = GroupName "focused glass hail"
pattern $bS_PHEROMONE :: GroupName ItemKind
$mS_PHEROMONE :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_PHEROMONE = GroupName "pheromone"
pattern $bS_CALMING_MIST :: GroupName ItemKind
$mS_CALMING_MIST :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_CALMING_MIST = GroupName "calming mist"
pattern $bS_DISTRESSING_ODOR :: GroupName ItemKind
$mS_DISTRESSING_ODOR :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_DISTRESSING_ODOR = GroupName "distressing odor"
pattern $bS_HEALING_MIST :: GroupName ItemKind
$mS_HEALING_MIST :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_HEALING_MIST = GroupName "healing mist"
pattern $bS_HEALING_MIST_2 :: GroupName ItemKind
$mS_HEALING_MIST_2 :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_HEALING_MIST_2 = GroupName "strong healing mist"
pattern $bS_WOUNDING_MIST :: GroupName ItemKind
$mS_WOUNDING_MIST :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_WOUNDING_MIST = GroupName "wounding mist"
pattern $bS_DISTORTION :: GroupName ItemKind
$mS_DISTORTION :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_DISTORTION = GroupName "distortion"
pattern $bS_SMOKE :: GroupName ItemKind
$mS_SMOKE :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_SMOKE = GroupName "smoke"
pattern $bS_BOILING_WATER :: GroupName ItemKind
$mS_BOILING_WATER :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_BOILING_WATER = GroupName "boiling water"
pattern $bS_GLUE :: GroupName ItemKind
$mS_GLUE :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_GLUE = GroupName "glue"
pattern $bS_WASTE :: GroupName ItemKind
$mS_WASTE :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_WASTE = GroupName "waste"
pattern $bS_ANTI_SLOW_MIST :: GroupName ItemKind
$mS_ANTI_SLOW_MIST :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_ANTI_SLOW_MIST = GroupName "anti-slow mist"
pattern $bS_ANTIDOTE_MIST :: GroupName ItemKind
$mS_ANTIDOTE_MIST :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_ANTIDOTE_MIST = GroupName "antidote mist"
pattern $bS_SLEEP_MIST :: GroupName ItemKind
$mS_SLEEP_MIST :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_SLEEP_MIST = GroupName "sleep mist"
pattern $bS_DENSE_SHOWER :: GroupName ItemKind
$mS_DENSE_SHOWER :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_DENSE_SHOWER = GroupName "dense shower"
pattern $bS_SPARSE_SHOWER :: GroupName ItemKind
$mS_SPARSE_SHOWER :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_SPARSE_SHOWER = GroupName "sparse shower"
pattern $bS_MELEE_PROTECTIVE_BALM :: GroupName ItemKind
$mS_MELEE_PROTECTIVE_BALM :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_MELEE_PROTECTIVE_BALM = GroupName "melee protective balm"
pattern $bS_RANGE_PROTECTIVE_BALM :: GroupName ItemKind
$mS_RANGE_PROTECTIVE_BALM :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_RANGE_PROTECTIVE_BALM = GroupName "ranged protective balm"
pattern $bS_DEFENSELESSNESS_RUNOUT :: GroupName ItemKind
$mS_DEFENSELESSNESS_RUNOUT :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_DEFENSELESSNESS_RUNOUT = GroupName "PhD defense question"
pattern $bS_RESOLUTION_DUST :: GroupName ItemKind
$mS_RESOLUTION_DUST :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_RESOLUTION_DUST = GroupName "resolution dust"
pattern $bS_HASTE_SPRAY :: GroupName ItemKind
$mS_HASTE_SPRAY :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_HASTE_SPRAY = GroupName "haste spray"
pattern $bS_SLOWNESS_MIST :: GroupName ItemKind
$mS_SLOWNESS_MIST :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_SLOWNESS_MIST = GroupName "slowness mist"
pattern $bS_EYE_DROP :: GroupName ItemKind
$mS_EYE_DROP :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_EYE_DROP = GroupName "eye drop"
pattern $bS_IRON_FILING :: GroupName ItemKind
$mS_IRON_FILING :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_IRON_FILING = GroupName "iron filing"
pattern $bS_SMELLY_DROPLET :: GroupName ItemKind
$mS_SMELLY_DROPLET :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_SMELLY_DROPLET = GroupName "smelly droplet"
pattern $bS_EYE_SHINE :: GroupName ItemKind
$mS_EYE_SHINE :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_EYE_SHINE = GroupName "eye shine"
pattern $bS_WHISKEY_SPRAY :: GroupName ItemKind
$mS_WHISKEY_SPRAY :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_WHISKEY_SPRAY = GroupName "whiskey spray"
pattern $bS_YOUTH_SPRINKLE :: GroupName ItemKind
$mS_YOUTH_SPRINKLE :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_YOUTH_SPRINKLE = GroupName "youth sprinkle"
pattern $bS_POISON_CLOUD :: GroupName ItemKind
$mS_POISON_CLOUD :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_POISON_CLOUD = GroupName "poison cloud"
pattern $bS_PING_PLASH :: GroupName ItemKind
$mS_PING_PLASH :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_PING_PLASH = GroupName "ping and flash"
pattern $bS_VIOLENT_BURNING_OIL_2 :: GroupName ItemKind
$mS_VIOLENT_BURNING_OIL_2 :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_VIOLENT_BURNING_OIL_2 = GroupName "violent burning oil 2"
pattern $bS_VIOLENT_BURNING_OIL_3 :: GroupName ItemKind
$mS_VIOLENT_BURNING_OIL_3 :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_VIOLENT_BURNING_OIL_3 = GroupName "violent burning oil 3"
pattern $bS_VIOLENT_BURNING_OIL_4 :: GroupName ItemKind
$mS_VIOLENT_BURNING_OIL_4 :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_VIOLENT_BURNING_OIL_4 = GroupName "violent burning oil 4"
pattern $bS_BURNING_OIL_2 :: GroupName ItemKind
$mS_BURNING_OIL_2 :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_BURNING_OIL_2 = GroupName "burning oil 2"
pattern $bS_BURNING_OIL_3 :: GroupName ItemKind
$mS_BURNING_OIL_3 :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_BURNING_OIL_3 = GroupName "burning oil 3"
pattern $bS_BURNING_OIL_4 :: GroupName ItemKind
$mS_BURNING_OIL_4 :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_BURNING_OIL_4 = GroupName "burning oil 4"
pattern $bS_FOCUSED_BURNING_OIL_2 :: GroupName ItemKind
$mS_FOCUSED_BURNING_OIL_2 :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_FOCUSED_BURNING_OIL_2 = GroupName "focused burning oil 2"
pattern $bS_FOCUSED_BURNING_OIL_3 :: GroupName ItemKind
$mS_FOCUSED_BURNING_OIL_3 :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_FOCUSED_BURNING_OIL_3 = GroupName "focused burning oil 3"
pattern $bS_FOCUSED_BURNING_OIL_4 :: GroupName ItemKind
$mS_FOCUSED_BURNING_OIL_4 :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
S_FOCUSED_BURNING_OIL_4 = GroupName "focused burning oil 4"

firecrackerAt :: Int -> GroupName ItemKind
firecrackerAt :: Int -> GroupName ItemKind
firecrackerAt n :: Int
n = Text -> GroupName ItemKind
forall a. Text -> GroupName a
GroupName (Text -> GroupName ItemKind) -> Text -> GroupName ItemKind
forall a b. (a -> b) -> a -> b
$ "firecracker" Text -> Text -> Text
<+> Int -> Text
forall a. Show a => a -> Text
tshow Int
n

blastNoStatOf :: GroupName ItemKind -> GroupName ItemKind
blastNoStatOf :: GroupName ItemKind -> GroupName ItemKind
blastNoStatOf grp :: GroupName ItemKind
grp = Text -> GroupName ItemKind
forall a. Text -> GroupName a
GroupName (Text -> GroupName ItemKind) -> Text -> GroupName ItemKind
forall a b. (a -> b) -> a -> b
$ GroupName ItemKind -> Text
forall a. GroupName a -> Text
fromGroupName GroupName ItemKind
grp Text -> Text -> Text
<+> "mist"

blastBonusStatOf :: GroupName ItemKind -> GroupName ItemKind
blastBonusStatOf :: GroupName ItemKind -> GroupName ItemKind
blastBonusStatOf grp :: GroupName ItemKind
grp = Text -> GroupName ItemKind
forall a. Text -> GroupName a
GroupName (Text -> GroupName ItemKind) -> Text -> GroupName ItemKind
forall a b. (a -> b) -> a -> b
$ GroupName ItemKind -> Text
forall a. GroupName a -> Text
fromGroupName GroupName ItemKind
grp Text -> Text -> Text
<+> "dew"

pattern $bARMOR_MISC :: GroupName ItemKind
$mARMOR_MISC :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
ARMOR_MISC = GroupName "miscellaneous armor"

-- * Content

blasts :: [ItemKind]
blasts :: [ItemKind]
blasts =
  [ItemKind
spreadBurningOil2, ItemKind
spreadBurningOil3, ItemKind
spreadBurningOil4, ItemKind
spreadBurningOil82, ItemKind
spreadBurningOil83, ItemKind
spreadBurningOil84, ItemKind
focusedBurningOil2, ItemKind
focusedBurningOil3, ItemKind
focusedBurningOil4, ItemKind
firecracker1, ItemKind
firecracker2, ItemKind
firecracker3, ItemKind
firecracker4, ItemKind
firecracker5, ItemKind
spreadFragmentation, ItemKind
spreadFragmentation8, ItemKind
focusedFragmentation, ItemKind
spreadConcussion, ItemKind
spreadConcussion8, ItemKind
focusedConcussion, ItemKind
spreadFlash, ItemKind
spreadFlash8, ItemKind
focusedFlash, ItemKind
singleSpark, ItemKind
glassPiece, ItemKind
focusedGlass, ItemKind
fragrance, ItemKind
pheromone, ItemKind
mistCalming, ItemKind
odorDistressing, ItemKind
mistHealing, ItemKind
mistHealing2, ItemKind
mistWounding, ItemKind
distortion, ItemKind
smoke, ItemKind
boilingWater, ItemKind
glue, ItemKind
waste, ItemKind
mistAntiSlow, ItemKind
mistAntidote, ItemKind
mistSleep, ItemKind
denseShower, ItemKind
sparseShower, ItemKind
protectingBalmMelee, ItemKind
protectingBalmRanged, ItemKind
defenselessnessRunout, ItemKind
resolutionDust, ItemKind
hasteSpray, ItemKind
slownessMist, ItemKind
eyeDrop, ItemKind
ironFiling, ItemKind
smellyDroplet, ItemKind
eyeShine, ItemKind
whiskeySpray, ItemKind
youthSprinkle, ItemKind
poisonCloud, ItemKind
pingFlash, ItemKind
blastNoSkMove, ItemKind
blastNoSkMelee, ItemKind
blastNoSkDisplace, ItemKind
blastNoSkAlter, ItemKind
blastNoSkWait, ItemKind
blastNoSkMoveItem, ItemKind
blastNoSkProject, ItemKind
blastNoSkApply, ItemKind
blastBonusSkMove, ItemKind
blastBonusSkMelee, ItemKind
blastBonusSkDisplace, ItemKind
blastBonusSkAlter, ItemKind
blastBonusSkWait, ItemKind
blastBonusSkMoveItem, ItemKind
blastBonusSkProject, ItemKind
blastBonusSkApply]

spreadBurningOil2,    spreadBurningOil3, spreadBurningOil4, spreadBurningOil82, spreadBurningOil83, spreadBurningOil84, focusedBurningOil2, focusedBurningOil3, focusedBurningOil4, firecracker1, firecracker2, firecracker3, firecracker4, firecracker5, spreadFragmentation, spreadFragmentation8, focusedFragmentation, spreadConcussion, spreadConcussion8, focusedConcussion, spreadFlash, spreadFlash8, focusedFlash, singleSpark, glassPiece, focusedGlass, fragrance, pheromone, mistCalming, odorDistressing, mistHealing, mistHealing2, mistWounding, distortion, smoke, boilingWater, glue, waste, mistAntiSlow, mistAntidote, mistSleep, denseShower, sparseShower, protectingBalmMelee, protectingBalmRanged, defenselessnessRunout, resolutionDust, hasteSpray, slownessMist, eyeDrop, ironFiling, smellyDroplet, eyeShine, whiskeySpray, youthSprinkle, poisonCloud, pingFlash, blastNoSkMove, blastNoSkMelee, blastNoSkDisplace, blastNoSkAlter, blastNoSkWait, blastNoSkMoveItem, blastNoSkProject, blastNoSkApply, blastBonusSkMove, blastBonusSkMelee, blastBonusSkDisplace, blastBonusSkAlter, blastBonusSkWait, blastBonusSkMoveItem, blastBonusSkProject, blastBonusSkApply :: ItemKind

-- We take care (e.g., in burningOil below) that blasts are not faster
-- than 100% fastest natural speed, or some frames would be skipped,
-- which is a waste of perfectly good frames.

-- * Parameterized blasts

spreadBurningOil :: Int -> GroupName ItemKind -> ItemKind
spreadBurningOil :: Int -> GroupName ItemKind -> ItemKind
spreadBurningOil n :: Int
n grp :: GroupName ItemKind
grp = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '*'
  , iname :: Text
iname    = "burning oil"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
grp, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrYellow]
  , icount :: Dice
icount   = Int -> Dice
intToDice (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
* 3)
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "sear"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Int -> Aspect
toVelocity (Int -> Int -> Int
forall a. Ord a => a -> a -> a
min 100 (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Int
n Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` 2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* 10)
               , Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast
               , Skill -> Dice -> Aspect
AddSkill Skill
SkShine 2 ]
  , ieffects :: [Effect]
ieffects = [ Dice -> Effect
Burn 1
               , GroupName ItemKind -> Dice -> Effect
toOrganBad GroupName ItemKind
S_PACIFIED (2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 2) ]
                   -- slips and frantically puts out fire
  , idesc :: Text
idesc    = "Sticky oil, burning brightly."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
spreadBurningOil2 :: ItemKind
spreadBurningOil2 = Int -> GroupName ItemKind -> ItemKind
spreadBurningOil 2 GroupName ItemKind
S_VIOLENT_BURNING_OIL_2
                      -- 2 steps, 2 turns
spreadBurningOil3 :: ItemKind
spreadBurningOil3 = Int -> GroupName ItemKind -> ItemKind
spreadBurningOil 3 GroupName ItemKind
S_VIOLENT_BURNING_OIL_3
                      -- 2 steps, 2 turns
spreadBurningOil4 :: ItemKind
spreadBurningOil4 = Int -> GroupName ItemKind -> ItemKind
spreadBurningOil 4 GroupName ItemKind
S_VIOLENT_BURNING_OIL_4
                      -- 4 steps, 2 turns
spreadBurningOil8 :: Int -> GroupName ItemKind -> ItemKind
spreadBurningOil8 :: Int -> GroupName ItemKind -> ItemKind
spreadBurningOil8 n :: Int
n grp :: GroupName ItemKind
grp = (Int -> GroupName ItemKind -> ItemKind
spreadBurningOil (Int
n Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` 2) GroupName ItemKind
grp)
  { icount :: Dice
icount   = 7
  }
spreadBurningOil82 :: ItemKind
spreadBurningOil82 = Int -> GroupName ItemKind -> ItemKind
spreadBurningOil8 2 GroupName ItemKind
S_BURNING_OIL_2
spreadBurningOil83 :: ItemKind
spreadBurningOil83 = Int -> GroupName ItemKind -> ItemKind
spreadBurningOil8 3 GroupName ItemKind
S_BURNING_OIL_3
spreadBurningOil84 :: ItemKind
spreadBurningOil84 = Int -> GroupName ItemKind -> ItemKind
spreadBurningOil8 4 GroupName ItemKind
S_BURNING_OIL_4
focusedBurningOil :: Int -> GroupName ItemKind -> GroupName ItemKind -> ItemKind
focusedBurningOil :: Int -> GroupName ItemKind -> GroupName ItemKind -> ItemKind
focusedBurningOil n :: Int
n grp :: GroupName ItemKind
grp grpExplode :: GroupName ItemKind
grpExplode = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "igniting oil"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
grp, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Brown]
  , icount :: Dice
icount   = Int -> Dice
intToDice Int
n
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "ignite"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Int -> Aspect
toLinger 0  -- 0 steps, 1 turn
               , Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast ]
      -- when the target position is occupied, the explosion starts one step
      -- away, hence we set range to 0 steps, to limit dispersal
  , ieffects :: [Effect]
ieffects = [Effect -> Effect
OnSmash (Effect -> Effect) -> Effect -> Effect
forall a b. (a -> b) -> a -> b
$ GroupName ItemKind -> Effect
Explode GroupName ItemKind
grpExplode]
  , idesc :: Text
idesc    = ItemKind -> Text
idesc ItemKind
spreadBurningOil2
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
focusedBurningOil2 :: ItemKind
focusedBurningOil2 = Int -> GroupName ItemKind -> GroupName ItemKind -> ItemKind
focusedBurningOil 2 GroupName ItemKind
S_FOCUSED_BURNING_OIL_2 GroupName ItemKind
S_BURNING_OIL_2
focusedBurningOil3 :: ItemKind
focusedBurningOil3 = Int -> GroupName ItemKind -> GroupName ItemKind -> ItemKind
focusedBurningOil 3 GroupName ItemKind
S_FOCUSED_BURNING_OIL_3 GroupName ItemKind
S_BURNING_OIL_3
focusedBurningOil4 :: ItemKind
focusedBurningOil4 = Int -> GroupName ItemKind -> GroupName ItemKind -> ItemKind
focusedBurningOil 4 GroupName ItemKind
S_FOCUSED_BURNING_OIL_4 GroupName ItemKind
S_BURNING_OIL_4
firecracker :: Int -> ItemKind
firecracker :: Int -> ItemKind
firecracker n :: Int
n = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '*'
  , iname :: Text
iname    = "firecracker"
  , ifreq :: Freqs ItemKind
ifreq    = [(if Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== 5
                 then GroupName ItemKind
S_FIRECRACKER
                 else Int -> GroupName ItemKind
firecrackerAt Int
n, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [[Color]
brightCol [Color] -> Int -> Color
forall a. [a] -> Int -> a
!! ((Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 2) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` [Color] -> Int
forall a. [a] -> Int
length [Color]
brightCol)]
  , icount :: Dice
icount   = if Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= 3 then 1 Int -> Int -> Dice
`d` Int -> Int -> Int
forall a. Ord a => a -> a -> a
min 2 Int
n else 2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 2
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = if Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 4 then "singe" else "crack"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Int -> Aspect
toVelocity 5  -- 1 step, 1 turn
               , Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast
               , Skill -> Dice -> Aspect
AddSkill Skill
SkShine (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ Int -> Dice
intToDice (Int -> Dice) -> Int -> Dice
forall a b. (a -> b) -> a -> b
$ 1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` 2 ]
  , ieffects :: [Effect]
ieffects = [if Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 4 then Dice -> Effect
Burn 1 else Int -> Effect
RefillCalm (-2)]
               [Effect] -> [Effect] -> [Effect]
forall a. [a] -> [a] -> [a]
++ [Int -> Dice -> Effect
Discharge 1 30 | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 3]
               [Effect] -> [Effect] -> [Effect]
forall a. [a] -> [a] -> [a]
++ [Effect -> Effect
OnSmash (Effect -> Effect) -> Effect -> Effect
forall a b. (a -> b) -> a -> b
$ GroupName ItemKind -> Effect
Explode (GroupName ItemKind -> Effect) -> GroupName ItemKind -> Effect
forall a b. (a -> b) -> a -> b
$ Int -> GroupName ItemKind
firecrackerAt (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1) | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 2]
  , idesc :: Text
idesc    = "Scraps of burnt paper, covering little pockets of black powder, buffeted by colorful explosions."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
firecracker5 :: ItemKind
firecracker5 = Int -> ItemKind
firecracker 5
firecracker4 :: ItemKind
firecracker4 = Int -> ItemKind
firecracker 4
firecracker3 :: ItemKind
firecracker3 = Int -> ItemKind
firecracker 3
firecracker2 :: ItemKind
firecracker2 = Int -> ItemKind
firecracker 2
firecracker1 :: ItemKind
firecracker1 = Int -> ItemKind
firecracker 1

-- * Focused blasts

spreadFragmentation :: ItemKind
spreadFragmentation = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '*'
  , iname :: Text
iname    = "fragmentation burst"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_VIOLENT_FRAGMENTATION, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Red]
  , icount :: Dice
icount   = 16  -- strong but few, so not always hits target
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "tear apart"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 3 Int -> Int -> Dice
`d` 1  -- deadly and adjacent actor hit by 2 on average;
                        -- however, moderate armour blocks completely
  , iaspects :: [Aspect]
iaspects = [ ThrowMod -> Aspect
ToThrow (ThrowMod -> Aspect) -> ThrowMod -> Aspect
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int -> ThrowMod
ThrowMod 100 20 4  -- 4 steps, 1 turn
               , Flag -> Aspect
SetFlag Flag
Lobable, Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast
               , Skill -> Dice -> Aspect
AddSkill Skill
SkShine 3, Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ -12 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5 ]
  , ieffects :: [Effect]
ieffects = [Int -> Int -> CStore -> GroupName ItemKind -> Effect
DropItem 1 1 CStore
COrgan GroupName ItemKind
CONDITION]
  , idesc :: Text
idesc    = "Flying shards, flame and smoke."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
spreadFragmentation8 :: ItemKind
spreadFragmentation8 = ItemKind
spreadFragmentation
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_FRAGMENTATION, 1)]
  , icount :: Dice
icount   = 8
  , iaspects :: [Aspect]
iaspects = [ ThrowMod -> Aspect
ToThrow (ThrowMod -> Aspect) -> ThrowMod -> Aspect
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int -> ThrowMod
ThrowMod 100 10 2  -- 2 steps, 1 turn
               , Flag -> Aspect
SetFlag Flag
Lobable, Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast
               , Skill -> Dice -> Aspect
AddSkill Skill
SkShine 3, Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ -12 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5 ]
      -- smaller radius, so worse for area effect, but twice the direct damage
  }
focusedFragmentation :: ItemKind
focusedFragmentation = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "deflagration ignition"  -- black powder
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_FOCUSED_FRAGMENTATION, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrYellow]
  , icount :: Dice
icount   = 4  -- 32 in total vs 16; on average 4 hits
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "ignite"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Int -> Aspect
toLinger 0  -- 0 steps, 1 turn
               , Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast ]
      -- when the target position is occupied, the explosion starts one step
      -- away, hence we set range to 0 steps, to limit dispersal
  , ieffects :: [Effect]
ieffects = [Effect -> Effect
OnSmash (Effect -> Effect) -> Effect -> Effect
forall a b. (a -> b) -> a -> b
$ GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_FRAGMENTATION]
  , idesc :: Text
idesc    = ItemKind -> Text
idesc ItemKind
spreadFragmentation
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
spreadConcussion :: ItemKind
spreadConcussion = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '*'
  , iname :: Text
iname    = "concussion blast"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_VIOLENT_CONCUSSION, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Magenta]
  , icount :: Dice
icount   = 16
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "shock"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 1 Int -> Int -> Dice
`d` 1  -- only air pressure, so not as deadly as fragmentation,
                        -- but armour can't block completely that easily
  , iaspects :: [Aspect]
iaspects = [ ThrowMod -> Aspect
ToThrow (ThrowMod -> Aspect) -> ThrowMod -> Aspect
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int -> ThrowMod
ThrowMod 100 20 4  -- 4 steps, 1 turn
               , Flag -> Aspect
SetFlag Flag
Lobable, Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast
               , Skill -> Dice -> Aspect
AddSkill Skill
SkShine 3, Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ -8 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5 ]
      -- outdoors it has short range, but we only model indoors in the game;
      -- it's much faster than black powder shock wave, but we are beyond
      -- human-noticeable speed differences on short distances anyway
  , ieffects :: [Effect]
ieffects = [ Int -> Int -> CStore -> GroupName ItemKind -> Effect
DropItem Int
forall a. Bounded a => a
maxBound 1 CStore
CEqp GroupName ItemKind
ARMOR_MISC
               , ThrowMod -> Effect
PushActor (Int -> Int -> Int -> ThrowMod
ThrowMod 400 25 1)  -- 1 step, fast; after DropItem
                   -- this produces spam for braced actors; too bad
               , GroupName ItemKind -> Dice -> Effect
toOrganBad GroupName ItemKind
S_IMMOBILE 3  -- no balance
               , GroupName ItemKind -> Dice -> Effect
toOrganBad GroupName ItemKind
S_DEAFENED 23 ]
  , idesc :: Text
idesc    = "Shock wave, hot gases, some fire and smoke."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
spreadConcussion8 :: ItemKind
spreadConcussion8 = ItemKind
spreadConcussion
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_CONCUSSION, 1)]
  , icount :: Dice
icount   = 8
  , iaspects :: [Aspect]
iaspects = [ ThrowMod -> Aspect
ToThrow (ThrowMod -> Aspect) -> ThrowMod -> Aspect
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int -> ThrowMod
ThrowMod 100 10 2  -- 2 steps, 1 turn
               , Flag -> Aspect
SetFlag Flag
Lobable, Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast
               , Skill -> Dice -> Aspect
AddSkill Skill
SkShine 3, Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ -8 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5 ]
  }
focusedConcussion :: ItemKind
focusedConcussion = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "detonation ignition"  -- nitroglycerine
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_FOCUSED_CONCUSSION, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrYellow]
  , icount :: Dice
icount   = 4
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "ignite"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Int -> Aspect
toLinger 0  -- 0 steps, 1 turn
               , Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast ]
  , ieffects :: [Effect]
ieffects = [Effect -> Effect
OnSmash (Effect -> Effect) -> Effect -> Effect
forall a b. (a -> b) -> a -> b
$ GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_CONCUSSION]
  , idesc :: Text
idesc    = ItemKind -> Text
idesc ItemKind
spreadConcussion
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
spreadFlash :: ItemKind
spreadFlash = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "magnesium flash"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_VIOLENT_FLASH, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrWhite]
  , icount :: Dice
icount   = 16
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "dazzle"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ ThrowMod -> Aspect
ToThrow (ThrowMod -> Aspect) -> ThrowMod -> Aspect
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int -> ThrowMod
ThrowMod 100 20 4  -- 4 steps, 1 turn
               , Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast
               , Skill -> Dice -> Aspect
AddSkill Skill
SkShine 5 ]
  , ieffects :: [Effect]
ieffects = [GroupName ItemKind -> Dice -> Effect
toOrganBad GroupName ItemKind
S_BLIND 5, GroupName ItemKind -> Dice -> Effect
toOrganBad GroupName ItemKind
S_WEAKENED 20]
                 -- Wikipedia says: blind for five seconds and afterimage
                 -- for much longer, harming aim
  , idesc :: Text
idesc    = "A very bright flash of fire."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
spreadFlash8 :: ItemKind
spreadFlash8 = ItemKind
spreadFlash
  { iname :: Text
iname    = "spark"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_SPARK, 1)]
  , icount :: Dice
icount   = 8
  , iverbHit :: Text
iverbHit = "singe"
  , iaspects :: [Aspect]
iaspects = [ ThrowMod -> Aspect
ToThrow (ThrowMod -> Aspect) -> ThrowMod -> Aspect
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int -> ThrowMod
ThrowMod 100 10 2  -- 2 steps, 1 turn
               , Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast
               , Skill -> Dice -> Aspect
AddSkill Skill
SkShine 5 ]
  }
focusedFlash :: ItemKind
focusedFlash = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "magnesium ignition"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_FOCUSED_FLASH, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrYellow]
  , icount :: Dice
icount   = 4
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "ignite"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Int -> Aspect
toLinger 0  -- 0 steps, 1 turn
               , Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast ]
  , ieffects :: [Effect]
ieffects = [Effect -> Effect
OnSmash (Effect -> Effect) -> Effect -> Effect
forall a b. (a -> b) -> a -> b
$ GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_SPARK]
  , idesc :: Text
idesc    = ItemKind -> Text
idesc ItemKind
spreadFlash
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
singleSpark :: ItemKind
singleSpark = ItemKind
spreadFlash
  { iname :: Text
iname    = "single spark"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_SINGLE_SPARK, 1)]
  , icount :: Dice
icount   = 1
  , iverbHit :: Text
iverbHit = "spark"
  , iaspects :: [Aspect]
iaspects = [ Int -> Aspect
toLinger 5  -- 1 step, 1 turn
               , Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast
               , Skill -> Dice -> Aspect
AddSkill Skill
SkShine 3 ]
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = "A glowing ember."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
glassPiece :: ItemKind
glassPiece = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '*'
  , iname :: Text
iname    = "glass piece"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_GLASS_HAIL, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Blue]
  , icount :: Dice
icount   = 8
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "cut"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 2 Int -> Int -> Dice
`d` 1
  , iaspects :: [Aspect]
iaspects = [ ThrowMod -> Aspect
ToThrow (ThrowMod -> Aspect) -> ThrowMod -> Aspect
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int -> ThrowMod
ThrowMod 100 20 4  -- 4 steps, 1 turn
               , Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast
               , Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ -15 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5 ]
                 -- brittle, not too dense; armor blocks
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = "Swift, sharp edges."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
focusedGlass :: ItemKind
focusedGlass = ItemKind
glassPiece  -- when blowing up windows
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_FOCUSED_GLASS_HAIL, 1)]
  , icount :: Dice
icount   = 4
  , iaspects :: [Aspect]
iaspects = [ Int -> Aspect
toLinger 0  -- 0 steps, 1 turn
               , Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast
               , Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ -15 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5 ]
  , ieffects :: [Effect]
ieffects = [Effect -> Effect
OnSmash (Effect -> Effect) -> Effect -> Effect
forall a b. (a -> b) -> a -> b
$ GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_GLASS_HAIL]
  }

-- * Assorted blasts that don't induce conditions or not used mainly for them

fragrance :: ItemKind
fragrance = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "fragrance"  -- instant, fast fragrance
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_FRAGRANCE, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Magenta]
  , icount :: Dice
icount   = 12
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "engulf"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ ThrowMod -> Aspect
ToThrow (ThrowMod -> Aspect) -> ThrowMod -> Aspect
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int -> ThrowMod
ThrowMod 200 5 1  -- 2 steps, .5 turn (necklaces)
               , Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast ]
  , ieffects :: [Effect]
ieffects = [Effect
Impress, GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_ROSE_SMELLING 45]
  -- Linger 10, because sometimes it takes 2 turns due to starting just
  -- before actor turn's end (e.g., via a necklace).
  , idesc :: Text
idesc    = "A pleasant scent."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
pheromone :: ItemKind
pheromone = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "musky whiff"  -- a kind of mist rather than fragrance
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_PHEROMONE, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrMagenta]
  , icount :: Dice
icount   = 16
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "tempt"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Int -> Aspect
toVelocity 10  -- 2 steps, 2 turns
               , Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast ]
  , ieffects :: [Effect]
ieffects = [Effect
Dominate]
  , idesc :: Text
idesc    = "A sharp, strong scent."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
mistCalming :: ItemKind
mistCalming = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind  -- unused
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "mist"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_CALMING_MIST, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrGreen]
  , icount :: Dice
icount   = 8
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "sooth"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Int -> Aspect
toVelocity 5  -- 1 step, 1 turn
               , Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast ]
  , ieffects :: [Effect]
ieffects = [Int -> Effect
RefillCalm 2]
  , idesc :: Text
idesc    = "A soothing, gentle cloud."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
odorDistressing :: ItemKind
odorDistressing = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "distressing whiff"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_DISTRESSING_ODOR, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color
BrRed]  -- salmon
  , icount :: Dice
icount   = 8
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "distress"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Int -> Aspect
toLinger 10  -- 2 steps, 1 turn
               , Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast ]
  , ieffects :: [Effect]
ieffects = [ Int -> Effect
RefillCalm (-10)
               , GroupName ItemKind -> Dice -> Effect
toOrganBad GroupName ItemKind
S_FOUL_SMELLING (20 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 5)
               , GroupName ItemKind -> Dice -> Effect
toOrganBad GroupName ItemKind
S_IMPATIENT (2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 2) ]
  , idesc :: Text
idesc    = "It turns the stomach."  -- and so can't stand still
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
mistHealing :: ItemKind
mistHealing = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "mist"  -- powerful, so slow and narrow
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_HEALING_MIST, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color
BrGreen]
  , icount :: Dice
icount   = 8
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "revitalize"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Int -> Aspect
toVelocity 5  -- 1 step, 1 turn
               , Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast
               , Skill -> Dice -> Aspect
AddSkill Skill
SkShine 1 ]
  , ieffects :: [Effect]
ieffects = [Int -> Effect
RefillHP 2]
  , idesc :: Text
idesc    = "It fills the air with light and life."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
mistHealing2 :: ItemKind
mistHealing2 = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "mist"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_HEALING_MIST_2, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Green]
  , icount :: Dice
icount   = 8
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "revitalize"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Int -> Aspect
toVelocity 5  -- 1 step, 1 turn
               , Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast
               , Skill -> Dice -> Aspect
AddSkill Skill
SkShine 2 ]
  , ieffects :: [Effect]
ieffects = [Int -> Effect
RefillHP 4]
  , idesc :: Text
idesc    = "At its touch, wounds close and bruises fade."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
mistWounding :: ItemKind
mistWounding = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "mist"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_WOUNDING_MIST, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrRed]
  , icount :: Dice
icount   = 8
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "devitalize"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Int -> Aspect
toVelocity 5  -- 1 step, 1 turn
               , Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast ]
  , ieffects :: [Effect]
ieffects = [Int -> Effect
RefillHP (-2)]
  , idesc :: Text
idesc    = "The air itself stings and itches."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
distortion :: ItemKind
distortion = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = 'v'
  , iname :: Text
iname    = "vortex"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_DISTORTION, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
White]
  , icount :: Dice
icount   = 8  -- braced are immune to Teleport; avoid failure messages
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "engulf"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Int -> Aspect
toLinger 10  -- 2 steps, 1 turn
               , Flag -> Aspect
SetFlag Flag
Lobable, Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast ]
  , ieffects :: [Effect]
ieffects = [Dice -> Effect
Teleport (Dice -> Effect) -> Dice -> Effect
forall a b. (a -> b) -> a -> b
$ 15 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 10]
  , idesc :: Text
idesc    = "The air shifts oddly, as though light is being warped."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
smoke :: ItemKind
smoke = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind  -- when stuff burns out  -- unused
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "smoke fume"  -- pluralizes better than 'smokes'
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_SMOKE, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrBlack]
  , icount :: Dice
icount   = 16
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "choke"  -- or "obscure"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Int -> Aspect
toVelocity 20  -- 4 steps, 2 turns
               , Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast ]
  , ieffects :: [Effect]
ieffects = [GroupName ItemKind -> Dice -> Effect
toOrganBad GroupName ItemKind
S_WITHHOLDING (5 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 3)]
                  -- choking and tears, can roughly see, but not aim
  , idesc :: Text
idesc    = "Twirling clouds of grey smoke."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
boilingWater :: ItemKind
boilingWater = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '*'
  , iname :: Text
iname    = "boiling water"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_BOILING_WATER, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
White]
  , icount :: Dice
icount   = 18
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "boil"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Int -> Aspect
toVelocity 30  -- 6 steps, 2 turns
               , Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast ]
  , ieffects :: [Effect]
ieffects = [Dice -> Effect
Burn 1]
  , idesc :: Text
idesc    = "It bubbles and hisses."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
glue :: ItemKind
glue = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '*'
  , iname :: Text
iname    = "hoof glue"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_GLUE, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Cyan]
  , icount :: Dice
icount   = 8  -- Paralyze doesn't stack; avoid failure messages
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "glue"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Int -> Aspect
toVelocity 20  -- 4 steps, 2 turns
               , Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast ]
  , ieffects :: [Effect]
ieffects = [Dice -> Effect
Paralyze 10]
  , idesc :: Text
idesc    = "Thick and clinging."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
waste :: ItemKind
waste = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '*'
  , iname :: Text
iname    = "waste piece"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_WASTE, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Brown]
  , icount :: Dice
icount   = 16
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "splosh"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [Int -> Aspect
toLinger 10, Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast]
  , ieffects :: [Effect]
ieffects = [ GroupName ItemKind -> Dice -> Effect
toOrganBad GroupName ItemKind
S_FOUL_SMELLING (30 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 10)
               , GroupName ItemKind -> Dice -> Effect
toOrganBad GroupName ItemKind
S_DISPOSSESSED (10 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 5) ]
  , idesc :: Text
idesc    = "Sodden and foul-smelling."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
mistAntiSlow :: ItemKind
mistAntiSlow = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "mist"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_ANTI_SLOW_MIST, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color
BrYellow]
  , icount :: Dice
icount   = 8
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "propel"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Int -> Aspect
toVelocity 5  -- 1 step, 1 turn
               , Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast ]
  , ieffects :: [Effect]
ieffects = [Int -> Int -> CStore -> GroupName ItemKind -> Effect
DropItem 1 1 CStore
COrgan GroupName ItemKind
S_SLOWED]
  , idesc :: Text
idesc    = "A cleansing rain."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
mistAntidote :: ItemKind
mistAntidote = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "mist"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_ANTIDOTE_MIST, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color
BrBlue]
  , icount :: Dice
icount   = 8
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "cure"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Int -> Aspect
toVelocity 5  -- 1 step, 1 turn
               , Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast ]
  , ieffects :: [Effect]
ieffects = [Int -> Int -> CStore -> GroupName ItemKind -> Effect
DropItem 1 Int
forall a. Bounded a => a
maxBound CStore
COrgan GroupName ItemKind
S_POISONED]
  , idesc :: Text
idesc    = "Washes away death's dew."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
mistSleep :: ItemKind
mistSleep = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "mist"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_SLEEP_MIST, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color
BrMagenta]
  , icount :: Dice
icount   = 8
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "put to sleep"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Int -> Aspect
toVelocity 5  -- 1 step, 1 turn
               , Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast ]
  , ieffects :: [Effect]
ieffects = [Effect
PutToSleep]
  , idesc :: Text
idesc    = "Lulls weary warriors."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }

-- * Condition-inducing blasts

-- Almost all have @toLinger 10@, that travels 2 steps in 1 turn.
-- These are very fast projectiles, not getting into the way of big
-- actors and not burdening the engine for long.
-- A few are slower 'mists'.

denseShower :: ItemKind
denseShower = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "dense shower"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_DENSE_SHOWER, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color
Green]
  , icount :: Dice
icount   = 12
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "strengthen"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [Int -> Aspect
toLinger 10, Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast]
  , ieffects :: [Effect]
ieffects = [GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_STRENGTHENED 5]
  , idesc :: Text
idesc    = "A thick rain of droplets."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
sparseShower :: ItemKind
sparseShower = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "sparse shower"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_SPARSE_SHOWER, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color
Red]
  , icount :: Dice
icount   = 8
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "weaken"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [Int -> Aspect
toLinger 10, Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast]
  , ieffects :: [Effect]
ieffects = [GroupName ItemKind -> Dice -> Effect
toOrganBad GroupName ItemKind
S_WEAKENED 7]
  , idesc :: Text
idesc    = "Light droplets that cling to clothing."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
protectingBalmMelee :: ItemKind
protectingBalmMelee = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "balm droplet"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_MELEE_PROTECTIVE_BALM, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color
Brown]
  , icount :: Dice
icount   = 16
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "balm"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [Int -> Aspect
toLinger 10, Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast]
  , ieffects :: [Effect]
ieffects = [GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_PROTECTED_FROM_MELEE (3 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 3)]
  , idesc :: Text
idesc    = "A thick ointment that hardens the skin."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
protectingBalmRanged :: ItemKind
protectingBalmRanged = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "balm droplet"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_RANGE_PROTECTIVE_BALM, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrYellow]
  , icount :: Dice
icount   = 16
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "balm"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [Int -> Aspect
toLinger 10, Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast]
  , ieffects :: [Effect]
ieffects = [GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_PROTECTED_FROM_RANGED (3 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 3)]
  , idesc :: Text
idesc    = "Grease that protects from flying death."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
defenselessnessRunout :: ItemKind
defenselessnessRunout = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '?'
  , iname :: Text
iname    = "PhD defense question"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_DEFENSELESSNESS_RUNOUT, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color
BrRed]
  , icount :: Dice
icount   = 16
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "nag"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [Int -> Aspect
toLinger 10, Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast]
  , ieffects :: [Effect]
ieffects = [GroupName ItemKind -> Dice -> Effect
toOrganBad GroupName ItemKind
S_DEFENSELESS (3 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 3)]
  , idesc :: Text
idesc    = "Only the most learned make use of this."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
resolutionDust :: ItemKind
resolutionDust = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "resolution dust"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_RESOLUTION_DUST, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Brown]
  , icount :: Dice
icount   = 16
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "calm"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [Int -> Aspect
toLinger 10, Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast]
  , ieffects :: [Effect]
ieffects = [GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_RESOLUTE (3 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 3)]
                 -- short enough duration that @calmEnough@ not a big problem
  , idesc :: Text
idesc    = "A handful of honest earth, to strengthen the soul."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
hasteSpray :: ItemKind
hasteSpray = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "haste spray"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_HASTE_SPRAY, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color
BrYellow]
  , icount :: Dice
icount   = 16
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "haste"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [Int -> Aspect
toLinger 10, Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast]
  , ieffects :: [Effect]
ieffects = [GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_HASTED (3 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 3)]
  , idesc :: Text
idesc    = "A quick spurt."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
slownessMist :: ItemKind
slownessMist = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "slowness mist"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_SLOWNESS_MIST, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrBlue]
  , icount :: Dice
icount   = 8
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "slow"
  , iweight :: Int
iweight  = 0
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [Int -> Aspect
toVelocity 5, Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast]
                 -- 1 step, 1 turn, mist, slow
  , ieffects :: [Effect]
ieffects = [GroupName ItemKind -> Dice -> Effect
toOrganBad GroupName ItemKind
S_SLOWED (3 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 3)]
  , idesc :: Text
idesc    = "Clammy fog, making each movement an effort."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
eyeDrop :: ItemKind
eyeDrop = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "eye drop"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_EYE_DROP, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color
BrCyan]
  , icount :: Dice
icount   = 16
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "cleanse"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [Int -> Aspect
toLinger 10, Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast]
  , ieffects :: [Effect]
ieffects = [GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_FAR_SIGHTED (3 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 3)]
  , idesc :: Text
idesc    = "Not to be taken orally."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
ironFiling :: ItemKind
ironFiling = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind  -- fast, short, strongly blinding blast
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "iron filing"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_IRON_FILING, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Red]
  , icount :: Dice
icount   = 16
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "blind"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [Int -> Aspect
toLinger 10, Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast]
  , ieffects :: [Effect]
ieffects = [GroupName ItemKind -> Dice -> Effect
toOrganBad GroupName ItemKind
S_BLIND (10 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 10)]
  , idesc :: Text
idesc    = "A shaving of bright metal."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
smellyDroplet :: ItemKind
smellyDroplet = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "smelly droplet"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_SMELLY_DROPLET, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color
Blue]
  , icount :: Dice
icount   = 16
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "sensitize"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [Int -> Aspect
toLinger 10, Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast]
  , ieffects :: [Effect]
ieffects = [GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_KEEN_SMELLING (5 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 3)]
  , idesc :: Text
idesc    = "A viscous lump that stains the skin."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
eyeShine :: ItemKind
eyeShine = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "eye shine"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_EYE_SHINE, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color
Cyan]
  , icount :: Dice
icount   = 16
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "smear"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [Int -> Aspect
toLinger 10, Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast]
  , ieffects :: [Effect]
ieffects = [GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_SHINY_EYED (3 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 3)]
  , idesc :: Text
idesc    = "They almost glow in the dark."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
whiskeySpray :: ItemKind
whiskeySpray = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "whiskey spray"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_WHISKEY_SPRAY, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color
Brown]
  , icount :: Dice
icount   = 16
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "inebriate"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [Int -> Aspect
toLinger 10, Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast]
  , ieffects :: [Effect]
ieffects = [GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_DRUNK (3 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 3)]
  , idesc :: Text
idesc    = "It burns in the best way."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
youthSprinkle :: ItemKind
youthSprinkle = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "youth sprinkle"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_YOUTH_SPRINKLE, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color
BrGreen]
  , icount :: Dice
icount   = 16
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "sprinkle"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [Int -> Aspect
toLinger 10, Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast]
  , ieffects :: [Effect]
ieffects = [ GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_ROSE_SMELLING (40 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 20)
               , GroupName ItemKind -> Effect
toOrganNoTimer GroupName ItemKind
S_REGENERATING ]
  , idesc :: Text
idesc    = "Bright and smelling of the Spring."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
poisonCloud :: ItemKind
poisonCloud = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "poison cloud"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_POISON_CLOUD, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color
BrMagenta]
  , icount :: Dice
icount   = 16
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "poison"
  , iweight :: Int
iweight  = 0  -- lingers, blocking path
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ ThrowMod -> Aspect
ToThrow (ThrowMod -> Aspect) -> ThrowMod -> Aspect
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int -> ThrowMod
ThrowMod 10 100 2  -- 2 steps, 2 turns
               , Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast ]
  , ieffects :: [Effect]
ieffects = [GroupName ItemKind -> Effect
toOrganNoTimer GroupName ItemKind
S_POISONED]
  , idesc :: Text
idesc    = "Choking gas that stings the eyes."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
pingFlash :: ItemKind
pingFlash = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "flash"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
S_PING_PLASH, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color
Green]
  , icount :: Dice
icount   = 1
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "ping"
  , iweight :: Int
iweight  = 1  -- to prevent blocking the way
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Int -> Aspect
toLinger 0
               , Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast
               , Skill -> Dice -> Aspect
AddSkill Skill
SkShine 2 ]
  , ieffects :: [Effect]
ieffects = [Effect -> Effect
OnSmash Effect
Yell]
  , idesc :: Text
idesc    = "A ping and a display flash from an echolocator out of sync momentarily."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
blastNoStat :: GroupName ItemKind -> ItemKind
blastNoStat :: GroupName ItemKind -> ItemKind
blastNoStat grp :: GroupName ItemKind
grp = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "mist"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind -> GroupName ItemKind
blastNoStatOf GroupName ItemKind
grp, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color
White]
  , icount :: Dice
icount   = 12
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "drain"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Int -> Aspect
toVelocity 10  -- 2 steps, 2 turns
               , Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast ]
  , ieffects :: [Effect]
ieffects = [GroupName ItemKind -> Dice -> Effect
toOrganBad GroupName ItemKind
grp (3 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 3)]
  , idesc :: Text
idesc    = "Completely disables one personal faculty."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
blastNoSkMove :: ItemKind
blastNoSkMove = GroupName ItemKind -> ItemKind
blastNoStat GroupName ItemKind
S_IMMOBILE
blastNoSkMelee :: ItemKind
blastNoSkMelee = GroupName ItemKind -> ItemKind
blastNoStat GroupName ItemKind
S_PACIFIED
blastNoSkDisplace :: ItemKind
blastNoSkDisplace = GroupName ItemKind -> ItemKind
blastNoStat GroupName ItemKind
S_IRREPLACEABLE
blastNoSkAlter :: ItemKind
blastNoSkAlter = GroupName ItemKind -> ItemKind
blastNoStat GroupName ItemKind
S_RETAINING
blastNoSkWait :: ItemKind
blastNoSkWait = GroupName ItemKind -> ItemKind
blastNoStat GroupName ItemKind
S_IMPATIENT
blastNoSkMoveItem :: ItemKind
blastNoSkMoveItem = GroupName ItemKind -> ItemKind
blastNoStat GroupName ItemKind
S_DISPOSSESSED
blastNoSkProject :: ItemKind
blastNoSkProject = GroupName ItemKind -> ItemKind
blastNoStat GroupName ItemKind
S_WITHHOLDING
blastNoSkApply :: ItemKind
blastNoSkApply = GroupName ItemKind -> ItemKind
blastNoStat GroupName ItemKind
S_PARSIMONIOUS
blastBonusStat :: GroupName ItemKind -> ItemKind
blastBonusStat :: GroupName ItemKind -> ItemKind
blastBonusStat grp :: GroupName ItemKind
grp = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = '`'
  , iname :: Text
iname    = "dew"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind -> GroupName ItemKind
blastBonusStatOf GroupName ItemKind
grp, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color
White]
  , icount :: Dice
icount   = 12
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iverbHit :: Text
iverbHit = "elevate"
  , iweight :: Int
iweight  = 1
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Int -> Aspect
toVelocity 10  -- 2 steps, 2 turns
               , Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Blast ]
  , ieffects :: [Effect]
ieffects = [GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
grp (20 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 5)]
  , idesc :: Text
idesc    = "Temporarily enhances the given personal faculty."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
blastBonusSkMove :: ItemKind
blastBonusSkMove = GroupName ItemKind -> ItemKind
blastBonusStat GroupName ItemKind
S_MORE_MOBILE
blastBonusSkMelee :: ItemKind
blastBonusSkMelee = GroupName ItemKind -> ItemKind
blastBonusStat GroupName ItemKind
S_MORE_COMBATIVE
blastBonusSkDisplace :: ItemKind
blastBonusSkDisplace = GroupName ItemKind -> ItemKind
blastBonusStat GroupName ItemKind
S_MORE_DISPLACING
blastBonusSkAlter :: ItemKind
blastBonusSkAlter = GroupName ItemKind -> ItemKind
blastBonusStat GroupName ItemKind
S_MORE_MODIFYING
blastBonusSkWait :: ItemKind
blastBonusSkWait = GroupName ItemKind -> ItemKind
blastBonusStat GroupName ItemKind
S_MORE_PATIENT
blastBonusSkMoveItem :: ItemKind
blastBonusSkMoveItem = GroupName ItemKind -> ItemKind
blastBonusStat GroupName ItemKind
S_MORE_TIDY
blastBonusSkProject :: ItemKind
blastBonusSkProject = GroupName ItemKind -> ItemKind
blastBonusStat GroupName ItemKind
S_MORE_PROJECTING
blastBonusSkApply :: ItemKind
blastBonusSkApply = GroupName ItemKind -> ItemKind
blastBonusStat GroupName ItemKind
S_MORE_PRACTICAL