-- | Item definitions.
module Content.ItemKind
  ( -- * Group name patterns
    pattern HARPOON, pattern EDIBLE_PLANT, pattern RING_OF_OPPORTUNITY_GRENADIER, pattern ARMOR_LOOSE, pattern CLOTHING_MISC, pattern CHIC_GEAR
  , groupNamesSingleton, groupNames
  , -- * Content
    content, items, otherItemContent
  ) where

import Prelude ()

import Game.LambdaHack.Core.Prelude

import Content.ItemKindActor
import Content.ItemKindBlast
import Content.ItemKindEmbed
import Content.ItemKindOrgan
import Content.ItemKindTemporary
import Content.RuleKind
import Game.LambdaHack.Content.ItemKind
import Game.LambdaHack.Content.RuleKind
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

groupNamesSingleton :: [GroupName ItemKind]
groupNamesSingleton :: [GroupName ItemKind]
groupNamesSingleton =
       [GroupName ItemKind
S_FRAGRANCE, GroupName ItemKind
S_SINGLE_SPARK, GroupName ItemKind
S_SPARK]
    [GroupName ItemKind]
-> [GroupName ItemKind] -> [GroupName ItemKind]
forall a. [a] -> [a] -> [a]
++ [GroupName ItemKind
FLASK_UNKNOWN, GroupName ItemKind
POTION_UNKNOWN, GroupName ItemKind
EDIBLE_PLANT_UNKNOWN, GroupName ItemKind
SCROLL_UNKNOWN, GroupName ItemKind
NECKLACE_UNKNOWN, GroupName ItemKind
RING_UNKNOWN, GroupName ItemKind
HAMMER_UNKNOWN, GroupName ItemKind
GEM_UNKNOWN, GroupName ItemKind
CURRENCY_UNKNOWN]
    [GroupName ItemKind]
-> [GroupName ItemKind] -> [GroupName ItemKind]
forall a. [a] -> [a] -> [a]
++ [GroupName ItemKind]
embedsGNSingleton [GroupName ItemKind]
-> [GroupName ItemKind] -> [GroupName ItemKind]
forall a. [a] -> [a] -> [a]
++ [GroupName ItemKind]
actorsGNSingleton [GroupName ItemKind]
-> [GroupName ItemKind] -> [GroupName ItemKind]
forall a. [a] -> [a] -> [a]
++ [GroupName ItemKind]
organsGNSingleton
    [GroupName ItemKind]
-> [GroupName ItemKind] -> [GroupName ItemKind]
forall a. [a] -> [a] -> [a]
++ [GroupName ItemKind]
blastsGNSingleton [GroupName ItemKind]
-> [GroupName ItemKind] -> [GroupName ItemKind]
forall a. [a] -> [a] -> [a]
++ [GroupName ItemKind]
temporariesGNSingleton

pattern FLASK_UNKNOWN, POTION_UNKNOWN, EDIBLE_PLANT_UNKNOWN, SCROLL_UNKNOWN, NECKLACE_UNKNOWN, RING_UNKNOWN, HAMMER_UNKNOWN, GEM_UNKNOWN, CURRENCY_UNKNOWN :: GroupName ItemKind

groupNames :: [GroupName ItemKind]
groupNames :: [GroupName ItemKind]
groupNames =
       [GroupName ItemKind
TREASURE, GroupName ItemKind
ANY_SCROLL, GroupName ItemKind
ANY_GLASS, GroupName ItemKind
ANY_POTION, GroupName ItemKind
ANY_FLASK, GroupName ItemKind
EXPLOSIVE, GroupName ItemKind
ANY_JEWELRY, GroupName ItemKind
VALUABLE, GroupName ItemKind
UNREPORTED_INVENTORY]
    [GroupName ItemKind]
-> [GroupName ItemKind] -> [GroupName ItemKind]
forall a. [a] -> [a] -> [a]
++ [GroupName ItemKind
HARPOON, GroupName ItemKind
EDIBLE_PLANT, GroupName ItemKind
RING_OF_OPPORTUNITY_GRENADIER, GroupName ItemKind
ARMOR_LOOSE, GroupName ItemKind
CLOTHING_MISC, GroupName ItemKind
CHIC_GEAR]
    [GroupName ItemKind]
-> [GroupName ItemKind] -> [GroupName ItemKind]
forall a. [a] -> [a] -> [a]
++ [GroupName ItemKind]
embedsGN [GroupName ItemKind]
-> [GroupName ItemKind] -> [GroupName ItemKind]
forall a. [a] -> [a] -> [a]
++ [GroupName ItemKind]
actorsGN [GroupName ItemKind]
-> [GroupName ItemKind] -> [GroupName ItemKind]
forall a. [a] -> [a] -> [a]
++ [GroupName ItemKind]
organsGN [GroupName ItemKind]
-> [GroupName ItemKind] -> [GroupName ItemKind]
forall a. [a] -> [a] -> [a]
++ [GroupName ItemKind]
blastsGN

pattern HARPOON, EDIBLE_PLANT, RING_OF_OPPORTUNITY_GRENADIER, ARMOR_LOOSE, CLOTHING_MISC, CHIC_GEAR :: GroupName ItemKind

-- The @UNKNOWN@ patterns don't need to be exported. Used internally.
-- They also represent singleton groups.
pattern $bFLASK_UNKNOWN :: GroupName ItemKind
$mFLASK_UNKNOWN :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
FLASK_UNKNOWN = GroupName "flask unknown"
pattern $bPOTION_UNKNOWN :: GroupName ItemKind
$mPOTION_UNKNOWN :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
POTION_UNKNOWN = GroupName "potion unknown"
pattern $bEDIBLE_PLANT_UNKNOWN :: GroupName ItemKind
$mEDIBLE_PLANT_UNKNOWN :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
EDIBLE_PLANT_UNKNOWN = GroupName "edible plant unknown"
pattern $bSCROLL_UNKNOWN :: GroupName ItemKind
$mSCROLL_UNKNOWN :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
SCROLL_UNKNOWN = GroupName "scroll unknown"
pattern $bNECKLACE_UNKNOWN :: GroupName ItemKind
$mNECKLACE_UNKNOWN :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
NECKLACE_UNKNOWN = GroupName "necklace unknown"
pattern $bRING_UNKNOWN :: GroupName ItemKind
$mRING_UNKNOWN :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
RING_UNKNOWN = GroupName "ring unknown"
pattern $bHAMMER_UNKNOWN :: GroupName ItemKind
$mHAMMER_UNKNOWN :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
HAMMER_UNKNOWN = GroupName "hammer unknown"
pattern $bGEM_UNKNOWN :: GroupName ItemKind
$mGEM_UNKNOWN :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
GEM_UNKNOWN = GroupName "gem unknown"
pattern $bCURRENCY_UNKNOWN :: GroupName ItemKind
$mCURRENCY_UNKNOWN :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
CURRENCY_UNKNOWN = GroupName "currency unknown"

pattern $bHARPOON :: GroupName ItemKind
$mHARPOON :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
HARPOON = GroupName "harpoon"
pattern $bEDIBLE_PLANT :: GroupName ItemKind
$mEDIBLE_PLANT :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
EDIBLE_PLANT = GroupName "edible plant"
pattern $bRING_OF_OPPORTUNITY_GRENADIER :: GroupName ItemKind
$mRING_OF_OPPORTUNITY_GRENADIER :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
RING_OF_OPPORTUNITY_GRENADIER = GroupName "ring of grenadier"
pattern $bARMOR_LOOSE :: GroupName ItemKind
$mARMOR_LOOSE :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
ARMOR_LOOSE = GroupName "loose armor"
pattern $bCLOTHING_MISC :: GroupName ItemKind
$mCLOTHING_MISC :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
CLOTHING_MISC = GroupName "miscellaneous clothing"
pattern $bCHIC_GEAR :: GroupName ItemKind
$mCHIC_GEAR :: forall r. GroupName ItemKind -> (Void# -> r) -> (Void# -> r) -> r
CHIC_GEAR = GroupName "chic gear"

-- * Content

content :: [ItemKind]
content :: [ItemKind]
content = [ItemKind]
items [ItemKind] -> [ItemKind] -> [ItemKind]
forall a. [a] -> [a] -> [a]
++ [ItemKind]
otherItemContent

otherItemContent :: [ItemKind]
otherItemContent :: [ItemKind]
otherItemContent = [ItemKind]
embeds [ItemKind] -> [ItemKind] -> [ItemKind]
forall a. [a] -> [a] -> [a]
++ [ItemKind]
actors [ItemKind] -> [ItemKind] -> [ItemKind]
forall a. [a] -> [a] -> [a]
++ [ItemKind]
organs [ItemKind] -> [ItemKind] -> [ItemKind]
forall a. [a] -> [a] -> [a]
++ [ItemKind]
blasts [ItemKind] -> [ItemKind] -> [ItemKind]
forall a. [a] -> [a] -> [a]
++ [ItemKind]
temporaries

items :: [ItemKind]
items :: [ItemKind]
items =
  [ItemKind
sandstoneRock, ItemKind
dart, ItemKind
spike, ItemKind
spike2, ItemKind
slingStone, ItemKind
slingBullet, ItemKind
paralizingProj, ItemKind
harpoon, ItemKind
harpoon2, ItemKind
net, ItemKind
fragmentationBomb, ItemKind
concussionBomb, ItemKind
flashBomb, ItemKind
firecrackerBomb, ItemKind
flaskTemplate, ItemKind
flask1, ItemKind
flask2, ItemKind
flask3, ItemKind
flask4, ItemKind
flask5, ItemKind
flask6, ItemKind
flask7, ItemKind
flask8, ItemKind
flask9, ItemKind
flask10, ItemKind
flask11, ItemKind
flask12, ItemKind
flask13, ItemKind
flask14, ItemKind
potionTemplate, ItemKind
potion1, ItemKind
potion2, ItemKind
potion3, ItemKind
potion4, ItemKind
potion5, ItemKind
potion6, ItemKind
potion7, ItemKind
potion8, ItemKind
potion9, ItemKind
potion10, ItemKind
potion11, ItemKind
potion12, ItemKind
potion13, ItemKind
potion14, ItemKind
potion15, ItemKind
scrollTemplate, ItemKind
scroll1, ItemKind
scroll2, ItemKind
scroll3, ItemKind
scroll4, ItemKind
scroll5, ItemKind
scroll6, ItemKind
scroll7, ItemKind
scroll8, ItemKind
scroll9, ItemKind
scroll10, ItemKind
scroll11, ItemKind
scroll12, ItemKind
scroll13, ItemKind
ediblePlantTemplate, ItemKind
ediblePlant1, ItemKind
ediblePlant2, ItemKind
ediblePlant3, ItemKind
ediblePlant4, ItemKind
ediblePlant5, ItemKind
ediblePlant6, ItemKind
ediblePlant7, ItemKind
light1, ItemKind
light2, ItemKind
light3, ItemKind
blanket, ItemKind
gorget, ItemKind
necklaceTemplate, ItemKind
necklace1, ItemKind
necklace2, ItemKind
necklace3, ItemKind
necklace4, ItemKind
necklace5, ItemKind
necklace6, ItemKind
necklace7, ItemKind
necklace8, ItemKind
necklace9, ItemKind
necklace10, ItemKind
motionScanner, ItemKind
imageItensifier, ItemKind
sightSharpening, ItemKind
ringTemplate, ItemKind
ring1, ItemKind
ring2, ItemKind
ring3, ItemKind
ring4, ItemKind
ring5, ItemKind
ring6, ItemKind
ring7, ItemKind
ring8, ItemKind
armorLeather, ItemKind
armorMail, ItemKind
meleeEnhancement, ItemKind
gloveFencing, ItemKind
gloveGauntlet, ItemKind
gloveJousting, ItemKind
hatUshanka, ItemKind
capReinforced, ItemKind
helmArmored, ItemKind
smokingJacket, ItemKind
buckler, ItemKind
shield, ItemKind
shield2, ItemKind
shield3, ItemKind
hammerTemplate, ItemKind
hammer1, ItemKind
hammer2, ItemKind
hammer3, ItemKind
hammerParalyze, ItemKind
hammerSpark, ItemKind
knife, ItemKind
daggerDropBestWeapon, ItemKind
sword, ItemKind
swordImpress, ItemKind
swordNullify, ItemKind
halberd, ItemKind
halberd2, ItemKind
halberd3, ItemKind
halberdPushActor, ItemKind
gemTemplate, ItemKind
gem1, ItemKind
gem2, ItemKind
gem3, ItemKind
gem4, ItemKind
gem5, ItemKind
currencyTemplate, ItemKind
currency, ItemKind
jumpingPole, ItemKind
seeingItem]

sandstoneRock,    dart, spike, spike2, slingStone, slingBullet, paralizingProj, harpoon, harpoon2, net, fragmentationBomb, concussionBomb, flashBomb, firecrackerBomb, flaskTemplate, flask1, flask2, flask3, flask4, flask5, flask6, flask7, flask8, flask9, flask10, flask11, flask12, flask13, flask14, potionTemplate, potion1, potion2, potion3, potion4, potion5, potion6, potion7, potion8, potion9, potion10, potion11, potion12, potion13, potion14, potion15, scrollTemplate, scroll1, scroll2, scroll3, scroll4, scroll5, scroll6, scroll7, scroll8, scroll9, scroll10, scroll11, scroll12, scroll13, ediblePlantTemplate, ediblePlant1, ediblePlant2, ediblePlant3, ediblePlant4, ediblePlant5, ediblePlant6, ediblePlant7, light1, light2, light3, blanket, gorget, necklaceTemplate, necklace1, necklace2, necklace3, necklace4, necklace5, necklace6, necklace7, necklace8, necklace9, necklace10, motionScanner, imageItensifier, sightSharpening, ringTemplate, ring1, ring2, ring3, ring4, ring5, ring6, ring7, ring8, armorLeather, armorMail, meleeEnhancement, gloveFencing, gloveGauntlet, gloveJousting, hatUshanka, capReinforced, helmArmored, smokingJacket, buckler, shield, shield2, shield3, hammerTemplate, hammer1, hammer2, hammer3, hammerParalyze, hammerSpark, knife, daggerDropBestWeapon, sword, swordImpress, swordNullify, halberd, halberd2, halberd3, halberdPushActor, gemTemplate, gem1, gem2, gem3, gem4, gem5, currencyTemplate, currency, jumpingPole, seeingItem :: ItemKind

-- Keep the dice rolls and sides in aspects small so that not too many
-- distinct items are generated (for display in item lore and for narrative
-- impact ("oh, I found the more powerful of the two variants of the item!",
-- instead of "hmm, I found one of the countless variants, a decent one").
-- In particular, for unique items, unless they inherit aspects from
-- a standard item, permit only a couple possible variants.
-- This is especially important if an item kind has multiple random aspects.
-- Instead multiply dice results, e.g., (1 `d` 3) * 5 instead of 1 `d` 15.
--
-- Beware of non-periodic non-weapon durable items with beneficial effects
-- and low timeout -- AI will starve applying such an item incessantly.

-- * Item group symbols, partially from Nethack

symbolProjectile, _symbolLauncher, symbolLight, symbolTool, symbolSpecial, symbolGold, symbolNecklace, symbolRing, symbolPotion, symbolFlask, symbolScroll, symbolTorsoArmor, symbolMiscArmor, symbolClothes, symbolShield, symbolPolearm, symbolEdged, symbolHafted, symbolWand, _symbolStaff, symbolFood :: Char

symbolProjectile :: Char
symbolProjectile = RuleContent -> Char
rsymbolProjectile RuleContent
standardRules  -- '|'
_symbolLauncher :: Char
_symbolLauncher  = '}'
symbolLight :: Char
symbolLight      = '('
symbolTool :: Char
symbolTool       = '('
symbolSpecial :: Char
symbolSpecial    = '*'  -- don't overuse, because it clashes with projectiles
symbolGold :: Char
symbolGold       = '$'  -- also gems
symbolNecklace :: Char
symbolNecklace   = '"'
symbolRing :: Char
symbolRing       = '='
symbolPotion :: Char
symbolPotion     = '!'  -- concoction, bottle, jar, vial, canister
symbolFlask :: Char
symbolFlask      = '!'
symbolScroll :: Char
symbolScroll     = '?'  -- book, note, tablet, remote, chip, card
symbolTorsoArmor :: Char
symbolTorsoArmor = '['
symbolMiscArmor :: Char
symbolMiscArmor  = '['
symbolClothes :: Char
symbolClothes    = '['
symbolShield :: Char
symbolShield     = ']'
symbolPolearm :: Char
symbolPolearm    = ')'
symbolEdged :: Char
symbolEdged      = ')'
symbolHafted :: Char
symbolHafted     = ')'
symbolWand :: Char
symbolWand       = '/'  -- magical rod, transmitter, pistol, rifle, instrument
_symbolStaff :: Char
_symbolStaff     = '_'  -- scanner
symbolFood :: Char
symbolFood       = ','  -- also body part; distinct from floor: not middle dot

-- ** Thrown weapons

sandstoneRock :: ItemKind
sandstoneRock = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolProjectile
  , iname :: Text
iname    = "sandstone rock"
  , ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
S_SANDSTONE_ROCK, 1)
               , (GroupName ItemKind
UNREPORTED_INVENTORY, 1) ]  -- too weak to spam
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Green]
  , icount :: Dice
icount   = 1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 2  -- > 1, to let AI ignore sole pieces
  , irarity :: Rarity
irarity  = [(1, 50), (10, 1)]
  , iverbHit :: Text
iverbHit = "hit"
  , iweight :: Int
iweight  = 300
  , idamage :: Dice
idamage  = 1 Int -> Int -> Dice
`d` 1
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ -16 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5
               , Flag -> Aspect
SetFlag Flag
Fragile
               , Int -> Aspect
toVelocity 70 ] -- not dense, irregular
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = "A lump of brittle sandstone rock."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
dart :: ItemKind
dart = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolProjectile
  , iname :: Text
iname    = "dart"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_ARROW, 50), (GroupName ItemKind
WEAK_ARROW, 50)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrRed]
  , icount :: Dice
icount   = 1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 4 Int -> Int -> Dice
`dL` 5
  , irarity :: Rarity
irarity  = [(1, 15), (10, 5)]
  , iverbHit :: Text
iverbHit = "prick"
  , iweight :: Int
iweight  = 40
  , idamage :: Dice
idamage  = 1 Int -> Int -> Dice
`d` 1
  , iaspects :: [Aspect]
iaspects = [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
+ 1 Int -> Int -> Dice
`d` 2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`dL` 3) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5]
                 -- only good against leather
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = "A sharp delicate dart with fins."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
spike :: ItemKind
spike = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolProjectile
  , iname :: Text
iname    = "spike"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_ARROW, 50), (GroupName ItemKind
WEAK_ARROW, 50)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Cyan]
  , icount :: Dice
icount   = 1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 4 Int -> Int -> Dice
`dL` 5
  , irarity :: Rarity
irarity  = [(1, 10), (10, 8)]
  , iverbHit :: Text
iverbHit = "nick"
  , iweight :: Int
iweight  = 150
  , idamage :: Dice
idamage  = 2 Int -> Int -> Dice
`d` 1
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (-10 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`dL` 3) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5
                   -- heavy vs armor
               , Flag -> Aspect
SetFlag Flag
MinorEffects
               , Int -> Aspect
toVelocity 70 ]  -- hitting with tip costs speed
  , ieffects :: [Effect]
ieffects = [ GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_SINGLE_SPARK  -- when hitting enemy
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_SINGLE_SPARK) ]  -- at wall hit
      -- this results in a wordy item synopsis, but it's OK, the spark really
      -- is useful in some situations, not just a flavour
  , idesc :: Text
idesc    = "A cruel long nail with small head."  -- "Much inferior to arrows though, especially given the contravariance problems."  -- funny, but destroy the suspension of disbelief; this is supposed to be a Lovecraftian horror and any hilarity must ensue from the failures in making it so and not from actively trying to be funny; also, mundane objects are not supposed to be scary or transcendental; the scare is in horrors from the abstract dimension visiting our ordinary reality; without the contrast there's no horror and no wonder, so also the magical items must be contrasted with ordinary XIX century and antique items
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
spike2 :: ItemKind
spike2 = ItemKind
spike
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 2), (GroupName ItemKind
ANY_ARROW, 1), (GroupName ItemKind
WEAK_ARROW, 1)]
  , icount :: Dice
icount   = 6 Int -> Int -> Dice
`dL` 5
  , iverbHit :: Text
iverbHit = "penetrate"
  , iweight :: Int
iweight  = 200
  , idamage :: Dice
idamage = 4 Int -> Int -> Dice
`d` 1
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (-10 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`dL` 3) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5
               , Flag -> Aspect
SetFlag Flag
MinorEffects
               , Dice -> [Aspect] -> [Aspect] -> Aspect
Odds (10 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 1 Int -> Int -> Dice
`dL` 10) [] [Int -> Aspect
toVelocity 70] ]
                   -- at deep levels sometimes even don't limit velocity
  , idesc :: Text
idesc    = "A jagged skewer of rusty metal."
  }
slingStone :: ItemKind
slingStone = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolProjectile
  , iname :: Text
iname    = "sling stone"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 5), (GroupName ItemKind
ANY_ARROW, 100)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Blue]
  , icount :: Dice
icount   = 1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 3 Int -> Int -> Dice
`dL` 4
  , irarity :: Rarity
irarity  = [(1, 1), (10, 20)]
  , iverbHit :: Text
iverbHit = "batter"
  , iweight :: Int
iweight  = 200
  , idamage :: Dice
idamage  = 1 Int -> Int -> Dice
`d` 1
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (-10 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`dL` 3) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5
                   -- heavy, to bludgeon through armor
               , Flag -> Aspect
SetFlag Flag
MinorEffects
               , Int -> Aspect
toVelocity 150 ]
  , ieffects :: [Effect]
ieffects = [ GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_SINGLE_SPARK  -- when hitting enemy
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_SINGLE_SPARK) ]  -- at wall hit
  , idesc :: Text
idesc    = "A round stone, carefully sized and smoothed to fit the pouch of a standard string and cloth sling."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
slingBullet :: ItemKind
slingBullet = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolProjectile
  , iname :: Text
iname    = "sling bullet"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 5), (GroupName ItemKind
ANY_ARROW, 100)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrBlack]
  , icount :: Dice
icount   = 1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 6 Int -> Int -> Dice
`dL` 4
  , irarity :: Rarity
irarity  = [(1, 1), (10, 15)]
  , iverbHit :: Text
iverbHit = "slug"
  , iweight :: Int
iweight  = 28
  , idamage :: Dice
idamage  = 1 Int -> Int -> Dice
`d` 1
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (-17 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`dL` 3) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5
                   -- not too good against armor
               , ThrowMod -> Aspect
ToThrow (ThrowMod -> Aspect) -> ThrowMod -> Aspect
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int -> ThrowMod
ThrowMod 200 100 2 ]  -- piercing
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = "Small almond-shaped leaden projectile that weighs more than the sling used to tie the bag. It doesn't drop out of the sling's pouch when swung and doesn't snag when released. Known to pierce through flesh, at least at maximum speed."  -- we lie, it doesn't slow down in our model; but it stops piercing alright
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }

-- ** Exotic thrown weapons

-- Identified, because shape (and name) says it all. Detailed aspects id by use.
-- This is an extremely large value for @Paralyze@. Normally for such values
-- we should instead use condition that disables (almost) all stats,
-- except @SkWait@, so that the player can switch leader and not be
-- helpless nor experience instadeath (unless his party is 1-person
-- or the actor is isolated, but that's usually player's fault).
paralizingProj :: ItemKind
paralizingProj = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolProjectile
  , iname :: Text
iname    = "bolas set"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrGreen]
  , icount :: Dice
icount   = 1 Int -> Int -> Dice
`dL` 4
  , irarity :: Rarity
irarity  = [(5, 5), (10, 5)]
  , iverbHit :: Text
iverbHit = "entangle"
  , iweight :: Int
iweight  = 500
  , idamage :: Dice
idamage  = 1 Int -> Int -> Dice
`d` 1
  , iaspects :: [Aspect]
iaspects = [Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ -14 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5]
  , ieffects :: [Effect]
ieffects = [Dice -> Effect
Paralyze 15, Int -> Dice -> Effect
Discharge 1 100]
  , idesc :: Text
idesc    = "Wood balls tied with hemp rope. The foe is unlikely to use its main weapon while fighting for balance."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
harpoon :: ItemKind
harpoon = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolProjectile
  , iname :: Text
iname    = "harpoon"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
HARPOON, 100)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Brown]
  , icount :: Dice
icount   = 1 Int -> Int -> Dice
`dL` 5
  , irarity :: Rarity
irarity  = [(10, 10)]
  , iverbHit :: Text
iverbHit = "hook"
  , iweight :: Int
iweight  = 750
  , idamage :: Dice
idamage  = 5 Int -> Int -> Dice
`d` 1
  , iaspects :: [Aspect]
iaspects = [Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (-10 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`dL` 3) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5]
  , ieffects :: [Effect]
ieffects = [ ThrowMod -> Effect
PullActor (Int -> Int -> Int -> ThrowMod
ThrowMod 200 50 1)  -- 1 step, fast
               , Effect
Yell ]  -- yell, because brutal
  , idesc :: Text
idesc    = "The cruel, barbed head lodges in its victim so painfully that the weakest tug of the thin line sends the victim flying."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
harpoon2 :: ItemKind
harpoon2 = ItemKind
harpoon
  { iname :: Text
iname    = "whaling harpoon"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 5), (GroupName ItemKind
HARPOON, 2)]
  , icount :: Dice
icount   = 2 Int -> Int -> Dice
`dL` 5
  , iweight :: Int
iweight  = 1000
  , idamage :: Dice
idamage  = 10 Int -> Int -> Dice
`d` 1
  , idesc :: Text
idesc    = "With a brittle, barbed head and thick cord, this ancient weapon is designed for formidable prey."
  }
net :: ItemKind
net = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolProjectile
  , iname :: Text
iname    = "net"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrGreen]
  , icount :: Dice
icount   = 1 Int -> Int -> Dice
`dL` 3
  , irarity :: Rarity
irarity  = [(5, 5), (10, 7)]
  , iverbHit :: Text
iverbHit = "entangle"
  , iweight :: Int
iweight  = 1000
  , idamage :: Dice
idamage  = 2 Int -> Int -> Dice
`d` 1
  , iaspects :: [Aspect]
iaspects = [Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ -14 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5]
  , 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)
               , Int -> Int -> CStore -> GroupName ItemKind -> Effect
DropItem Int
forall a. Bounded a => a
maxBound 1 CStore
CEqp GroupName ItemKind
ARMOR_LOOSE
                   -- only one of each kind is dropped, because no rubbish
                   -- in this group and so no risk of exploit
               , ThrowMod -> Effect
SendFlying (Int -> Int -> Int -> ThrowMod
ThrowMod 100 50 1) ]  -- 1 step; painful
  , idesc :: Text
idesc    = "A wide net with weights along the edges. Entangles armor and restricts movement."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }

-- ** Explosives, with the only effect being @Explode@

fragmentationBomb :: ItemKind
fragmentationBomb = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolProjectile
  , iname :: Text
iname    = "clay pot"
      -- clay pot filled with black powder; fragmentation comes from the clay
      -- shards, so it's not obvious if it's a weapon or just storage method;
      -- deflagration, not detonation, so large mass and hard container
      -- required not to burn harmlessly; improvised short fuze
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
EXPLOSIVE, 200)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Red]
  , icount :: Dice
icount   = 1 Int -> Int -> Dice
`dL` 5  -- many, because not very intricate
  , irarity :: Rarity
irarity  = [(5, 8), (10, 5)]
  , iverbHit :: Text
iverbHit = "thud"
  , iweight :: Int
iweight  = 3000  -- low velocity due to weight
  , idamage :: Dice
idamage  = 0  -- heavy and hard, but let's not confuse with blast damage
  , iaspects :: [Aspect]
iaspects = [ Text -> Aspect
ELabel "of black powder"
               , Flag -> Aspect
SetFlag Flag
Lobable, Flag -> Aspect
SetFlag Flag
Fragile ]
  , ieffects :: [Effect]
ieffects = [ GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_FOCUSED_FRAGMENTATION
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_VIOLENT_FRAGMENTATION) ]
  , idesc :: Text
idesc    = "The practical application of science."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
concussionBomb :: ItemKind
concussionBomb = ItemKind
fragmentationBomb
  { iname :: Text
iname    = "satchel"
      -- slightly stabilized nitroglycerine in a soft satchel, hence
      -- no fragmentation, but huge shock wave despite small size and lack of
      -- strong container to build up pressure (hence only mild hearing loss);
      -- indoors helps the shock wave; unstable enough that no fuze required
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Magenta]
  , iverbHit :: Text
iverbHit = "flap"
  , iweight :: Int
iweight  = 400
  , iaspects :: [Aspect]
iaspects = [ Text -> Aspect
ELabel "of mining charges"
               , Flag -> Aspect
SetFlag Flag
Lobable, Flag -> Aspect
SetFlag Flag
Fragile
               , Int -> Aspect
toVelocity 70 ]  -- flappy and so slow
  , ieffects :: [Effect]
ieffects = [ GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_FOCUSED_CONCUSSION
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_VIOLENT_CONCUSSION) ]
  , idesc :: Text
idesc    = "Avoid sudden movements."
  }
-- Not flashbang, because powerful bang without fragmentation is harder
-- to manufacture (requires an oxidizer and steel canister with holes).
-- The bang would also paralyze and/or lower the movement skill
-- (out of balance due to ear trauma).
flashBomb :: ItemKind
flashBomb = ItemKind
fragmentationBomb
  { iname :: Text
iname    = "magnesium ribbon"  -- filled with magnesium flash powder
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrYellow]  -- avoid @BrWhite@; looks wrong in dark
  , iverbHit :: Text
iverbHit = "flash"
  , iweight :: Int
iweight  = 400
  , iaspects :: [Aspect]
iaspects = [ Flag -> Aspect
SetFlag Flag
Lobable, Flag -> Aspect
SetFlag Flag
Fragile
               , Int -> Aspect
toVelocity 70 ]  -- bad shape for throwing
  , ieffects :: [Effect]
ieffects = [GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_FOCUSED_FLASH, Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_VIOLENT_FLASH)]
  , idesc :: Text
idesc    = "For dramatic entrances and urgent exits."
  }
firecrackerBomb :: ItemKind
firecrackerBomb = ItemKind
fragmentationBomb
  { iname :: Text
iname = "roll"  -- not fireworks, as they require outdoors
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrMagenta]
  , irarity :: Rarity
irarity  = [(1, 5), (5, 6)]  -- a toy, if deadly
  , iverbHit :: Text
iverbHit = "crack"  -- a pun, matches the verb from "ItemKindBlast"
  , iweight :: Int
iweight  = 1000
  , iaspects :: [Aspect]
iaspects = [Flag -> Aspect
SetFlag Flag
Lobable, Flag -> Aspect
SetFlag Flag
Fragile]
  , ieffects :: [Effect]
ieffects = [GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_FIRECRACKER, Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_FIRECRACKER)]
  , idesc :: Text
idesc    = "String and paper, concealing a deadly surprise."
  }

-- ** Exploding consumables.

-- Not identified, because they are perfect for the id-by-use fun,
-- due to effects. They are fragile and upon hitting the ground explode
-- for effects roughly corresponding to their normal effects.
-- Whether to hit with them or explode them close to the target
-- is intended to be an interesting tactical decision.

-- Flasks are intended to be thrown. They are often not natural: maths, magic,
-- distillery. In fact, they cover all temporary conditions, except those
-- for stats resistance and regeneration. They never heal, directly
-- nor indirectly (regen), so may be thrown without the risk of wasting
-- precious HP.
--
-- There is no flask nor condition that only does Calm or max Calm depletion,
-- because Calm reduced often via combat, etc.

flaskTemplate :: ItemKind
flaskTemplate = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolFlask
  , iname :: Text
iname    = "flask"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
FLASK_UNKNOWN, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipGlassPlain [Color]
darkCol [Flavour] -> [Flavour] -> [Flavour]
forall a. [a] -> [a] -> [a]
++ [Color] -> [Flavour]
zipGlassFancy [Color]
darkCol
               [Flavour] -> [Flavour] -> [Flavour]
forall a. [a] -> [a] -> [a]
++ [Color] -> [Flavour]
zipLiquid [Color]
darkCol
  , icount :: Dice
icount   = 1 Int -> Int -> Dice
`dL` 3
  , irarity :: Rarity
irarity  = [(1, 7), (10, 3)]
  , iverbHit :: Text
iverbHit = "splash"
  , iweight :: Int
iweight  = 500
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ GroupName ItemKind -> Aspect
PresentAs GroupName ItemKind
FLASK_UNKNOWN, Flag -> Aspect
SetFlag Flag
Lobable, Flag -> Aspect
SetFlag Flag
Fragile
               , Int -> Aspect
toVelocity 60 ]  -- oily, rather bad grip
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = "A flask of oily liquid of a suspect color. Something seems to be moving inside. Double dose causes twice longer effect. Triple dose is not advisable, since the active substance is never without unhealty side-efects and often dissolved in large volumes of alcohol."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
flask1 :: ItemKind
flask1 = ItemKind
flaskTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_FLASK, 100), (GroupName ItemKind
EXPLOSIVE, 100)
               , (GroupName ItemKind
ANY_GLASS, 100) ]
  , icount :: Dice
icount   = 1 Int -> Int -> Dice
`dL` 5
  , irarity :: Rarity
irarity  = [(10, 10)]
  , iaspects :: [Aspect]
iaspects = Text -> Aspect
ELabel "of strength renewal brew"
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
flaskTemplate
  , ieffects :: [Effect]
ieffects = [ GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_STRENGTHENED (20 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 5)
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_DENSE_SHOWER) ]
  }
flask2 :: ItemKind
flask2 = ItemKind
flaskTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_FLASK, 100), (GroupName ItemKind
EXPLOSIVE, 100)
               , (GroupName ItemKind
ANY_GLASS, 100) ]
  , iaspects :: [Aspect]
iaspects = Text -> Aspect
ELabel "of weakness brew"
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
flaskTemplate
  , ieffects :: [Effect]
ieffects = [ GroupName ItemKind -> Dice -> Effect
toOrganBad GroupName ItemKind
S_WEAKENED (20 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 5)
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_SPARSE_SHOWER) ]
  }
flask3 :: ItemKind
flask3 = ItemKind
flaskTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_FLASK, 100), (GroupName ItemKind
EXPLOSIVE, 100)
               , (GroupName ItemKind
ANY_GLASS, 100) ]
  , iaspects :: [Aspect]
iaspects = Text -> Aspect
ELabel "of melee protective balm"
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
flaskTemplate
  , ieffects :: [Effect]
ieffects = [ GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_PROTECTED_FROM_MELEE (20 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 5)
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_MELEE_PROTECTIVE_BALM) ]
  }
flask4 :: ItemKind
flask4 = ItemKind
flaskTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_FLASK, 100), (GroupName ItemKind
EXPLOSIVE, 100)
               , (GroupName ItemKind
ANY_GLASS, 100) ]
  , iaspects :: [Aspect]
iaspects = Text -> Aspect
ELabel "of ranged protective balm"
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
flaskTemplate
  , ieffects :: [Effect]
ieffects = [ GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_PROTECTED_FROM_RANGED (20 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 5)
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_RANGE_PROTECTIVE_BALM) ]
  }
flask5 :: ItemKind
flask5 = ItemKind
flaskTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_FLASK, 100), (GroupName ItemKind
EXPLOSIVE, 100)
               , (GroupName ItemKind
ANY_GLASS, 100) ]
  , iaspects :: [Aspect]
iaspects = Text -> Aspect
ELabel "of PhD defense questions"
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
flaskTemplate
  , ieffects :: [Effect]
ieffects = [ GroupName ItemKind -> Dice -> Effect
toOrganBad GroupName ItemKind
S_DEFENSELESS (20 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 5)
               , Effect
Impress
               , DetectKind -> Int -> Effect
Detect DetectKind
DetectExit 20
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_DEFENSELESSNESS_RUNOUT) ]
  }
flask6 :: ItemKind
flask6 = ItemKind
flaskTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_FLASK, 100), (GroupName ItemKind
EXPLOSIVE, 100)
               , (GroupName ItemKind
ANY_GLASS, 100) ]
  , irarity :: Rarity
irarity  = [(1, 1)]  -- not every playthrough needs one
  , iaspects :: [Aspect]
iaspects = Text -> Aspect
ELabel "of resolution"
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
flaskTemplate
  , ieffects :: [Effect]
ieffects = [ GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_RESOLUTE (500 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 200)  -- long, for scouting
               , Int -> Effect
RefillCalm 60  -- not to make it a drawback, via @calmEnough@
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_RESOLUTION_DUST) ]
  }
flask7 :: ItemKind
flask7 = ItemKind
flaskTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_FLASK, 100), (GroupName ItemKind
EXPLOSIVE, 100)
               , (GroupName ItemKind
ANY_GLASS, 100) ]
  , icount :: Dice
icount   = 1 Int -> Int -> Dice
`d` 2  -- too powerful en masse
  , iaspects :: [Aspect]
iaspects = Text -> Aspect
ELabel "of haste brew"
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
flaskTemplate
  , ieffects :: [Effect]
ieffects = [ GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_HASTED (20 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 5)
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_HASTE_SPRAY) ]
  }
flask8 :: ItemKind
flask8 = ItemKind
flaskTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_FLASK, 100), (GroupName ItemKind
EXPLOSIVE, 100)
               , (GroupName ItemKind
ANY_GLASS, 100) ]
  , iaspects :: [Aspect]
iaspects = Text -> Aspect
ELabel "of eye drops"
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
flaskTemplate
  , ieffects :: [Effect]
ieffects = [ GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_FAR_SIGHTED (40 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 10)
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_EYE_DROP) ]
  }
flask9 :: ItemKind
flask9 = ItemKind
flaskTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_FLASK, 100), (GroupName ItemKind
EXPLOSIVE, 100)
               , (GroupName ItemKind
ANY_GLASS, 100) ]
  , irarity :: Rarity
irarity  = [(10, 2)]  -- not very useful right now
  , iaspects :: [Aspect]
iaspects = Text -> Aspect
ELabel "of smelly concoction"
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
flaskTemplate
  , ieffects :: [Effect]
ieffects = [ GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_KEEN_SMELLING (40 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 10)
               , DetectKind -> Int -> Effect
Detect DetectKind
DetectActor 10  -- make it at least slightly useful
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_SMELLY_DROPLET) ]
  }
flask10 :: ItemKind
flask10 = ItemKind
flaskTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_FLASK, 100), (GroupName ItemKind
EXPLOSIVE, 100)
               , (GroupName ItemKind
ANY_GLASS, 100) ]
  , irarity :: Rarity
irarity  = [(10, 2)]  -- not very useful right now
  , iaspects :: [Aspect]
iaspects = Text -> Aspect
ELabel "of cat tears"
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
flaskTemplate
  , ieffects :: [Effect]
ieffects = [ GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_SHINY_EYED (40 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 10)
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_EYE_SHINE) ]
  }
flask11 :: ItemKind
flask11 = ItemKind
flaskTemplate
  { iname :: Text
iname    = "bottle"
  , ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_FLASK, 100), (GroupName ItemKind
EXPLOSIVE, 100)
               , (GroupName ItemKind
ANY_GLASS, 100) ]
  , icount :: Dice
icount   = 1 Int -> Int -> Dice
`d` 3  -- the only one sometimes giving away its identity
  , iaspects :: [Aspect]
iaspects = Text -> Aspect
ELabel "of whiskey"
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
flaskTemplate
  , ieffects :: [Effect]
ieffects = [ GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_DRUNK (20 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 5)
               , Dice -> Effect
Burn 10, Int -> Effect
RefillHP 10, Effect
Yell
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_WHISKEY_SPRAY) ]
  }
flask12 :: ItemKind
flask12 = ItemKind
flaskTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_FLASK, 100), (GroupName ItemKind
EXPLOSIVE, 100)
               , (GroupName ItemKind
ANY_GLASS, 100) ]
  , iaspects :: [Aspect]
iaspects = Text -> Aspect
ELabel "of bait cocktail"
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
flaskTemplate
  , ieffects :: [Effect]
ieffects = [ GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_DRUNK (20 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 5)
               , Dice -> Effect
Burn 1, Int -> Effect
RefillHP 3  -- risky exploit possible, good
               , GroupName ItemKind -> Dice -> Effect
Summon GroupName ItemKind
MOBILE_ANIMAL 1
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Dice -> Effect
Summon GroupName ItemKind
MOBILE_ANIMAL 1)
               , Effect -> Effect
OnSmash Effect
Impress  -- mildly useful when thrown
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_WASTE) ]
  }
flask13 :: ItemKind
flask13 = ItemKind
flaskTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_FLASK, 100), (GroupName ItemKind
EXPLOSIVE, 100)
               , (GroupName ItemKind
ANY_GLASS, 100) ]
  , iaspects :: [Aspect]
iaspects = Text -> Aspect
ELabel "of poison"
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
flaskTemplate
  , ieffects :: [Effect]
ieffects = [ GroupName ItemKind -> Effect
toOrganNoTimer GroupName ItemKind
S_POISONED, GroupName ItemKind -> Effect
toOrganNoTimer GroupName ItemKind
S_POISONED  -- x2
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_POISON_CLOUD) ]
  }
flask14 :: ItemKind
flask14 = ItemKind
flaskTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_FLASK, 100), (GroupName ItemKind
EXPLOSIVE, 100)
               , (GroupName ItemKind
ANY_GLASS, 100) ]
  , iaspects :: [Aspect]
iaspects = Text -> Aspect
ELabel "of calamity"
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
flaskTemplate
  , ieffects :: [Effect]
ieffects = [ GroupName ItemKind -> Effect
toOrganNoTimer GroupName ItemKind
S_POISONED
               , GroupName ItemKind -> Dice -> Effect
toOrganBad GroupName ItemKind
S_WEAKENED (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_DEFENSELESS (20 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 5)
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_GLASS_HAIL) ]  -- enough glass to cause that
  }

-- Vials are often not intended to be thrown. They usually natural,
-- including natural stat boosts. They also include the only healing
-- consumables in the game, apart of elixirs and, to a limited extent, fruits.
-- They appear deeper than most flasks. Various configurations of effects.
-- A different class of effects is on scrolls and mechanical items.
-- Some are shared.

potionTemplate :: ItemKind
potionTemplate = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolPotion
  , iname :: Text
iname    = "potion"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
POTION_UNKNOWN, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipLiquid [Color]
brightCol [Flavour] -> [Flavour] -> [Flavour]
forall a. [a] -> [a] -> [a]
++ [Color] -> [Flavour]
zipPlain [Color]
brightCol [Flavour] -> [Flavour] -> [Flavour]
forall a. [a] -> [a] -> [a]
++ [Color] -> [Flavour]
zipFancy [Color]
brightCol
  , icount :: Dice
icount   = 1 Int -> Int -> Dice
`dL` 3
  , irarity :: Rarity
irarity  = [(1, 10), (10, 6)]
  , iverbHit :: Text
iverbHit = "splash"
  , iweight :: Int
iweight  = 200
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ GroupName ItemKind -> Aspect
PresentAs GroupName ItemKind
POTION_UNKNOWN, Flag -> Aspect
SetFlag Flag
Lobable, Flag -> Aspect
SetFlag Flag
Fragile
               , Int -> Aspect
toVelocity 50 ]  -- oily, small momentum due to small size
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = "A vial of bright, frothing concoction. The best medicine that nature has to offer for wounds, ailments and mood swings."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
potion1 :: ItemKind
potion1 = ItemKind
potionTemplate
  { iname :: Text
iname    = "vial"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_POTION, 100), (GroupName ItemKind
ANY_GLASS, 100)]
  , icount :: Dice
icount   = 3 Int -> Int -> Dice
`dL` 1  -- very useful, despite appearances
  , iaspects :: [Aspect]
iaspects = Text -> Aspect
ELabel "of rose water"
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
potionTemplate
  , ieffects :: [Effect]
ieffects = [ Effect
Impress, GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_ROSE_SMELLING (80 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 20)
               , Effect -> Effect
OnSmash Effect
ApplyPerfume, Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_FRAGRANCE) ]
  }
potion2 :: ItemKind
potion2 = ItemKind
potionTemplate
  { iname :: Text
iname    = "the Potion"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
TREASURE, 100), (GroupName ItemKind
ANY_GLASS, 100)]
  , icount :: Dice
icount   = 1
  , irarity :: Rarity
irarity  = [(5, 8), (10, 8)]
  , iaspects :: [Aspect]
iaspects = [ Flag -> Aspect
SetFlag Flag
Unique, Text -> Aspect
ELabel "of Attraction"
               , Flag -> Aspect
SetFlag Flag
Precious, Flag -> Aspect
SetFlag Flag
Lobable, Flag -> Aspect
SetFlag Flag
Fragile
               , Int -> Aspect
toVelocity 50 ]  -- identified
  , ieffects :: [Effect]
ieffects = [ Effect
Dominate
               , GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_HASTED (20 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 5)
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_PHEROMONE)
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_HASTE_SPRAY) ]
  , idesc :: Text
idesc    = "The liquid fizzes with energy."
  }
potion3 :: ItemKind
potion3 = ItemKind
potionTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_POTION, 100), (GroupName ItemKind
ANY_GLASS, 100)]
  , ieffects :: [Effect]
ieffects = [ Int -> Effect
RefillHP 5, Int -> Int -> CStore -> GroupName ItemKind -> Effect
DropItem 1 Int
forall a. Bounded a => a
maxBound CStore
COrgan GroupName ItemKind
S_POISONED
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_HEALING_MIST) ]
  }
potion4 :: ItemKind
potion4 = ItemKind
potionTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_POTION, 100), (GroupName ItemKind
ANY_GLASS, 100)]
  , irarity :: Rarity
irarity  = [(1, 6), (10, 10)]
  , ieffects :: [Effect]
ieffects = [ Int -> Effect
RefillHP 10
               , Int -> Int -> CStore -> GroupName ItemKind -> Effect
DropItem Int
forall a. Bounded a => a
maxBound Int
forall a. Bounded a => a
maxBound CStore
COrgan GroupName ItemKind
CONDITION
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_HEALING_MIST_2) ]
  }
potion5 :: ItemKind
potion5 = ItemKind
potionTemplate
  { iname :: Text
iname    = "ampoule"  -- probably filled with nitroglycerine, but let's
                          -- not mix fantasy with too much technical jargon
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_POTION, 100), (GroupName ItemKind
ANY_GLASS, 100)]
  , icount :: Dice
icount   = 3 Int -> Int -> Dice
`dL` 1
  , ieffects :: [Effect]
ieffects = [ Int -> Int -> CStore -> GroupName ItemKind -> Effect
DropItem 1 Int
forall a. Bounded a => a
maxBound CStore
COrgan GroupName ItemKind
CONDITION
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_VIOLENT_CONCUSSION) ]
      -- not fragmentation nor glass hail, because not enough glass
  }
potion6 :: ItemKind
potion6 = ItemKind
potionTemplate
  -- needs to be common to show at least a portion of effects
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_POTION, 100), (GroupName ItemKind
ANY_GLASS, 100)]
  , icount :: Dice
icount   = 3 Int -> Int -> Dice
`dL` 1  -- always as many as possible on this level
                         -- without giving away potion identity
  , irarity :: Rarity
irarity  = [(1, 12)]
  , ieffects :: [Effect]
ieffects = [ [Effect] -> Effect
OneOf [ Int -> Effect
RefillHP 10, Int -> Effect
RefillHP 5, Dice -> Effect
Burn 5
                       , Int -> Int -> CStore -> GroupName ItemKind -> Effect
DropItem 1 Int
forall a. Bounded a => a
maxBound CStore
COrgan GroupName ItemKind
S_POISONED
                       , GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_STRENGTHENED (20 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 5) ]
               , Effect -> Effect
OnSmash ([Effect] -> Effect
OneOf [ GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_DENSE_SHOWER
                                , GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_SPARSE_SHOWER
                                , GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_MELEE_PROTECTIVE_BALM
                                , GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_RANGE_PROTECTIVE_BALM
                                , GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_DEFENSELESSNESS_RUNOUT ]) ]
  }
potion7 :: ItemKind
potion7 = ItemKind
potionTemplate
  -- needs to be common to show at least a portion of effects
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_POTION, 100), (GroupName ItemKind
ANY_GLASS, 100)]
  , icount :: Dice
icount   = 3 Int -> Int -> Dice
`dL` 1
  , irarity :: Rarity
irarity  = [(10, 10)]
  , ieffects :: [Effect]
ieffects = [ Effect
Impress
               , [Effect] -> Effect
OneOf [ Int -> Effect
RefillHP 20, Int -> Effect
RefillHP 10, Dice -> Effect
Burn 10
                       , Int -> Int -> CStore -> GroupName ItemKind -> Effect
DropItem 1 Int
forall a. Bounded a => a
maxBound CStore
COrgan GroupName ItemKind
S_POISONED
                       , GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_HASTED (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) ]
               , Effect -> Effect
OnSmash ([Effect] -> Effect
OneOf [ GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_HEALING_MIST_2
                                , GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_WOUNDING_MIST
                                , GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_DISTRESSING_ODOR
                                , GroupName ItemKind -> Effect
Explode (GroupName ItemKind -> Effect) -> GroupName ItemKind -> Effect
forall a b. (a -> b) -> a -> b
$ GroupName ItemKind -> GroupName ItemKind
blastNoStatOf GroupName ItemKind
S_IMPATIENT
                                , GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_HASTE_SPRAY
                                , GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_SLOWNESS_MIST
                                , GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_FRAGRANCE
                                , GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_VIOLENT_FLASH ]) ]
  }
potion8 :: ItemKind
potion8 = ItemKind
potionTemplate
  { iname :: Text
iname    = "the Potion"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
TREASURE, 100), (GroupName ItemKind
ANY_GLASS, 100)]
  , icount :: Dice
icount   = 1
  , irarity :: Rarity
irarity  = [(10, 5)]
  , iaspects :: [Aspect]
iaspects = [ Flag -> Aspect
SetFlag Flag
Unique, Text -> Aspect
ELabel "of Love"
               , Flag -> Aspect
SetFlag Flag
Precious, Flag -> Aspect
SetFlag Flag
Lobable, Flag -> Aspect
SetFlag Flag
Fragile
               , Int -> Aspect
toVelocity 50 ]  -- identified
  , ieffects :: [Effect]
ieffects = [ Int -> Effect
RefillHP 60, Int -> Effect
RefillCalm (-60)
               , GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_ROSE_SMELLING (80 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 20)
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_HEALING_MIST_2)
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_DISTRESSING_ODOR) ]
  , idesc :: Text
idesc    = "Perplexing swirls of intense, compelling colour."
  }
potion9 :: ItemKind
potion9 = ItemKind
potionTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_POTION, 100), (GroupName ItemKind
ANY_GLASS, 100)]
  , irarity :: Rarity
irarity  = [(10, 5)]
  , iaspects :: [Aspect]
iaspects = Text -> Aspect
ELabel "of grenadier focus"
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
potionTemplate
  , ieffects :: [Effect]
ieffects = [ GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_MORE_PROJECTING (40 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 10)
               , GroupName ItemKind -> Dice -> Effect
toOrganBad GroupName ItemKind
S_PACIFIED (5 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 3)
                   -- the malus has to be weak, or would be too good
                   -- when thrown at foes
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode (GroupName ItemKind -> Effect) -> GroupName ItemKind -> Effect
forall a b. (a -> b) -> a -> b
$ GroupName ItemKind -> GroupName ItemKind
blastBonusStatOf GroupName ItemKind
S_MORE_PROJECTING)
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode (GroupName ItemKind -> Effect) -> GroupName ItemKind -> Effect
forall a b. (a -> b) -> a -> b
$ GroupName ItemKind -> GroupName ItemKind
blastNoStatOf GroupName ItemKind
S_PACIFIED) ]
  , idesc :: Text
idesc    = "Thick, sluggish fluid with violently-bursting bubbles."
  }
potion10 :: ItemKind
potion10 = ItemKind
potionTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_POTION, 100), (GroupName ItemKind
ANY_GLASS, 100)]
  , irarity :: Rarity
irarity  = [(10, 8)]
  , iaspects :: [Aspect]
iaspects = Text -> Aspect
ELabel "of frenzy"
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
potionTemplate
  , ieffects :: [Effect]
ieffects = [ Effect
Yell
               , GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_STRENGTHENED (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_RETAINING (5 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 3)
               , GroupName ItemKind -> Dice -> Effect
toOrganBad GroupName ItemKind
S_FRENZIED (40 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 10)
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_DENSE_SHOWER)
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode (GroupName ItemKind -> Effect) -> GroupName ItemKind -> Effect
forall a b. (a -> b) -> a -> b
$ GroupName ItemKind -> GroupName ItemKind
blastNoStatOf GroupName ItemKind
S_RETAINING)    -- more
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode (GroupName ItemKind -> Effect) -> GroupName ItemKind -> Effect
forall a b. (a -> b) -> a -> b
$ GroupName ItemKind -> GroupName ItemKind
blastNoStatOf GroupName ItemKind
S_RETAINING) ]  -- explosion
  }
potion11 :: ItemKind
potion11 = ItemKind
potionTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_POTION, 100), (GroupName ItemKind
ANY_GLASS, 100)]
  , irarity :: Rarity
irarity  = [(10, 8)]
  , iaspects :: [Aspect]
iaspects = Text -> Aspect
ELabel "of panic"
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
potionTemplate
  , ieffects :: [Effect]
ieffects = [ Int -> Effect
RefillCalm (-30)
               , GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_HASTED (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_WEAKENED (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_WITHHOLDING (10 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 5)
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_HASTE_SPRAY)
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_SPARSE_SHOWER)
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode (GroupName ItemKind -> Effect) -> GroupName ItemKind -> Effect
forall a b. (a -> b) -> a -> b
$ GroupName ItemKind -> GroupName ItemKind
blastNoStatOf GroupName ItemKind
S_WITHHOLDING) ]
  }
potion12 :: ItemKind
potion12 = ItemKind
potionTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_POTION, 100), (GroupName ItemKind
ANY_GLASS, 100)]
  , irarity :: Rarity
irarity  = [(10, 8)]
  , iaspects :: [Aspect]
iaspects = Text -> Aspect
ELabel "of quicksilver"
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
potionTemplate
  , ieffects :: [Effect]
ieffects = [ GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_HASTED (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_BLIND (10 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 5)
               , GroupName ItemKind -> Dice -> Effect
toOrganBad GroupName ItemKind
S_IMMOBILE (5 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 5)
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_HASTE_SPRAY)
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_IRON_FILING)
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode (GroupName ItemKind -> Effect) -> GroupName ItemKind -> Effect
forall a b. (a -> b) -> a -> b
$ GroupName ItemKind -> GroupName ItemKind
blastNoStatOf GroupName ItemKind
S_IMMOBILE) ]
  }
potion13 :: ItemKind
potion13 = ItemKind
potionTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_FLASK, 100), (GroupName ItemKind
EXPLOSIVE, 100)
               , (GroupName ItemKind
ANY_GLASS, 100) ]
  , irarity :: Rarity
irarity  = [(10, 4)]
  , iaspects :: [Aspect]
iaspects = Text -> Aspect
ELabel "of slow resistance"
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
potionTemplate
  , ieffects :: [Effect]
ieffects = [ GroupName ItemKind -> Effect
toOrganNoTimer GroupName ItemKind
S_SLOW_RESISTANT
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_ANTI_SLOW_MIST) ]
  }
potion14 :: ItemKind
potion14 = ItemKind
potionTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_FLASK, 100), (GroupName ItemKind
EXPLOSIVE, 100)
               , (GroupName ItemKind
ANY_GLASS, 100) ]
  , irarity :: Rarity
irarity  = [(10, 4)]
  , iaspects :: [Aspect]
iaspects = Text -> Aspect
ELabel "of poison resistance"
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
potionTemplate
  , ieffects :: [Effect]
ieffects = [ GroupName ItemKind -> Effect
toOrganNoTimer GroupName ItemKind
S_POISON_RESISTANT
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_ANTIDOTE_MIST) ]
  }
-- The player has full control over throwing the flask at his party,
-- so he can milk the explosion, so it has to be much weaker, so a weak
-- healing effect is enough. OTOH, throwing a harmful flask at many enemies
-- at once is not easy to arrange, so these explosions can stay powerful.
potion15 :: ItemKind
potion15 = ItemKind
potionTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_FLASK, 100), (GroupName ItemKind
EXPLOSIVE, 100)
               , (GroupName ItemKind
ANY_GLASS, 100) ]
  , irarity :: Rarity
irarity  = [(1, 2), (10, 12)]
  , iaspects :: [Aspect]
iaspects = Text -> Aspect
ELabel "of regeneration brew"
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
potionTemplate
  , ieffects :: [Effect]
ieffects = [ GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_ROSE_SMELLING (80 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 20)
               , GroupName ItemKind -> Effect
toOrganNoTimer GroupName ItemKind
S_REGENERATING
               , GroupName ItemKind -> Effect
toOrganNoTimer GroupName ItemKind
S_REGENERATING  -- x2
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_YOUTH_SPRINKLE) ]
  }

-- ** Non-exploding consumables, not specifically designed for throwing

-- Readable or otherwise communicating consumables require high apply skill
-- to be consumed.

scrollTemplate :: ItemKind
scrollTemplate = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolScroll
  , iname :: Text
iname    = "scroll"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
SCROLL_UNKNOWN, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color]
stdCol [Flavour] -> [Flavour] -> [Flavour]
forall a. [a] -> [a] -> [a]
++ [Color] -> [Flavour]
zipPlain [Color]
stdCol
  , icount :: Dice
icount   = 1 Int -> Int -> Dice
`dL` 3
  , irarity :: Rarity
irarity  = [(1, 14), (10, 7)]
  , iverbHit :: Text
iverbHit = "thump"
  , iweight :: Int
iweight  = 50
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ GroupName ItemKind -> Aspect
PresentAs GroupName ItemKind
SCROLL_UNKNOWN
               , Int -> Aspect
toVelocity 30 ]  -- bad shape, even rolled up
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = "Scraps of haphazardly scribbled mysteries from beyond. Is this equation an alchemical recipe? Is this diagram an extradimensional map? Is this formula a secret call sign?"
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
scroll1 :: ItemKind
scroll1 = ItemKind
scrollTemplate
  { iname :: Text
iname    = "the Scroll"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
TREASURE, 100), (GroupName ItemKind
ANY_SCROLL, 100)]
  , icount :: Dice
icount   = 1
  , irarity :: Rarity
irarity  = [(5, 9), (10, 9)]  -- mixed blessing, so found early for a unique
  , iaspects :: [Aspect]
iaspects = [Flag -> Aspect
SetFlag Flag
Unique, Text -> Aspect
ELabel "of Reckless Beacon"]
               [Aspect] -> [Aspect] -> [Aspect]
forall a. [a] -> [a] -> [a]
++ ItemKind -> [Aspect]
iaspects ItemKind
scrollTemplate
  , ieffects :: [Effect]
ieffects = [GroupName ItemKind -> Dice -> Effect
Summon GroupName ItemKind
HERO 1, GroupName ItemKind -> Dice -> Effect
Summon GroupName ItemKind
MOBILE_ANIMAL (2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 2)]
  , idesc :: Text
idesc    = "The bright flame and sweet-smelling smoke of this heavily infused scroll should attract natural creatures inhabiting the area, including human survivors, if any."
  }
scroll2 :: ItemKind
scroll2 = ItemKind
scrollTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_SCROLL, 100)]
  , irarity :: Rarity
irarity  = [(1, 6), (10, 2)]
  , ieffects :: [Effect]
ieffects = [Bool -> Effect
Ascend Bool
False]
  }
scroll3 :: ItemKind
scroll3 = ItemKind
scrollTemplate
  -- needs to be common to show at least a portion of effects
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_SCROLL, 100)]
  , icount :: Dice
icount   = 3 Int -> Int -> Dice
`dL` 1
  , irarity :: Rarity
irarity  = [(1, 14)]
  , ieffects :: [Effect]
ieffects = [[Effect] -> Effect
OneOf [ Dice -> Effect
Teleport 5, Dice -> Effect
Paralyze 10, Dice -> Effect
InsertMove 30
                      , DetectKind -> Int -> Effect
Detect DetectKind
DetectEmbed 12, DetectKind -> Int -> Effect
Detect DetectKind
DetectHidden 20 ]]
  }
scroll4 :: ItemKind
scroll4 = ItemKind
scrollTemplate
  -- needs to be common to show at least a portion of effects
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_SCROLL, 100)]
  , icount :: Dice
icount   = 3 Int -> Int -> Dice
`dL` 1
  , irarity :: Rarity
irarity  = [(10, 14)]
  , ieffects :: [Effect]
ieffects = [ Effect
Impress
               , [Effect] -> Effect
OneOf [ Dice -> Effect
Teleport 20, Bool -> Effect
Ascend Bool
False, Bool -> Effect
Ascend Bool
True
                       , GroupName ItemKind -> Dice -> Effect
Summon GroupName ItemKind
HERO 1, GroupName ItemKind -> Dice -> Effect
Summon GroupName ItemKind
MOBILE_ANIMAL (Dice -> Effect) -> Dice -> Effect
forall a b. (a -> b) -> a -> b
$ 1 Int -> Int -> Dice
`d` 2
                       , DetectKind -> Int -> Effect
Detect DetectKind
DetectLoot 20  -- the most useful of detections
                       , Maybe Int -> CStore -> GroupName ItemKind -> TimerDice -> Effect
CreateItem Maybe Int
forall a. Maybe a
Nothing CStore
CGround GroupName ItemKind
COMMON_ITEM TimerDice
timerNone ] ]
  }
scroll5 :: ItemKind
scroll5 = ItemKind
scrollTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_SCROLL, 100)]
  , irarity :: Rarity
irarity  = [(1, 6)]  -- powerful, but low counts at the depths it appears on
  , ieffects :: [Effect]
ieffects = [Dice -> Effect
InsertMove (Dice -> Effect) -> Dice -> Effect
forall a b. (a -> b) -> a -> b
$ 20 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`dL` 20]
  }
scroll6 :: ItemKind
scroll6 = ItemKind
scrollTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_SCROLL, 100)]
  , irarity :: Rarity
irarity  = [(10, 11)]
  , ieffects :: [Effect]
ieffects = [ThrowMod -> Effect
PullActor (Int -> Int -> Int -> ThrowMod
ThrowMod 800 75 1)]  -- 6 steps, 1.5 turns
  }
scroll7 :: ItemKind
scroll7 = ItemKind
scrollTemplate
  { iname :: Text
iname    = "the Scroll"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
TREASURE, 100), (GroupName ItemKind
ANY_SCROLL, 100)]
  , icount :: Dice
icount   = 1
  , irarity :: Rarity
irarity  = [(10, 12)]
  , iaspects :: [Aspect]
iaspects = [Flag -> Aspect
SetFlag Flag
Unique, Text -> Aspect
ELabel "of Rescue Proclamation"]
               [Aspect] -> [Aspect] -> [Aspect]
forall a. [a] -> [a] -> [a]
++ ItemKind -> [Aspect]
iaspects ItemKind
scrollTemplate
  , ieffects :: [Effect]
ieffects = [GroupName ItemKind -> Dice -> Effect
Summon GroupName ItemKind
HERO 1]
  , idesc :: Text
idesc    = "A survivor of past exploration missions is found that enjoys, apparently, complete physiological integrity. We can pronounce him a comrade in arms and let him join our party."
  }
scroll8 :: ItemKind
scroll8 = ItemKind
scrollTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_SCROLL, 100)]
  , irarity :: Rarity
irarity  = [(10, 4)]  -- powerful, even if not ideal; scares newbies
  , ieffects :: [Effect]
ieffects = [DetectKind -> Int -> Effect
Detect DetectKind
DetectAll 20]
  }
scroll9 :: ItemKind
scroll9 = ItemKind
scrollTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_SCROLL, 100)]
  , iaspects :: [Aspect]
iaspects = Text -> Aspect
ELabel "of cue interpretation"
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
scrollTemplate
  , ieffects :: [Effect]
ieffects = [DetectKind -> Int -> Effect
Detect DetectKind
DetectActor 20]
  }
scroll10 :: ItemKind
scroll10 = ItemKind
scrollTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_SCROLL, 100)]
  , icount :: Dice
icount   = 3 Int -> Int -> Dice
`dL` 1
  , irarity :: Rarity
irarity  = [(1, 20)]  -- uncommon deep down, where all is known
  , iaspects :: [Aspect]
iaspects = Text -> Aspect
ELabel "of scientific explanation"
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
scrollTemplate
  , ieffects :: [Effect]
ieffects = [Effect
Identify Effect -> Effect -> Effect
`AndEffect` Int -> Effect
RefillCalm 10]
  , idesc :: Text
idesc    = "The most pressing existential concerns are met with a deeply satisfying scientific answer."
  }
scroll11 :: ItemKind
scroll11 = ItemKind
scrollTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_SCROLL, 100)]
  , irarity :: Rarity
irarity  = [(10, 20)]  -- at gameover a crucial item may be missing
  , iaspects :: [Aspect]
iaspects = Text -> Aspect
ELabel "of transmutation"
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
scrollTemplate
  , ieffects :: [Effect]
ieffects = [Effect
PolyItem Effect -> Effect -> Effect
`AndEffect` GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_FIRECRACKER]
  }
scroll12 :: ItemKind
scroll12 = ItemKind
scrollTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_SCROLL, 100)]
  , irarity :: Rarity
irarity  = [(10, 15)]
  , iaspects :: [Aspect]
iaspects = Text -> Aspect
ELabel "of transfiguration"
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
scrollTemplate
  , ieffects :: [Effect]
ieffects = [Effect
RerollItem]
  }
scroll13 :: ItemKind
scroll13 = ItemKind
scrollTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_SCROLL, 100)]
  , irarity :: Rarity
irarity  = [(10, 15)]
  , iaspects :: [Aspect]
iaspects = Text -> Aspect
ELabel "of similarity"
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
scrollTemplate
  , ieffects :: [Effect]
ieffects = [Effect
DupItem]
  }

-- Foods require only minimal apply skill to consume. Many animals can eat them.

ediblePlantTemplate :: ItemKind
ediblePlantTemplate = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolFood
  , iname :: Text
iname    = "edible plant"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
EDIBLE_PLANT_UNKNOWN, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color]
stdCol
  , icount :: Dice
icount   = 1 Int -> Int -> Dice
`dL` 5
  , irarity :: Rarity
irarity  = [(1, 12), (10, 6)]  -- let's feed the animals
  , iverbHit :: Text
iverbHit = "thump"
  , iweight :: Int
iweight  = 50
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ GroupName ItemKind -> Aspect
PresentAs GroupName ItemKind
EDIBLE_PLANT_UNKNOWN
               , Int -> Aspect
toVelocity 30 ]  -- low density, often falling apart
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = "Withered but fragrant bits of a colorful plant. Taste tolerably and break down easily, but only eating may reveal the full effects."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
ediblePlant1 :: ItemKind
ediblePlant1 = ItemKind
ediblePlantTemplate
  { iname :: Text
iname    = "overripe berry"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
EDIBLE_PLANT, 100)]
  , ieffects :: [Effect]
ieffects = [Int -> Effect
RefillHP 1, GroupName ItemKind -> Dice -> Effect
toOrganBad GroupName ItemKind
S_IMMOBILE (5 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 5)]
  }
ediblePlant2 :: ItemKind
ediblePlant2 = ItemKind
ediblePlantTemplate
  { iname :: Text
iname    = "frayed fungus"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
EDIBLE_PLANT, 100)]
  , ieffects :: [Effect]
ieffects = [GroupName ItemKind -> Effect
toOrganNoTimer GroupName ItemKind
S_POISONED]
  }
ediblePlant3 :: ItemKind
ediblePlant3 = ItemKind
ediblePlantTemplate
  { iname :: Text
iname    = "thick leaf"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
EDIBLE_PLANT, 100)]
  , ieffects :: [Effect]
ieffects = [Int -> Int -> CStore -> GroupName ItemKind -> Effect
DropItem 1 Int
forall a. Bounded a => a
maxBound CStore
COrgan GroupName ItemKind
S_POISONED]
  }
ediblePlant4 :: ItemKind
ediblePlant4 = ItemKind
ediblePlantTemplate
  { iname :: Text
iname    = "shrunk fruit"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
EDIBLE_PLANT, 100)]
  , 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)]
  }
ediblePlant5 :: ItemKind
ediblePlant5 = ItemKind
ediblePlantTemplate
  { iname :: Text
iname    = "fragrant herb"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
EDIBLE_PLANT, 100)]
  , icount :: Dice
icount   = 1 Int -> Int -> Dice
`dL` 9
  , irarity :: Rarity
irarity  = [(1, 12), (10, 5)]
  , iaspects :: [Aspect]
iaspects = Text -> Aspect
ELabel "of lethargy"
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
ediblePlantTemplate
  , ieffects :: [Effect]
ieffects = [ GroupName ItemKind -> Dice -> Effect
toOrganBad GroupName ItemKind
S_SLOWED (20 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 5)
               , GroupName ItemKind -> Effect
toOrganNoTimer GroupName ItemKind
S_REGENERATING
               , GroupName ItemKind -> Effect
toOrganNoTimer GroupName ItemKind
S_REGENERATING  -- x2
               , Int -> Effect
RefillCalm 5 ]
  }
ediblePlant6 :: ItemKind
ediblePlant6 = ItemKind
ediblePlantTemplate
  { iname :: Text
iname    = "dull flower"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
EDIBLE_PLANT, 100)]
  , ieffects :: [Effect]
ieffects = [Effect
PutToSleep]
  }
ediblePlant7 :: ItemKind
ediblePlant7 = ItemKind
ediblePlantTemplate
  { iname :: Text
iname    = "spicy bark"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
EDIBLE_PLANT, 100)]
  , ieffects :: [Effect]
ieffects = [Dice -> Effect
InsertMove 20, GroupName ItemKind -> Dice -> Effect
toOrganBad GroupName ItemKind
S_FRENZIED (40 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 10)]
  }

-- ** Lights

light1 :: ItemKind
light1 = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolLight
  , iname :: Text
iname    = "wooden torch"
  , ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
LIGHT_ATTENUATOR, 100)
               , (GroupName ItemKind
S_WOODEN_TORCH, 1) ]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Brown]
  , icount :: Dice
icount   = 1 Int -> Int -> Dice
`dL` 4
  , irarity :: Rarity
irarity  = [(1, 40), (4, 1)]
  , iverbHit :: Text
iverbHit = "scorch"
  , iweight :: Int
iweight  = 1000
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkShine 3, Skill -> Dice -> Aspect
AddSkill Skill
SkSight (-2)
                   -- not only flashes, but also sparks,
                   -- so unused by AI due to the mixed blessing
               , Flag -> Aspect
SetFlag Flag
Lobable, Flag -> Aspect
SetFlag Flag
Equipable
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotShine ]
                   -- not Fragile; reusable flare
  , ieffects :: [Effect]
ieffects = [Dice -> Effect
Burn 1]
  , idesc :: Text
idesc    = "A heavy smoking wooden torch, improvised using a cloth soaked in tar, burning in an unsteady glow."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
light2 :: ItemKind
light2 = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolLight
  , iname :: Text
iname    = "oil lamp"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
LIGHT_ATTENUATOR, 100)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrYellow]
  , icount :: Dice
icount   = 1 Int -> Int -> Dice
`dL` 2
  , irarity :: Rarity
irarity  = [(4, 10)]
  , iverbHit :: Text
iverbHit = "burn"
  , iweight :: Int
iweight  = 1500
  , idamage :: Dice
idamage  = 1 Int -> Int -> Dice
`d` 1
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkShine 3, Skill -> Dice -> Aspect
AddSkill Skill
SkSight (-1)
               , Flag -> Aspect
SetFlag Flag
Lobable, Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Equipable
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotShine ]
  , 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)
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_BURNING_OIL_2) ]
  , idesc :: Text
idesc    = "A clay lamp filled with plant oil feeding a tiny wick."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
light3 :: ItemKind
light3 = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolLight
  , iname :: Text
iname    = "brass lantern"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
LIGHT_ATTENUATOR, 100)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Red]
  , icount :: Dice
icount   = 1
  , irarity :: Rarity
irarity  = [(10, 6)]
  , iverbHit :: Text
iverbHit = "burn"
  , iweight :: Int
iweight  = 3000
  , idamage :: Dice
idamage  = 2 Int -> Int -> Dice
`d` 1
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkShine 4, Skill -> Dice -> Aspect
AddSkill Skill
SkSight (-1)
               , Flag -> Aspect
SetFlag Flag
Lobable, Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Equipable
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotShine ]
  , ieffects :: [Effect]
ieffects = [ Dice -> Effect
Burn 1
               , GroupName ItemKind -> Dice -> Effect
toOrganBad GroupName ItemKind
S_PACIFIED (4 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 2)
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_BURNING_OIL_4) ]
  , idesc :: Text
idesc    = "Very bright and very heavy brass lantern."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
blanket :: ItemKind
blanket = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolLight
  , iname :: Text
iname    = "wool blanket"
  , ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
LIGHT_ATTENUATOR, 100)
               , (GroupName ItemKind
FIREPROOF_CLOTH, 1) ]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrBlack]
  , icount :: Dice
icount   = 1
  , irarity :: Rarity
irarity  = [(1, 1)]  -- not every playthrough needs one
  , iverbHit :: Text
iverbHit = "swoosh"
  , iweight :: Int
iweight  = 1000
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkShine (-10)
               , Skill -> Dice -> Aspect
AddSkill Skill
SkArmorMelee 2, Skill -> Dice -> Aspect
AddSkill Skill
SkMaxCalm 5
               , Flag -> Aspect
SetFlag Flag
Lobable, Flag -> Aspect
SetFlag Flag
Equipable
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotArmorMelee ]
                  -- not Fragile; reusable douse implement;
                   -- douses torch, lamp and lantern in one action,
                   -- both in equipment and when thrown at the floor
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = "Warm, comforting, and concealing, woven from soft wool."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }

-- ** Periodic jewelry

-- Morally these are the aspects, but we also need to add a fake @Timeout@,
-- to let clients know that the not identified item is periodic jewelry.
iaspects_necklaceTemplate :: [Aspect]
iaspects_necklaceTemplate :: [Aspect]
iaspects_necklaceTemplate =
  [ GroupName ItemKind -> Aspect
PresentAs GroupName ItemKind
NECKLACE_UNKNOWN
  , Flag -> Aspect
SetFlag Flag
Periodic, Flag -> Aspect
SetFlag Flag
Precious, Flag -> Aspect
SetFlag Flag
Equipable
  , Int -> Aspect
toVelocity 50 ]  -- not dense enough
gorget :: ItemKind
gorget = ItemKind
necklaceTemplate
  { iname :: Text
iname    = "Old Gorget"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 25), (GroupName ItemKind
TREASURE, 25)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color
BrCyan]  -- looks exactly the same as one of necklaces,
                                  -- but it's OK, it's an artifact
  , iaspects :: [Aspect]
iaspects = [ Flag -> Aspect
SetFlag Flag
Unique
               , Dice -> Aspect
Timeout (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ 5 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
- 1 Int -> Int -> Dice
`dL` 4
                   -- the dL dice need to be in negative positions
                   -- for negative stats, such as @Timeout@, so that
                   -- the @RerollItem@ effect makes the item better, not worse
               , Skill -> Dice -> Aspect
AddSkill Skill
SkArmorMelee 3, Skill -> Dice -> Aspect
AddSkill Skill
SkArmorRanged 2
               , Skill -> Dice -> Aspect
AddSkill Skill
SkHearing 3
               , Flag -> Aspect
SetFlag Flag
Durable ]
               [Aspect] -> [Aspect] -> [Aspect]
forall a. [a] -> [a] -> [a]
++ [Aspect]
iaspects_necklaceTemplate
  , ieffects :: [Effect]
ieffects = [Int -> Effect
RefillCalm 1]
  , idesc :: Text
idesc    = "Highly ornamental, cold, large steel medallion on a chain. Unlikely to offer much protection as an armor piece, but the old worn engraving reassures the wearer."
  }
-- Not identified, because id by use, e.g., via periodic activations. Fun.
necklaceTemplate :: ItemKind
necklaceTemplate = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolNecklace
  , iname :: Text
iname    = "necklace"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
NECKLACE_UNKNOWN, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color]
stdCol [Flavour] -> [Flavour] -> [Flavour]
forall a. [a] -> [a] -> [a]
++ [Color] -> [Flavour]
zipPlain [Color]
brightCol
  , icount :: Dice
icount   = 1
  , irarity :: Rarity
irarity  = [(4, 3), (10, 6)]
  , iverbHit :: Text
iverbHit = "whip"
  , iweight :: Int
iweight  = 30
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = Dice -> Aspect
Timeout 1000000
                 -- fake, needed to display "charging"; the timeout itself
                 -- won't be displayed thanks to periodic; as a side-effect,
                 -- it can't be activated until identified, which is better
                 -- than letting the player try to activate before the real
                 -- cooldown is over and waste turn
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: [Aspect]
iaspects_necklaceTemplate
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = "Menacing Greek symbols shimmer with increasing speed along a chain of fine encrusted links. After a tense build-up, a prismatic arc shoots towards the ground and the iridescence subdues, becomes ordered and resembles a harmless ornament again, for a time."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
necklace1 :: ItemKind
necklace1 = ItemKind
necklaceTemplate
  { iname :: Text
iname    = "the Necklace"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
TREASURE, 100), (GroupName ItemKind
ANY_JEWELRY, 100)]
  , irarity :: Rarity
irarity  = [(10, 3)]
  , iaspects :: [Aspect]
iaspects = [ Flag -> Aspect
SetFlag Flag
Unique, Text -> Aspect
ELabel "of Aromata"
               , Dice -> Aspect
Timeout (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (4 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
- 1 Int -> Int -> Dice
`dL` 3) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 10
                   -- priceless, so worth the long wait and Calm drain
               , Flag -> Aspect
SetFlag Flag
Durable ]
               [Aspect] -> [Aspect] -> [Aspect]
forall a. [a] -> [a] -> [a]
++ [Aspect]
iaspects_necklaceTemplate
  , ieffects :: [Effect]
ieffects = [ Int -> Effect
RefillCalm (-5)
               , Condition -> Effect -> Effect
When (ActivationFlag -> Condition
TriggeredBy ActivationFlag
ActivationPeriodic) (Effect -> Effect) -> Effect -> Effect
forall a b. (a -> b) -> a -> b
$ Int -> Effect
RefillHP 1 ]
  , idesc :: Text
idesc    = "A cord of freshly dried herbs and healing berries."
  }
necklace2 :: ItemKind
necklace2 = ItemKind
necklaceTemplate
  { iname :: Text
iname    = "the Necklace"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
TREASURE, 100), (GroupName ItemKind
ANY_JEWELRY, 100)]
      -- too nasty to call it just a COMMON_ITEM
  , irarity :: Rarity
irarity  = [(10, 3)]
  , iaspects :: [Aspect]
iaspects = [ Flag -> Aspect
SetFlag Flag
Unique, Text -> Aspect
ELabel "of Live Bait"
               , Dice -> Aspect
Timeout 30
               , Skill -> Dice -> Aspect
AddSkill Skill
SkOdor 2
               , Flag -> Aspect
SetFlag Flag
Durable ]
               [Aspect] -> [Aspect] -> [Aspect]
forall a. [a] -> [a] -> [a]
++ [Aspect]
iaspects_necklaceTemplate
  , ieffects :: [Effect]
ieffects = [ Int -> Int -> CStore -> GroupName ItemKind -> Effect
DropItem 1 1 CStore
COrgan GroupName ItemKind
CONDITION  -- mildly useful when applied
               , Condition -> Effect -> Effect
When (ActivationFlag -> Condition
TriggeredBy ActivationFlag
ActivationPeriodic) (Effect -> Effect) -> Effect -> Effect
forall a b. (a -> b) -> a -> b
$ [Effect] -> Effect
SeqEffect
                   [ Effect
Impress
                   , GroupName ItemKind -> Dice -> Effect
Summon GroupName ItemKind
MOBILE_ANIMAL (Dice -> Effect) -> Dice -> Effect
forall a b. (a -> b) -> a -> b
$ 1 Int -> Int -> Dice
`dL` 2
                   , GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_WASTE ] ]
  , idesc :: Text
idesc    = "A cord hung with lumps of decaying meat. It's better not to think about the source."
  }
necklace3 :: ItemKind
necklace3 = ItemKind
necklaceTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_JEWELRY, 100)]
  , iaspects :: [Aspect]
iaspects = [ Text -> Aspect
ELabel "of fearful listening"
               , Dice -> Aspect
Timeout 40
                   -- has to be larger than Calm drain or item not removable;
                   -- equal is not enough if enemies drained Calm already
               , Skill -> Dice -> Aspect
AddSkill Skill
SkHearing 6 ]
               [Aspect] -> [Aspect] -> [Aspect]
forall a. [a] -> [a] -> [a]
++ [Aspect]
iaspects_necklaceTemplate
  , ieffects :: [Effect]
ieffects = [ DetectKind -> Int -> Effect
Detect DetectKind
DetectActor 20  -- can be applied; destroys the item
               , Condition -> Effect -> Effect
When (ActivationFlag -> Condition
TriggeredBy ActivationFlag
ActivationPeriodic) (Effect -> Effect) -> Effect -> Effect
forall a b. (a -> b) -> a -> b
$ Int -> Effect
RefillCalm (-30) ]
  }
necklace4 :: ItemKind
necklace4 = ItemKind
necklaceTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_JEWELRY, 100)]
  , iaspects :: [Aspect]
iaspects = [ Text -> Aspect
ELabel "of escape"
               , Dice -> Aspect
Timeout (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (7 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
- 1 Int -> Int -> Dice
`dL` 5) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 10 ]
               [Aspect] -> [Aspect] -> [Aspect]
forall a. [a] -> [a] -> [a]
++ [Aspect]
iaspects_necklaceTemplate
  , ieffects :: [Effect]
ieffects = [ Dice -> Effect
Teleport (Dice -> Effect) -> Dice -> Effect
forall a b. (a -> b) -> a -> b
$ 14 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 3 Int -> Int -> Dice
`d` 3  -- can be applied; destroys the item
               , DetectKind -> Int -> Effect
Detect DetectKind
DetectExit 20
               , Effect
Yell ]  -- drawback when used for quick exploring
  , idesc :: Text
idesc    = "A supple chain that slips through your fingers."
  }
necklace5 :: ItemKind
necklace5 = ItemKind
necklaceTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_JEWELRY, 100)]
  , iaspects :: [Aspect]
iaspects = [ Text -> Aspect
ELabel "of greed"
               , Dice -> Aspect
Timeout ((2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 3) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 10) ]
               [Aspect] -> [Aspect] -> [Aspect]
forall a. [a] -> [a] -> [a]
++ [Aspect]
iaspects_necklaceTemplate
  , ieffects :: [Effect]
ieffects = [ DetectKind -> Int -> Effect
Detect DetectKind
DetectLoot 20
               , GroupName ItemKind -> Dice -> Effect
toOrganBad GroupName ItemKind
S_PARSIMONIOUS (5 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 3)  -- hard to flee
               , Condition -> Effect -> Effect
When (ActivationFlag -> Condition
TriggeredBy ActivationFlag
ActivationPeriodic) (Effect -> Effect) -> Effect -> Effect
forall a b. (a -> b) -> a -> b
$ Dice -> Effect
Teleport 40 ]  -- risky
  }
necklace6 :: ItemKind
necklace6 = ItemKind
necklaceTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_JEWELRY, 100)]
  , iaspects :: [Aspect]
iaspects = Dice -> Aspect
Timeout ((3 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 3 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
- 1 Int -> Int -> Dice
`dL` 3) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 2)
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: [Aspect]
iaspects_necklaceTemplate
  , ieffects :: [Effect]
ieffects = [Dice -> Effect
Teleport (Dice -> Effect) -> Dice -> Effect
forall a b. (a -> b) -> a -> b
$ 3 Int -> Int -> Dice
`d` 2]
  }
necklace7 :: ItemKind
necklace7 = ItemKind
necklaceTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_JEWELRY, 100)]
  , iaspects :: [Aspect]
iaspects = Dice -> Aspect
Timeout (1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ (1 Int -> Int -> Dice
`d` 3) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 2)
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: [Aspect]
iaspects_necklaceTemplate
  , ieffects :: [Effect]
ieffects = [ThrowMod -> Effect
PushActor (Int -> Int -> Int -> ThrowMod
ThrowMod 100 50 1)]  -- 1 step, slow
                  -- the @50@ is only for the case of very light actor, etc.
  }
necklace8 :: ItemKind
necklace8 = ItemKind
necklaceTemplate
  { iname :: Text
iname    = "the Necklace"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
TREASURE, 100), (GroupName ItemKind
ANY_JEWELRY, 100)]
  , irarity :: Rarity
irarity  = [(10, 1)]  -- different gameplay for the actor that wears it
  , iaspects :: [Aspect]
iaspects = [ Flag -> Aspect
SetFlag Flag
Unique, Text -> Aspect
ELabel "of Overdrive"
               , Dice -> Aspect
Timeout 4
               , Skill -> Dice -> Aspect
AddSkill Skill
SkMaxHP 25  -- give incentive to cope with impatience
               , Flag -> Aspect
SetFlag Flag
Durable ]
               [Aspect] -> [Aspect] -> [Aspect]
forall a. [a] -> [a] -> [a]
++ [Aspect]
iaspects_necklaceTemplate
  , ieffects :: [Effect]
ieffects = [ Dice -> Effect
InsertMove (Dice -> Effect) -> Dice -> Effect
forall a b. (a -> b) -> a -> b
$ 9 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 11  -- unpredictable
               , GroupName ItemKind -> Dice -> Effect
toOrganBad GroupName ItemKind
S_IMPATIENT 4]
                 -- The same duration as timeout, to avoid spurious messages
                 -- as well as unlimited accumulation of the duration.
  , idesc :: Text
idesc    = "A string of beads in various colours, with no discernable pattern."
  }
necklace9 :: ItemKind
necklace9 = ItemKind
necklaceTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_JEWELRY, 100)]
  , irarity :: Rarity
irarity  = [(4, 3)]  -- entirely optional
  , iaspects :: [Aspect]
iaspects = Dice -> Aspect
Timeout ((1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 3) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5)
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: [Aspect]
iaspects_necklaceTemplate
  , ieffects :: [Effect]
ieffects = [GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_SPARK]
  }
necklace10 :: ItemKind
necklace10 = ItemKind
necklaceTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_JEWELRY, 100)]
  , iaspects :: [Aspect]
iaspects = Dice -> Aspect
Timeout ((1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 3) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5)
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: [Aspect]
iaspects_necklaceTemplate
  , ieffects :: [Effect]
ieffects = [GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_FRAGRANCE]
  }
motionScanner :: ItemKind
motionScanner = ItemKind
necklaceTemplate
  { iname :: Text
iname    = "draft detector"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ADD_NOCTO_1, 20)]
  , irarity :: Rarity
irarity  = [(5, 2)]
  , iverbHit :: Text
iverbHit = "jingle"
  , iweight :: Int
iweight  = 300  -- almost gives it away
  , iaspects :: [Aspect]
iaspects = [ Dice -> Aspect
Timeout (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ 4 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`dL` 6
               , Skill -> Dice -> Aspect
AddSkill Skill
SkNocto 1
               , Skill -> Dice -> Aspect
AddSkill Skill
SkArmorMelee (-20 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ (1 Int -> Int -> Dice
`dL` 3) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5)
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotMiscBonus ]
               [Aspect] -> [Aspect] -> [Aspect]
forall a. [a] -> [a] -> [a]
++ [Aspect]
iaspects_necklaceTemplate
  , ieffects :: [Effect]
ieffects = [GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_PING_PLASH]
  , idesc :: Text
idesc    = "A silk flag with a bell for detecting sudden draft changes. May indicate a nearby corridor crossing or a fast enemy approaching in the dark. The bell is very noisy and casts light reflection flashes."
  }

-- ** Non-periodic jewelry

imageItensifier :: ItemKind
imageItensifier = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolRing
  , iname :: Text
iname    = "light cone"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
TREASURE, 100), (GroupName ItemKind
ADD_NOCTO_1, 80)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color
BrYellow]
  , icount :: Dice
icount   = 1
  , irarity :: Rarity
irarity  = [(5, 2)]
  , iverbHit :: Text
iverbHit = "bang"
  , iweight :: Int
iweight  = 500
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkNocto 1, Skill -> Dice -> Aspect
AddSkill Skill
SkSight (-1)
               , Skill -> Dice -> Aspect
AddSkill Skill
SkArmorMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (-1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`dL` 6) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 3
               , Flag -> Aspect
SetFlag Flag
Precious, Flag -> Aspect
SetFlag Flag
Equipable
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotMiscBonus ]
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = "Contraption of lenses and mirrors on a polished brass headband for capturing and strengthening light in dark environment. Hampers vision in daylight. Stackable."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
sightSharpening :: ItemKind
sightSharpening = ItemKind
ringTemplate  -- small and round, so mistaken for a ring
  { iname :: Text
iname    = "sharp monocle"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
TREASURE, 20), (GroupName ItemKind
ADD_SIGHT, 1)]
      -- it's has to be very rare, because it's powerful and not unique,
      -- and also because it looks exactly as one of necklaces, so it would
      -- be misleading when seen on the map
  , irarity :: Rarity
irarity  = [(7, 1), (10, 12)]  -- low @ifreq@
  , iweight :: Int
iweight  = 50  -- heavier that it looks, due to glass
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkSight (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ 1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`dL` 2
               , Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (-1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 3) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 3
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotSight ]
               [Aspect] -> [Aspect] -> [Aspect]
forall a. [a] -> [a] -> [a]
++ ItemKind -> [Aspect]
iaspects ItemKind
ringTemplate
  , idesc :: Text
idesc    = "Lets you better focus your weaker eye."
  }
-- Don't add standard effects to rings, because they go in and out
-- of eqp and so activating them would require UI tedium: looking for
-- them in eqp and stash or even activating a wrong item by mistake.
--
-- By general mechanisms, due to not having effects that could identify
-- them by observing the effect, rings are identified on pickup.
-- That's unlike necklaces, which provide the fun of id-by-use, because they
-- have effects and when the effects are triggered, they get identified.
ringTemplate :: ItemKind
ringTemplate = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolRing
  , iname :: Text
iname    = "ring"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
RING_UNKNOWN, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color]
stdCol [Flavour] -> [Flavour] -> [Flavour]
forall a. [a] -> [a] -> [a]
++ [Color] -> [Flavour]
zipFancy [Color]
darkCol
  , icount :: Dice
icount   = 1
  , irarity :: Rarity
irarity  = [(10, 2)]  -- the default very low
  , iverbHit :: Text
iverbHit = "knock"
  , iweight :: Int
iweight  = 15
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [GroupName ItemKind -> Aspect
PresentAs GroupName ItemKind
RING_UNKNOWN, Flag -> Aspect
SetFlag Flag
Precious, Flag -> Aspect
SetFlag Flag
Equipable]
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = "It looks like an ordinary object, but it's in fact a generator of exceptional effects: adding to some of your natural qualities and subtracting from others."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
ring1 :: ItemKind
ring1 = ItemKind
ringTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_JEWELRY, 100)]
  , irarity :: Rarity
irarity  = [(8, 4)]
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkSpeed (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ 1 Int -> Int -> Dice
`dL` 3
               , Skill -> Dice -> Aspect
AddSkill Skill
SkMaxHP (-10)
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotSpeed ]
               [Aspect] -> [Aspect] -> [Aspect]
forall a. [a] -> [a] -> [a]
++ ItemKind -> [Aspect]
iaspects ItemKind
ringTemplate
  }
ring2 :: ItemKind
ring2 = ItemKind
ringTemplate
  { iname :: Text
iname    = "the Ring"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
TREASURE, 100), (GroupName ItemKind
ANY_JEWELRY, 100)]
  , iaspects :: [Aspect]
iaspects = [ Flag -> Aspect
SetFlag Flag
Unique, Text -> Aspect
ELabel "of Rush"
               , Skill -> Dice -> Aspect
AddSkill Skill
SkSpeed (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`dL` 2) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 2
               , Skill -> Dice -> Aspect
AddSkill Skill
SkMaxHP (-20)
               , Skill -> Dice -> Aspect
AddSkill Skill
SkMaxCalm (-40)
               , Flag -> Aspect
SetFlag Flag
Durable, EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotSpeed ]
               [Aspect] -> [Aspect] -> [Aspect]
forall a. [a] -> [a] -> [a]
++ ItemKind -> [Aspect]
iaspects ItemKind
ringTemplate
  , idesc :: Text
idesc    = "Roughly-shaped metal with shallow scratches marking it."
  }
ring3 :: ItemKind
ring3 = ItemKind
ringTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_JEWELRY, 100)]
  , irarity :: Rarity
irarity  = [(3, 4), (10, 8)]
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ (1 Int -> Int -> Dice
`dL` 2) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 2 ) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 3
               , Skill -> Dice -> Aspect
AddSkill Skill
SkMaxHP (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (-3 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`dL` 3) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 10
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotHurtMelee ]
               [Aspect] -> [Aspect] -> [Aspect]
forall a. [a] -> [a] -> [a]
++ ItemKind -> [Aspect]
iaspects ItemKind
ringTemplate
  }
ring4 :: ItemKind
ring4 = ItemKind
ringTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_JEWELRY, 100)]
  , irarity :: Rarity
irarity  = [(10, 8)]
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkMaxHP (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ 5 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ (1 Int -> Int -> Dice
`d` 2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`dL` 2) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5
               , Skill -> Dice -> Aspect
AddSkill Skill
SkMaxCalm (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ -30 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ (1 Int -> Int -> Dice
`dL` 3) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotMaxHP ]
               [Aspect] -> [Aspect] -> [Aspect]
forall a. [a] -> [a] -> [a]
++ ItemKind -> [Aspect]
iaspects ItemKind
ringTemplate
  }
ring5 :: ItemKind
ring5 = ItemKind
ringTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_JEWELRY, 100)]
  , irarity :: Rarity
irarity  = [(5, 1), (10, 9)]  -- needed after other rings drop Calm
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkMaxCalm (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ 20 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ (1 Int -> Int -> Dice
`dL` 4) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5
               , Skill -> Dice -> Aspect
AddSkill Skill
SkHearing 6
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotMiscBonus ]
               [Aspect] -> [Aspect] -> [Aspect]
forall a. [a] -> [a] -> [a]
++ ItemKind -> [Aspect]
iaspects ItemKind
ringTemplate
  , idesc :: Text
idesc    = "Cold, solid to the touch, perfectly round, engraved with solemn, strangely comforting, worn out words."
  }
ring6 :: ItemKind
ring6 = ItemKind
ringTemplate  -- weak skill per eqp slot, so can be without drawbacks
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ANY_JEWELRY, 100)]
  , irarity :: Rarity
irarity  = [(10, 3)]
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkShine 1
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotShine ]
               [Aspect] -> [Aspect] -> [Aspect]
forall a. [a] -> [a] -> [a]
++ ItemKind -> [Aspect]
iaspects ItemKind
ringTemplate
  , idesc :: Text
idesc    = "A sturdy ring with a large, shining stone."
  }
ring7 :: ItemKind
ring7 = ItemKind
ringTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
RING_OF_OPPORTUNITY_SNIPER, 1) ]  -- only for scenarios
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iaspects :: [Aspect]
iaspects = [ Text -> Aspect
ELabel "of opportunity sniper"
               , Skill -> Dice -> Aspect
AddSkill Skill
SkProject 8
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotProject ]
               [Aspect] -> [Aspect] -> [Aspect]
forall a. [a] -> [a] -> [a]
++ ItemKind -> [Aspect]
iaspects ItemKind
ringTemplate
  }
ring8 :: ItemKind
ring8 = ItemKind
ringTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
RING_OF_OPPORTUNITY_GRENADIER, 1) ]  -- only for scenarios
  , irarity :: Rarity
irarity  = [(1, 1)]
  , iaspects :: [Aspect]
iaspects = [ Text -> Aspect
ELabel "of opportunity grenadier"
               , Skill -> Dice -> Aspect
AddSkill Skill
SkProject 11
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotProject ]
               [Aspect] -> [Aspect] -> [Aspect]
forall a. [a] -> [a] -> [a]
++ ItemKind -> [Aspect]
iaspects ItemKind
ringTemplate
  }

-- ** Armor

armorLeather :: ItemKind
armorLeather = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolTorsoArmor
  , iname :: Text
iname    = "leather armor"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ARMOR_LOOSE, 1), (GroupName ItemKind
STARTING_ARMOR, 100)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Brown]
  , icount :: Dice
icount   = 1
  , irarity :: Rarity
irarity  = [(1, 9), (10, 3)]
  , iverbHit :: Text
iverbHit = "thud"
  , iweight :: Int
iweight  = 7000
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (-2)
               , Skill -> Dice -> Aspect
AddSkill Skill
SkArmorMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`dL` 4) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5
               , Skill -> Dice -> Aspect
AddSkill Skill
SkArmorRanged (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`dL` 2) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 3
               , Flag -> Aspect
SetFlag Flag
Durable, Flag -> Aspect
SetFlag Flag
Equipable
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotArmorMelee ]
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = "A stiff jacket formed from leather boiled in bee wax, padded linen and horse hair. Protects from anything that is not too sharp. Smells much better than the rest of your garment."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
armorMail :: ItemKind
armorMail = ItemKind
armorLeather
  { iname :: Text
iname    = "ring armor"
  , ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ARMOR_LOOSE, 1), (GroupName ItemKind
ARMOR_RANGED, 50)
               , (GroupName ItemKind
STARTING_ARMOR, 50) ]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Cyan]
  , irarity :: Rarity
irarity  = [(6, 9), (10, 3)]
  , iweight :: Int
iweight  = 12000
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (-3)
               , Skill -> Dice -> Aspect
AddSkill Skill
SkArmorMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`dL` 4) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5
               , Skill -> Dice -> Aspect
AddSkill Skill
SkArmorRanged (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (4 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`dL` 2) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 3
               , Skill -> Dice -> Aspect
AddSkill Skill
SkOdor 2
               , Flag -> Aspect
SetFlag Flag
Durable, Flag -> Aspect
SetFlag Flag
Equipable
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotArmorRanged ]
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = "A long shirt with tiny iron rings sewn into it. Discourages foes from attacking your torso, especially with ranged weapons, which can't pierce the rings nor aim between them. The stiff fabric is hard to wash, though."
  }
meleeEnhancement :: ItemKind
meleeEnhancement = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolTool
  , iname :: Text
iname    = "whetstone"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Blue]
  , icount :: Dice
icount   = 1
  , irarity :: Rarity
irarity  = [(10, 10)]
  , iverbHit :: Text
iverbHit = "smack"
  , iweight :: Int
iweight  = 400
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (1 Int -> Int -> Dice
`dL` 7) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5
               , Skill -> Dice -> Aspect
AddSkill Skill
SkArmorMelee 2
               , Flag -> Aspect
SetFlag Flag
Equipable, EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotHurtMelee ]
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = "A portable sharpening stone for keeping your weapons keen and true, without the need to set up camp, fish out tools and assemble a proper sharpening workshop. Provides an extra polish to amor, as well."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
gloveFencing :: ItemKind
gloveFencing = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolMiscArmor
  , iname :: Text
iname    = "leather glove"
  , ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ARMOR_MISC, 1), (GroupName ItemKind
ARMOR_RANGED, 50)
               , (GroupName ItemKind
STARTING_ARMOR, 50) ]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
White]
  , icount :: Dice
icount   = 1
  , irarity :: Rarity
irarity  = [(5, 9), (10, 9)]
  , iverbHit :: Text
iverbHit = "flap"
  , iweight :: Int
iweight  = 100
  , idamage :: Dice
idamage  = 1 Int -> Int -> Dice
`d` 1
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`dL` 2) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 3
               , Skill -> Dice -> Aspect
AddSkill Skill
SkArmorRanged (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (1 Int -> Int -> Dice
`dL` 2) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 3
               , Flag -> Aspect
SetFlag Flag
Durable, Flag -> Aspect
SetFlag Flag
Equipable
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotHurtMelee
               , Int -> Aspect
toVelocity 50 ]  -- flaps and flutters
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = "A fencing glove from rough leather ensuring a good grip. Also quite effective in averting or even catching slow projectiles."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
gloveGauntlet :: ItemKind
gloveGauntlet = ItemKind
gloveFencing
  { iname :: Text
iname    = "steel gauntlet"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ARMOR_MISC, 1), (GroupName ItemKind
STARTING_ARMOR, 50)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrCyan]
  , irarity :: Rarity
irarity  = [(1, 9), (10, 3)]
  , iweight :: Int
iweight  = 300
  , idamage :: Dice
idamage  = 2 Int -> Int -> Dice
`d` 1
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkArmorMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`dL` 4) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5
               , Flag -> Aspect
SetFlag Flag
Durable, Flag -> Aspect
SetFlag Flag
Equipable
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotArmorMelee
               , Int -> Aspect
toVelocity 50 ]  -- flaps and flutters
  , idesc :: Text
idesc    = "Long leather gauntlet covered in overlapping steel plates."
  }
gloveJousting :: ItemKind
gloveJousting = ItemKind
gloveFencing
  { iname :: Text
iname    = "Tournament Gauntlet"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ARMOR_MISC, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color
BrRed]
  , irarity :: Rarity
irarity  = [(1, 3), (10, 3)]
  , iverbHit :: Text
iverbHit = "rasp"
  , iweight :: Int
iweight  = 3000
  , idamage :: Dice
idamage  = 3 Int -> Int -> Dice
`d` 1
  , iaspects :: [Aspect]
iaspects = [ Flag -> Aspect
SetFlag Flag
Unique
               , Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (-7 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`dL` 5) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 3
               , Skill -> Dice -> Aspect
AddSkill Skill
SkArmorMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`dL` 2) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5
               , Skill -> Dice -> Aspect
AddSkill Skill
SkArmorRanged (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`dL` 2) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 3
                 -- very random on purpose and can even be good on occasion
                 -- or when ItemRerolled enough times
               , Flag -> Aspect
SetFlag Flag
Durable, Flag -> Aspect
SetFlag Flag
Equipable
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotArmorMelee
               , Int -> Aspect
toVelocity 50 ]  -- flaps and flutters
  , idesc :: Text
idesc    = "Rigid, steel jousting handgear. If only you had a lance. And a horse to carry it all."
  }
hatUshanka :: ItemKind
hatUshanka = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolMiscArmor
  , iname :: Text
iname    = "ushanka hat"
  , ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ARMOR_MISC, 1), (GroupName ItemKind
CLOTHING_MISC, 1)
               , (GroupName ItemKind
STARTING_ARMOR, 50) ]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Brown]
  , icount :: Dice
icount   = 1
  , irarity :: Rarity
irarity  = [(1, 6), (10, 1)]
  , iverbHit :: Text
iverbHit = "tickle"
  , iweight :: Int
iweight  = 500
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Dice -> Aspect
Timeout (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 2) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 3
               , Skill -> Dice -> Aspect
AddSkill Skill
SkArmorMelee 5, Skill -> Dice -> Aspect
AddSkill Skill
SkHearing (-10)
               , Flag -> Aspect
SetFlag Flag
Periodic, Flag -> Aspect
SetFlag Flag
Durable, Flag -> Aspect
SetFlag Flag
Equipable
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotArmorMelee
               , Int -> Aspect
toVelocity 50 ]  -- flaps and flutters
  , ieffects :: [Effect]
ieffects = [Int -> Effect
RefillCalm 1]
  , idesc :: Text
idesc    = "Soft and warm fur. It keeps your ears warm."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
capReinforced :: ItemKind
capReinforced = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolMiscArmor
  , iname :: Text
iname    = "leather cap"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ARMOR_MISC, 1), (GroupName ItemKind
STARTING_ARMOR, 50)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrYellow]
  , icount :: Dice
icount   = 1
  , irarity :: Rarity
irarity  = [(6, 9), (10, 3)]
  , iverbHit :: Text
iverbHit = "cut"
  , iweight :: Int
iweight  = 1000
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkArmorMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (1 Int -> Int -> Dice
`d` 2) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5
               , Skill -> Dice -> Aspect
AddSkill Skill
SkProject 1
                   -- the brim shields against blinding by light sources, etc.
               , Flag -> Aspect
SetFlag Flag
Durable, Flag -> Aspect
SetFlag Flag
Equipable
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotProject ]
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = "Boiled leather with a wide brim. It might soften a blow."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
helmArmored :: ItemKind
helmArmored = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolMiscArmor
  , iname :: Text
iname    = "bucket helm"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ARMOR_MISC, 1), (GroupName ItemKind
STARTING_ARMOR, 50)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrCyan]
  , icount :: Dice
icount   = 1
  , irarity :: Rarity
irarity  = [(6, 9), (10, 3)]
  , iverbHit :: Text
iverbHit = "bounce"
  , iweight :: Int
iweight  = 2000
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkArmorMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`dL` 4) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5
               , Skill -> Dice -> Aspect
AddSkill Skill
SkArmorRanged (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`dL` 2) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 3  -- headshot
               , Skill -> Dice -> Aspect
AddSkill Skill
SkHearing (-7), Skill -> Dice -> Aspect
AddSkill Skill
SkSight (-1)
               , Skill -> Dice -> Aspect
AddSkill Skill
SkSmell (-5)
               , Flag -> Aspect
SetFlag Flag
Durable, Flag -> Aspect
SetFlag Flag
Equipable
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotArmorRanged ]
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = "Blocks out everything, including your senses."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
smokingJacket :: ItemKind
smokingJacket = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolClothes
  , iname :: Text
iname    = "smoking jacket"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
CLOTHING_MISC, 1), (GroupName ItemKind
CHIC_GEAR, 100)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color
BrGreen]
  , icount :: Dice
icount   = 1
  , irarity :: Rarity
irarity  = [(1, 9), (10, 3)]
  , iverbHit :: Text
iverbHit = "stroke"
  , iweight :: Int
iweight  = 5000
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Dice -> Aspect
Timeout (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (1 Int -> Int -> Dice
`d` 2) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 3
               , Skill -> Dice -> Aspect
AddSkill Skill
SkSpeed 2
               , Skill -> Dice -> Aspect
AddSkill Skill
SkOdor 2
               , Flag -> Aspect
SetFlag Flag
Periodic, Flag -> Aspect
SetFlag Flag
Durable, Flag -> Aspect
SetFlag Flag
Equipable
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotSpeed ]
  , ieffects :: [Effect]
ieffects = [Int -> Effect
RefillCalm 1]
  , idesc :: Text
idesc    = "Wearing this velvet jacket, anyone would look dashing."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
-- Shield doesn't protect against ranged attacks to prevent
-- micromanagement: walking with shield, melee without.
-- Their biggest power is pushing enemies, which however reduces
-- to 1 extra damage point if no clear space behind enemy.
-- So they require keen tactical management.
-- Note that AI will pick them up but never wear and will use them at most
-- as a way to push itself. Despite being @Meleeable@, they will not be used
-- as weapons either. This is OK, using shields smartly is totally beyond AI.
buckler :: ItemKind
buckler = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolShield
  , iname :: Text
iname    = "buckler"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
ARMOR_LOOSE, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Blue]
  , icount :: Dice
icount   = 1
  , irarity :: Rarity
irarity  = [(4, 5)]
  , iverbHit :: Text
iverbHit = "bash"
  , iweight :: Int
iweight  = 2000
  , idamage :: Dice
idamage  = 0  -- safe to be used on self
  , iaspects :: [Aspect]
iaspects = [ Dice -> Aspect
Timeout (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (3 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 3 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
- 1 Int -> Int -> Dice
`dL` 3) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 2
               , Skill -> Dice -> Aspect
AddSkill Skill
SkArmorMelee 40
                   -- not enough to compensate; won't be in eqp
               , Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (-30)
                   -- too harmful; won't be wielded as weapon
               , Flag -> Aspect
SetFlag Flag
Durable, Flag -> Aspect
SetFlag Flag
Meleeable
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotArmorMelee ]
  , ieffects :: [Effect]
ieffects = [ThrowMod -> Effect
PushActor (Int -> Int -> Int -> ThrowMod
ThrowMod 200 50 1)]  -- 1 step, fast
  , idesc :: Text
idesc    = "Heavy and unwieldy. Absorbs a percentage of melee damage, both dealt and sustained. Too small to intercept projectiles with. May serve as a counterweight to suddenly push forth."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
shield :: ItemKind
shield = ItemKind
buckler
  { iname :: Text
iname    = "shield"
  , irarity :: Rarity
irarity  = [(8, 4)]  -- the stronger variants add to total probability
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Green]
  , iweight :: Int
iweight  = 4000
  , idamage :: Dice
idamage  = 4 Int -> Int -> Dice
`d` 1
  , iaspects :: [Aspect]
iaspects = [ Dice -> Aspect
Timeout (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (3 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 3 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
- 1 Int -> Int -> Dice
`dL` 3) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 4
               , Skill -> Dice -> Aspect
AddSkill Skill
SkArmorMelee 80
                   -- not enough to compensate; won't be in eqp
               , Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (-70)
                   -- too harmful; won't be wielded as weapon
               , Flag -> Aspect
SetFlag Flag
Durable, Flag -> Aspect
SetFlag Flag
Meleeable
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotArmorMelee
               , Int -> Aspect
toVelocity 50 ]  -- unwieldy to throw
  , ieffects :: [Effect]
ieffects = [ThrowMod -> Effect
PushActor (Int -> Int -> Int -> ThrowMod
ThrowMod 400 50 1)]  -- 2 steps, fast
  , idesc :: Text
idesc    = "Large and unwieldy. Absorbs a percentage of melee damage, both dealt and sustained. Too heavy to intercept projectiles with. Useful to push foes out of the way."
  }
shield2 :: ItemKind
shield2 = ItemKind
shield
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 3 Int -> Int -> Int
forall a. Num a => a -> a -> a
* 3)]  -- very low base rarity
  , iweight :: Int
iweight  = 5000
  , idamage :: Dice
idamage  = 8 Int -> Int -> Dice
`d` 1
  , idesc :: Text
idesc    = "A relic of long-past wars, heavy and with a central spike."
  }
shield3 :: ItemKind
shield3 = ItemKind
shield2
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 1 Int -> Int -> Int
forall a. Num a => a -> a -> a
* 3)]  -- very low base rarity
  , iweight :: Int
iweight  = 6000
  , idamage :: Dice
idamage  = 12 Int -> Int -> Dice
`d` 1
  }

-- ** Weapons

knife :: ItemKind
knife = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolEdged
  , iname :: Text
iname    = "dagger"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
STARTING_WEAPON, 200)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrCyan]
  , icount :: Dice
icount   = 1
  , irarity :: Rarity
irarity  = [(2, 45), (4, 1)]
  , iverbHit :: Text
iverbHit = "cut"
  , iweight :: Int
iweight  = 800
  , idamage :: Dice
idamage  = 6 Int -> Int -> Dice
`d` 1
  , iaspects :: [Aspect]
iaspects = [ Dice -> Aspect
Timeout 2
               , Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (-1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`dL` 2) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 3
               , Skill -> Dice -> Aspect
AddSkill Skill
SkArmorMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (1 Int -> Int -> Dice
`d` 2) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5
                   -- very common, so don't make too random
               , Flag -> Aspect
SetFlag Flag
Durable, Flag -> Aspect
SetFlag Flag
Meleeable
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotWeaponFast
               , Int -> Aspect
toVelocity 40 ]  -- ensuring it hits with the tip costs speed
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = "A short dagger for thrusting and parrying blows. Does not penetrate deeply, but is quick to move and hard to block. Especially useful in conjunction with a larger weapon."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
daggerDropBestWeapon :: ItemKind
daggerDropBestWeapon = ItemKind
knife
  { iname :: Text
iname    = "The Double Dagger"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
TREASURE, 20)]
  , irarity :: Rarity
irarity  = [(1, 3), (10, 3)]
  , iaspects :: [Aspect]
iaspects = Flag -> Aspect
SetFlag Flag
Unique
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
knife
  , ieffects :: [Effect]
ieffects = [Int -> Dice -> Effect
Discharge 1 50, Effect
Yell]  -- powerful and low timeout, but noisy
                                       -- and no effect if no weapons charged
  , idesc :: Text
idesc    = "A double dagger that a focused fencer can use to catch and twist away an opponent's blade."
  }
hammerTemplate :: ItemKind
hammerTemplate = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolHafted
  , iname :: Text
iname    = "war hammer"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
HAMMER_UNKNOWN, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color
BrMagenta]  -- avoid "pink"
  , icount :: Dice
icount   = 1
  , irarity :: Rarity
irarity  = [(5, 20), (8, 1)]
  , iverbHit :: Text
iverbHit = "club"
  , iweight :: Int
iweight  = 1600
  , idamage :: Dice
idamage  = 8 Int -> Int -> Dice
`d` 1  -- we are lying about the dice here, but the dungeon
                        -- is too small and the extra-dice hammers too rare
                        -- to subdivide this identification class by dice
  , iaspects :: [Aspect]
iaspects = [ GroupName ItemKind -> Aspect
PresentAs GroupName ItemKind
HAMMER_UNKNOWN
               , Flag -> Aspect
SetFlag Flag
Durable, Flag -> Aspect
SetFlag Flag
Meleeable
               , Int -> Aspect
toVelocity 40 ]  -- ensuring it hits with the tip costs speed
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = "It may not cause extensive wounds, but neither does it harmlessly glance off heavy armour as blades and polearms tend to. There are so many shapes and types, some looking more like tools than weapons, that at a glance you can't tell what a particular specimen does. It's obvious, though, that any of them requires some time to recover after a swing."  -- if it's really the average kind, the weak kind, the description stays; if not, it's replaced with one of the descriptions below at identification time
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
hammer1 :: ItemKind
hammer1 = ItemKind
hammerTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
STARTING_WEAPON, 70)]
  , iaspects :: [Aspect]
iaspects = [Dice -> Aspect
Timeout 5, EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotWeaponBig]
               [Aspect] -> [Aspect] -> [Aspect]
forall a. [a] -> [a] -> [a]
++ ItemKind -> [Aspect]
iaspects ItemKind
hammerTemplate
  }
hammer2 :: ItemKind
hammer2 = ItemKind
hammerTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 20), (GroupName ItemKind
STARTING_WEAPON, 7)]
  , iverbHit :: Text
iverbHit = "gouge"
  , iaspects :: [Aspect]
iaspects = [Dice -> Aspect
Timeout 3, EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotWeaponFast]
               [Aspect] -> [Aspect] -> [Aspect]
forall a. [a] -> [a] -> [a]
++ ItemKind -> [Aspect]
iaspects ItemKind
hammerTemplate
  , idesc :: Text
idesc    = "Upon closer inspection, this hammer turns out particularly handy and well balanced, with one thick and sturdy and two long and sharp points compensating the modest size."
  }
hammer3 :: ItemKind
hammer3 = ItemKind
hammerTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 3), (GroupName ItemKind
STARTING_WEAPON, 1)]
  , iverbHit :: Text
iverbHit = "puncture"
  , iweight :: Int
iweight  = 2400  -- weight gives it away
  , idamage :: Dice
idamage  = 12 Int -> Int -> Dice
`d` 1
  , iaspects :: [Aspect]
iaspects = [ Dice -> Aspect
Timeout 12  -- balance, or @DupItem@ would break the game
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotWeaponBig]
               [Aspect] -> [Aspect] -> [Aspect]
forall a. [a] -> [a] -> [a]
++ Aspect -> [Aspect] -> [Aspect]
forall a. Eq a => a -> [a] -> [a]
delete (GroupName ItemKind -> Aspect
PresentAs GroupName ItemKind
HAMMER_UNKNOWN) (ItemKind -> [Aspect]
iaspects ItemKind
hammerTemplate)
  , idesc :: Text
idesc    = "This hammer sports a long metal handle that increases the momentum of the sharpened head's swing, at the cost of long recovery."
  }
hammerParalyze :: ItemKind
hammerParalyze = ItemKind
hammerTemplate
  { iname :: Text
iname    = "The Brute Hammer"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
TREASURE, 20)]
  , irarity :: Rarity
irarity  = [(5, 1), (8, 6)]
  , iaspects :: [Aspect]
iaspects = [ Flag -> Aspect
SetFlag Flag
Unique
               , Dice -> Aspect
Timeout 5
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotWeaponBig ]
               [Aspect] -> [Aspect] -> [Aspect]
forall a. [a] -> [a] -> [a]
++ ItemKind -> [Aspect]
iaspects ItemKind
hammerTemplate
  , ieffects :: [Effect]
ieffects = [Dice -> Effect
Paralyze 10]
  , idesc :: Text
idesc    = "A huge shapeless lump of meteorite iron alloy on a sturdy pole. Nobody remains standing when this head connects."
  }
hammerSpark :: ItemKind
hammerSpark = ItemKind
hammerTemplate
  { iname :: Text
iname    = "The Grand Smithhammer"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
TREASURE, 20)]
  , irarity :: Rarity
irarity  = [(5, 1), (8, 6)]
  , iweight :: Int
iweight  = 2400  -- weight gives it away
  , idamage :: Dice
idamage  = 12 Int -> Int -> Dice
`d` 1
  , iaspects :: [Aspect]
iaspects = [ Flag -> Aspect
SetFlag Flag
Unique
               , Dice -> Aspect
Timeout 10
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotWeaponBig
               , Skill -> Dice -> Aspect
AddSkill Skill
SkShine 3]
               [Aspect] -> [Aspect] -> [Aspect]
forall a. [a] -> [a] -> [a]
++ Aspect -> [Aspect] -> [Aspect]
forall a. Eq a => a -> [a] -> [a]
delete (GroupName ItemKind -> Aspect
PresentAs GroupName ItemKind
HAMMER_UNKNOWN) (ItemKind -> [Aspect]
iaspects ItemKind
hammerTemplate)
  , ieffects :: [Effect]
ieffects = [GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_SPARK]
      -- we can't use a focused explosion, because it would harm the hammer
      -- wielder as well, unlike this one
  , idesc :: Text
idesc    = "Smiths of old wielded this heavy hammer and its sparks christened many a potent blade."
  }
sword :: ItemKind
sword = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolEdged
  , iname :: Text
iname    = "sword"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
STARTING_WEAPON, 30)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrBlue]
  , icount :: Dice
icount   = 1
  , irarity :: Rarity
irarity  = [(4, 1), (6, 20)]
  , iverbHit :: Text
iverbHit = "slash"
  , iweight :: Int
iweight  = 2000
  , idamage :: Dice
idamage  = 10 Int -> Int -> Dice
`d` 1
  , iaspects :: [Aspect]
iaspects = [ Dice -> Aspect
Timeout 7
               , Flag -> Aspect
SetFlag Flag
Durable, Flag -> Aspect
SetFlag Flag
Meleeable
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotWeaponBig
               , Int -> Aspect
toVelocity 40 ]  -- ensuring it hits with the tip costs speed
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = "Difficult to master; deadly when used effectively. The steel is particularly hard and keen, but rusts quickly without regular maintenance."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
swordImpress :: ItemKind
swordImpress = ItemKind
sword
  { iname :: Text
iname    = "The Master's Sword"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
TREASURE, 20)]
  , irarity :: Rarity
irarity  = [(5, 1), (8, 6)]
  , iaspects :: [Aspect]
iaspects = Flag -> Aspect
SetFlag Flag
Unique
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
sword
  , ieffects :: [Effect]
ieffects = [Effect
Impress]
  , idesc :: Text
idesc    = "A particularly well-balance blade, lending itself to impressive shows of fencing skill."
  }
swordNullify :: ItemKind
swordNullify = ItemKind
sword
  { iname :: Text
iname    = "The Gutting Sword"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
TREASURE, 20)]
  , iverbHit :: Text
iverbHit = "pierce"
  , irarity :: Rarity
irarity  = [(5, 1), (8, 6)]
  , iaspects :: [Aspect]
iaspects = [Flag -> Aspect
SetFlag Flag
Unique, Dice -> Aspect
Timeout 3, EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotWeaponFast]
               [Aspect] -> [Aspect] -> [Aspect]
forall a. [a] -> [a] -> [a]
++ (ItemKind -> [Aspect]
iaspects ItemKind
sword [Aspect] -> [Aspect] -> [Aspect]
forall a. Eq a => [a] -> [a] -> [a]
\\ [Dice -> Aspect
Timeout 7, EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotWeaponBig])
  , ieffects :: [Effect]
ieffects = [ Int -> Int -> CStore -> GroupName ItemKind -> Effect
DropItem 1 Int
forall a. Bounded a => a
maxBound CStore
COrgan GroupName ItemKind
CONDITION
               , Int -> Effect
RefillCalm (-10)
               , Effect
Yell ]
  , idesc :: Text
idesc    = "Cold, thin blade that pierces deeply and sends its victim into abrupt, sobering shock."
  }
halberd :: ItemKind
halberd = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolPolearm
  , iname :: Text
iname    = "war scythe"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100), (GroupName ItemKind
STARTING_WEAPON, 20)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrYellow]
  , icount :: Dice
icount   = 1
  , irarity :: Rarity
irarity  = [(5, 1), (8, 15)]
  , iverbHit :: Text
iverbHit = "impale"
  , iweight :: Int
iweight  = 3000
  , idamage :: Dice
idamage  = 12 Int -> Int -> Dice
`d` 1
  , iaspects :: [Aspect]
iaspects = [ Dice -> Aspect
Timeout 10
               , Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (-5 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`dL` 3) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5
                   -- useless against armor at game start
               , Skill -> Dice -> Aspect
AddSkill Skill
SkArmorMelee 20
               , Flag -> Aspect
SetFlag Flag
Durable, Flag -> Aspect
SetFlag Flag
Meleeable
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotWeaponBig
               , Int -> Aspect
toVelocity 20 ]  -- not balanced
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = "An improvised weapon made of scythe's blade attached to a long pole. Not often one succeeds in making enough space to swing it freely, but even when stuck between terrain obstacles it blocks approaches effectively and makes using other weapons difficult, both by friends and foes."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
halberd2 :: ItemKind
halberd2 = ItemKind
halberd
  { iname :: Text
iname    = "halberd"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 3 Int -> Int -> Int
forall a. Num a => a -> a -> a
* 2), (GroupName ItemKind
STARTING_WEAPON, 1)]
  , iweight :: Int
iweight  = 4000
  , iaspects :: [Aspect]
iaspects = Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee ((-6 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`dL` 4) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 10)
                 -- balance, or @DupItem@ would break the game;
                 -- together with @RerollItem@, it's allowed to, though
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: (ItemKind -> [Aspect]
iaspects ItemKind
halberd
                  [Aspect] -> [Aspect] -> [Aspect]
forall a. Eq a => [a] -> [a] -> [a]
\\ [Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (-6 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`dL` 4) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5])
  , idamage :: Dice
idamage  = 18 Int -> Int -> Dice
`d` 1
  , idesc :: Text
idesc    = "A long haft with a sharp blade. Designed and refined for war."
  }
halberd3 :: ItemKind
halberd3 = ItemKind
halberd2
  { iname :: Text
iname    = "bardiche"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 1 Int -> Int -> Int
forall a. Num a => a -> a -> a
* 2)]  -- compensating for low base rarity
  , iverbHit :: Text
iverbHit = "carve"
  , iweight :: Int
iweight  = 5000
  , idamage :: Dice
idamage  = 24 Int -> Int -> Dice
`d` 1
  , idesc :: Text
idesc    = "The reach of a spear but the edge of an axe."
  }
halberdPushActor :: ItemKind
halberdPushActor = ItemKind
halberd
  { iname :: Text
iname    = "The Swiss Halberd"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
TREASURE, 20)]
  , irarity :: Rarity
irarity  = [(7, 0), (9, 15)]
  , iaspects :: [Aspect]
iaspects = Flag -> Aspect
SetFlag Flag
Unique
               Aspect -> [Aspect] -> [Aspect]
forall a. a -> [a] -> [a]
: ItemKind -> [Aspect]
iaspects ItemKind
halberd
  , ieffects :: [Effect]
ieffects = [ThrowMod -> Effect
PushActor (Int -> Int -> Int -> ThrowMod
ThrowMod 200 100 1)]  -- 2 steps, slow
  , idesc :: Text
idesc    = "A versatile polearm, with great reach and leverage. Foes are held at a distance."
  }

-- ** Treasure

gemTemplate :: ItemKind
gemTemplate = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolGold
  , iname :: Text
iname    = "gem"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
GEM_UNKNOWN, 1), (GroupName ItemKind
VALUABLE, 100)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain ([Color] -> [Flavour]) -> [Color] -> [Flavour]
forall a b. (a -> b) -> a -> b
$ Color -> [Color] -> [Color]
forall a. Eq a => a -> [a] -> [a]
delete Color
BrYellow [Color]
brightCol  -- natural, so not fancy
  , icount :: Dice
icount   = 1
  , irarity :: Rarity
irarity  = [(3, 0), (10, 24)]
  , iverbHit :: Text
iverbHit = "tap"
  , iweight :: Int
iweight  = 50
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [GroupName ItemKind -> Aspect
PresentAs GroupName ItemKind
GEM_UNKNOWN, Flag -> Aspect
SetFlag Flag
Precious]
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = "Useless, and still worth around 100 gold each. Would gems of thought and pearls of artful design be valued that much in our age of Science and Progress!"
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
gem1 :: ItemKind
gem1 = ItemKind
gemTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
TREASURE, 100), (GroupName ItemKind
GEM, 100), (GroupName ItemKind
ANY_JEWELRY, 10)
               , (GroupName ItemKind
VALUABLE, 100) ]
  , irarity :: Rarity
irarity  = [(3, 0), (6, 12), (10, 8)]
  , iaspects :: [Aspect]
iaspects = [Skill -> Dice -> Aspect
AddSkill Skill
SkShine 1, Skill -> Dice -> Aspect
AddSkill Skill
SkSpeed (-1)]
                 -- reflects strongly, distracts; so it glows in the dark,
                 -- is visible on dark floor, but not too tempting to wear
               [Aspect] -> [Aspect] -> [Aspect]
forall a. [a] -> [a] -> [a]
++ ItemKind -> [Aspect]
iaspects ItemKind
gemTemplate
  }
gem2 :: ItemKind
gem2 = ItemKind
gem1
  { ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
TREASURE, 150), (GroupName ItemKind
GEM, 100), (GroupName ItemKind
ANY_JEWELRY, 10)
               , (GroupName ItemKind
VALUABLE, 100) ]
  , irarity :: Rarity
irarity  = [(5, 0), (7, 25), (10, 8)]
  }
gem3 :: ItemKind
gem3 = ItemKind
gem1
  { ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
TREASURE, 150), (GroupName ItemKind
GEM, 100), (GroupName ItemKind
ANY_JEWELRY, 10)
               , (GroupName ItemKind
VALUABLE, 100) ]
  , irarity :: Rarity
irarity  = [(7, 0), (8, 20), (10, 8)]
  }
gem4 :: ItemKind
gem4 = ItemKind
gem1
  { ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
TREASURE, 150), (GroupName ItemKind
GEM, 100), (GroupName ItemKind
ANY_JEWELRY, 30)
               , (GroupName ItemKind
VALUABLE, 100) ]
  , irarity :: Rarity
irarity  = [(9, 0), (10, 70)]
  }
gem5 :: ItemKind
gem5 = ItemKind
gem1
  { isymbol :: Char
isymbol  = Char
symbolSpecial
  , iname :: Text
iname    = "elixir"
  , ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
TREASURE, 100), (GroupName ItemKind
GEM, 25), (GroupName ItemKind
ANY_JEWELRY, 10)
               , (GroupName ItemKind
VALUABLE, 100) ]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrYellow]
  , irarity :: Rarity
irarity  = [(1, 40), (10, 10)]
  , iaspects :: [Aspect]
iaspects = [ Text -> Aspect
ELabel "of youth", Flag -> Aspect
SetFlag Flag
Precious  -- not hidden
               , Skill -> Dice -> Aspect
AddSkill Skill
SkOdor (-1) ]
  , ieffects :: [Effect]
ieffects = [Int -> Effect
RefillCalm 10, Int -> Effect
RefillHP 40]
  , idesc :: Text
idesc    = "A crystal vial of amber liquid, supposedly granting eternal youth and fetching 100 gold per piece. The main effect seems to be mild euphoria, but it admittedly smells good and heals minor ailments rather well."
  }
currencyTemplate :: ItemKind
currencyTemplate = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolGold
  , iname :: Text
iname    = "gold piece"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
CURRENCY_UNKNOWN, 1), (GroupName ItemKind
VALUABLE, 1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrYellow]
  , icount :: Dice
icount   = 10 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 20 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`dL` 20
  , irarity :: Rarity
irarity  = [(1, 25), (10, 10)]
  , iverbHit :: Text
iverbHit = "tap"
  , iweight :: Int
iweight  = 31
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [GroupName ItemKind -> Aspect
PresentAs GroupName ItemKind
CURRENCY_UNKNOWN, Flag -> Aspect
SetFlag Flag
Precious]
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = "Reliably valuable in every civilized plane of existence."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
currency :: ItemKind
currency = ItemKind
currencyTemplate
  { ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
TREASURE, 100), (GroupName ItemKind
S_CURRENCY, 100), (GroupName ItemKind
VALUABLE, 1)]
  , iaspects :: [Aspect]
iaspects = [Skill -> Dice -> Aspect
AddSkill Skill
SkShine 1, Skill -> Dice -> Aspect
AddSkill Skill
SkSpeed (-1)]
               [Aspect] -> [Aspect] -> [Aspect]
forall a. [a] -> [a] -> [a]
++ ItemKind -> [Aspect]
iaspects ItemKind
currencyTemplate
  }

-- ** Tools to be actively used, but not worn

jumpingPole :: ItemKind
jumpingPole = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolWand
  , iname :: Text
iname    = "jumping pole"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
White]
  , icount :: Dice
icount   = 1
  , irarity :: Rarity
irarity  = [(1, 3)]
  , iverbHit :: Text
iverbHit = "prod"
  , iweight :: Int
iweight  = 10000
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Dice -> Aspect
Timeout (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Dice
`d` 2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
- 1 Int -> Int -> Dice
`dL` 2) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* 5
               , Flag -> Aspect
SetFlag Flag
Durable ]
  , ieffects :: [Effect]
ieffects = [GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_HASTED 1]
                 -- This works and doesn't cause AI loops. @InsertMove@
                 -- would produce an activation that doesn't change game state.
                 -- Hasting for an absolute number of turns would cause
                 -- an explosion of time when several poles are accumulated.
                 -- Here it speeds AI up for exactly the turn spent activating,
                 -- so when AI applies it repeatedly, it gets its time back and
                 -- is not stuck. In total, the exploration speed is unchanged,
                 -- but it's useful when fleeing in the dark to make distance
                 -- and when initiating combat, so it's OK that AI uses it.
                 -- Timeout is rather high, because for factions with leaders
                 -- some time is often gained, so this could be useful
                 -- even during melee, which would be tiresome to employ.
  , idesc :: Text
idesc    = "Makes you vulnerable at take-off, but then you are free like a bird."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
seeingItem :: ItemKind
seeingItem = $WItemKind :: Char
-> Text
-> Freqs ItemKind
-> [Flavour]
-> Dice
-> Rarity
-> Text
-> Int
-> Dice
-> [Aspect]
-> [Effect]
-> [(GroupName ItemKind, CStore)]
-> Text
-> ItemKind
ItemKind
  { isymbol :: Char
isymbol  = Char
symbolFood
  , iname :: Text
iname    = "giant pupil"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, 100)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Red]
  , icount :: Dice
icount   = 1
  , irarity :: Rarity
irarity  = [(1, 2)]
  , iverbHit :: Text
iverbHit = "gaze at"
  , iweight :: Int
iweight  = 100
  , idamage :: Dice
idamage  = 0
  , iaspects :: [Aspect]
iaspects = [ Dice -> Aspect
Timeout 3
               , Skill -> Dice -> Aspect
AddSkill Skill
SkSight 10  -- a spyglass for quick wields
               , Skill -> Dice -> Aspect
AddSkill Skill
SkMaxCalm 30  -- to diminish clipping sight by Calm
               , Skill -> Dice -> Aspect
AddSkill Skill
SkShine 2  -- to lit corridors when flying
               , Flag -> Aspect
SetFlag Flag
Periodic ]
  , ieffects :: [Effect]
ieffects = [ DetectKind -> Int -> Effect
Detect DetectKind
DetectActor 20  -- rare enough
               , Condition -> Effect -> Effect
When (ActivationFlag -> Condition
TriggeredBy ActivationFlag
ActivationPeriodic) (Effect -> Effect) -> Effect -> Effect
forall a b. (a -> b) -> a -> b
$ [Effect] -> Effect
SeqEffect
                   [ GroupName ItemKind -> Effect
toOrganNoTimer GroupName ItemKind
S_POISONED  -- really can't be worn
                   , GroupName ItemKind -> Dice -> Effect
Summon GroupName ItemKind
MOBILE_MONSTER 1 ] ]
  , idesc :: Text
idesc    = "A slimy, dilated green pupil torn out from some giant eye. Clear and focused, as if still alive."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }