-- | Definitions of basic items.
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 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.DefsInternal
import Game.LambdaHack.Definition.Flavour

import Content.ItemKindActor
import Content.ItemKindBlast
import Content.ItemKindEmbed
import Content.ItemKindOrgan
import Content.ItemKindTemporary
import Content.RuleKind

-- * 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]
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 $mFLASK_UNKNOWN :: forall {r}. GroupName ItemKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bFLASK_UNKNOWN :: GroupName ItemKind
FLASK_UNKNOWN = GroupName "flask unknown"
pattern $mPOTION_UNKNOWN :: forall {r}. GroupName ItemKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bPOTION_UNKNOWN :: GroupName ItemKind
POTION_UNKNOWN = GroupName "potion unknown"
pattern $mEDIBLE_PLANT_UNKNOWN :: forall {r}. GroupName ItemKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bEDIBLE_PLANT_UNKNOWN :: GroupName ItemKind
EDIBLE_PLANT_UNKNOWN = GroupName "edible plant unknown"
pattern $mSCROLL_UNKNOWN :: forall {r}. GroupName ItemKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bSCROLL_UNKNOWN :: GroupName ItemKind
SCROLL_UNKNOWN = GroupName "scroll unknown"
pattern $mNECKLACE_UNKNOWN :: forall {r}. GroupName ItemKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bNECKLACE_UNKNOWN :: GroupName ItemKind
NECKLACE_UNKNOWN = GroupName "necklace unknown"
pattern $mRING_UNKNOWN :: forall {r}. GroupName ItemKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bRING_UNKNOWN :: GroupName ItemKind
RING_UNKNOWN = GroupName "ring unknown"
pattern $mHAMMER_UNKNOWN :: forall {r}. GroupName ItemKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bHAMMER_UNKNOWN :: GroupName ItemKind
HAMMER_UNKNOWN = GroupName "hammer unknown"
pattern $mGEM_UNKNOWN :: forall {r}. GroupName ItemKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bGEM_UNKNOWN :: GroupName ItemKind
GEM_UNKNOWN = GroupName "gem unknown"
pattern $mCURRENCY_UNKNOWN :: forall {r}. GroupName ItemKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bCURRENCY_UNKNOWN :: GroupName ItemKind
CURRENCY_UNKNOWN = GroupName "currency unknown"

pattern $mHARPOON :: forall {r}. GroupName ItemKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bHARPOON :: GroupName ItemKind
HARPOON = GroupName "harpoon"
pattern $mEDIBLE_PLANT :: forall {r}. GroupName ItemKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bEDIBLE_PLANT :: GroupName ItemKind
EDIBLE_PLANT = GroupName "edible plant"
pattern $mRING_OF_OPPORTUNITY_GRENADIER :: forall {r}. GroupName ItemKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bRING_OF_OPPORTUNITY_GRENADIER :: GroupName ItemKind
RING_OF_OPPORTUNITY_GRENADIER = GroupName "ring of grenadier"
pattern $mARMOR_LOOSE :: forall {r}. GroupName ItemKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bARMOR_LOOSE :: GroupName ItemKind
ARMOR_LOOSE = GroupName "loose armor"
pattern $mCLOTHING_MISC :: forall {r}. GroupName ItemKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bCLOTHING_MISC :: GroupName ItemKind
CLOTHING_MISC = GroupName "miscellaneous clothing"
pattern $mCHIC_GEAR :: forall {r}. GroupName ItemKind -> ((# #) -> r) -> ((# #) -> r) -> r
$bCHIC_GEAR :: GroupName ItemKind
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
flask15, 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
ring9, ItemKind
ring10, 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
daggerDischarge, 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, flask15, 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, ring9, ring10, armorLeather, armorMail, meleeEnhancement, gloveFencing, gloveGauntlet, gloveJousting, hatUshanka, capReinforced, helmArmored, smokingJacket, buckler, shield, shield2, shield3, hammerTemplate, hammer1, hammer2, hammer3, hammerParalyze, hammerSpark, knife, daggerDischarge, 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 :: ContentSymbol ItemKind

symbolProjectile :: ContentSymbol ItemKind
symbolProjectile = ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
rsymbolProjectile (ItemSymbolsUsedInEngine -> ContentSymbol ItemKind)
-> ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
forall a b. (a -> b) -> a -> b
$ RuleContent -> ItemSymbolsUsedInEngine
ritemSymbols RuleContent
standardRules
_symbolLauncher :: ContentSymbol ItemKind
_symbolLauncher  = ContentSymbol ItemKind -> ContentSymbol ItemKind
forall c. ContentSymbol ItemKind -> ContentSymbol ItemKind
toContentSymbol ContentSymbol ItemKind
'}'
symbolLight :: ContentSymbol ItemKind
symbolLight      = ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
rsymbolLight (ItemSymbolsUsedInEngine -> ContentSymbol ItemKind)
-> ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
forall a b. (a -> b) -> a -> b
$ RuleContent -> ItemSymbolsUsedInEngine
ritemSymbols RuleContent
standardRules
symbolTool :: ContentSymbol ItemKind
symbolTool       = ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
rsymbolTool (ItemSymbolsUsedInEngine -> ContentSymbol ItemKind)
-> ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
forall a b. (a -> b) -> a -> b
$ RuleContent -> ItemSymbolsUsedInEngine
ritemSymbols RuleContent
standardRules
symbolSpecial :: ContentSymbol ItemKind
symbolSpecial    = ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
rsymbolSpecial (ItemSymbolsUsedInEngine -> ContentSymbol ItemKind)
-> ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
forall a b. (a -> b) -> a -> b
$ RuleContent -> ItemSymbolsUsedInEngine
ritemSymbols RuleContent
standardRules
symbolGold :: ContentSymbol ItemKind
symbolGold       = ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
rsymbolGold (ItemSymbolsUsedInEngine -> ContentSymbol ItemKind)
-> ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
forall a b. (a -> b) -> a -> b
$ RuleContent -> ItemSymbolsUsedInEngine
ritemSymbols RuleContent
standardRules
symbolNecklace :: ContentSymbol ItemKind
symbolNecklace   = ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
rsymbolNecklace (ItemSymbolsUsedInEngine -> ContentSymbol ItemKind)
-> ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
forall a b. (a -> b) -> a -> b
$ RuleContent -> ItemSymbolsUsedInEngine
ritemSymbols RuleContent
standardRules
symbolRing :: ContentSymbol ItemKind
symbolRing       = ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
rsymbolRing (ItemSymbolsUsedInEngine -> ContentSymbol ItemKind)
-> ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
forall a b. (a -> b) -> a -> b
$ RuleContent -> ItemSymbolsUsedInEngine
ritemSymbols RuleContent
standardRules
symbolPotion :: ContentSymbol ItemKind
symbolPotion     = ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
rsymbolPotion (ItemSymbolsUsedInEngine -> ContentSymbol ItemKind)
-> ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
forall a b. (a -> b) -> a -> b
$ RuleContent -> ItemSymbolsUsedInEngine
ritemSymbols RuleContent
standardRules
symbolFlask :: ContentSymbol ItemKind
symbolFlask      = ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
rsymbolFlask (ItemSymbolsUsedInEngine -> ContentSymbol ItemKind)
-> ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
forall a b. (a -> b) -> a -> b
$ RuleContent -> ItemSymbolsUsedInEngine
ritemSymbols RuleContent
standardRules
symbolScroll :: ContentSymbol ItemKind
symbolScroll     = ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
rsymbolScroll (ItemSymbolsUsedInEngine -> ContentSymbol ItemKind)
-> ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
forall a b. (a -> b) -> a -> b
$ RuleContent -> ItemSymbolsUsedInEngine
ritemSymbols RuleContent
standardRules
symbolTorsoArmor :: ContentSymbol ItemKind
symbolTorsoArmor = ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
rsymbolTorsoArmor (ItemSymbolsUsedInEngine -> ContentSymbol ItemKind)
-> ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
forall a b. (a -> b) -> a -> b
$ RuleContent -> ItemSymbolsUsedInEngine
ritemSymbols RuleContent
standardRules
symbolMiscArmor :: ContentSymbol ItemKind
symbolMiscArmor  = ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
rsymbolMiscArmor (ItemSymbolsUsedInEngine -> ContentSymbol ItemKind)
-> ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
forall a b. (a -> b) -> a -> b
$ RuleContent -> ItemSymbolsUsedInEngine
ritemSymbols RuleContent
standardRules
symbolClothes :: ContentSymbol ItemKind
symbolClothes    = ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
rsymbolClothes (ItemSymbolsUsedInEngine -> ContentSymbol ItemKind)
-> ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
forall a b. (a -> b) -> a -> b
$ RuleContent -> ItemSymbolsUsedInEngine
ritemSymbols RuleContent
standardRules
symbolShield :: ContentSymbol ItemKind
symbolShield     = ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
rsymbolShield (ItemSymbolsUsedInEngine -> ContentSymbol ItemKind)
-> ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
forall a b. (a -> b) -> a -> b
$ RuleContent -> ItemSymbolsUsedInEngine
ritemSymbols RuleContent
standardRules
symbolPolearm :: ContentSymbol ItemKind
symbolPolearm    = ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
rsymbolPolearm (ItemSymbolsUsedInEngine -> ContentSymbol ItemKind)
-> ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
forall a b. (a -> b) -> a -> b
$ RuleContent -> ItemSymbolsUsedInEngine
ritemSymbols RuleContent
standardRules
symbolEdged :: ContentSymbol ItemKind
symbolEdged      = ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
rsymbolEdged (ItemSymbolsUsedInEngine -> ContentSymbol ItemKind)
-> ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
forall a b. (a -> b) -> a -> b
$ RuleContent -> ItemSymbolsUsedInEngine
ritemSymbols RuleContent
standardRules
symbolHafted :: ContentSymbol ItemKind
symbolHafted     = ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
rsymbolHafted (ItemSymbolsUsedInEngine -> ContentSymbol ItemKind)
-> ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
forall a b. (a -> b) -> a -> b
$ RuleContent -> ItemSymbolsUsedInEngine
ritemSymbols RuleContent
standardRules
symbolWand :: ContentSymbol ItemKind
symbolWand       = ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
rsymbolWand (ItemSymbolsUsedInEngine -> ContentSymbol ItemKind)
-> ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
forall a b. (a -> b) -> a -> b
$ RuleContent -> ItemSymbolsUsedInEngine
ritemSymbols RuleContent
standardRules
_symbolStaff :: ContentSymbol ItemKind
_symbolStaff     = ContentSymbol ItemKind -> ContentSymbol ItemKind
forall c. ContentSymbol ItemKind -> ContentSymbol ItemKind
toContentSymbol ContentSymbol ItemKind
'_'
symbolFood :: ContentSymbol ItemKind
symbolFood       = ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
rsymbolFood (ItemSymbolsUsedInEngine -> ContentSymbol ItemKind)
-> ItemSymbolsUsedInEngine -> ContentSymbol ItemKind
forall a b. (a -> b) -> a -> b
$ RuleContent -> ItemSymbolsUsedInEngine
ritemSymbols RuleContent
standardRules

-- ** Thrown weapons

sandstoneRock :: ItemKind
sandstoneRock = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolProjectile
  , iname :: Text
iname    = Text
"sandstone rock"
  , ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
S_SANDSTONE_ROCK, Int
1)
               , (GroupName ItemKind
UNREPORTED_INVENTORY, Int
1) ]  -- too weak to spam
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Green]
  , icount :: Dice
icount   = Dice
1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Dice
`d` Int
2  -- > 1, to let AI ignore sole pieces
  , irarity :: Rarity
irarity  = [(Double
1, Int
20), (Double
10, Int
1)]  -- a few already in starting stash
  , iverbHit :: Text
iverbHit = Text
"hit"
  , iweight :: Int
iweight  = Int
300
  , idamage :: Dice
idamage  = Int
1 Int -> Int -> Dice
`d` Int
1
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ -Dice
16 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* Dice
5
               , Flag -> Aspect
SetFlag Flag
Fragile
               , Int -> Aspect
toVelocity Int
70 ] -- not dense, irregular
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = Text
"A lump of brittle sandstone rock."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
dart :: ItemKind
dart = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolProjectile
  , iname :: Text
iname    = Text
"dart"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, Int
100), (GroupName ItemKind
ANY_ARROW, Int
50), (GroupName ItemKind
WEAK_ARROW, Int
50)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrRed]
  , icount :: Dice
icount   = Dice
1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
4 Int -> Int -> Dice
`dL` Int
5
  , irarity :: Rarity
irarity  = [(Double
1, Int
15), (Double
10, Int
5)]
  , iverbHit :: Text
iverbHit = Text
"prick"
  , iweight :: Int
iweight  = Int
40
  , idamage :: Dice
idamage  = Int
1 Int -> Int -> Dice
`d` Int
1
  , iaspects :: [Aspect]
iaspects = [Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (-Dice
15 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Dice
`d` Int
2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Dice
`dL` Int
3) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* Dice
5]
                 -- only good against leather
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = Text
"A sharp delicate dart with fins."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
spike :: ItemKind
spike = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolProjectile
  , iname :: Text
iname    = Text
"spike"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, Int
100), (GroupName ItemKind
ANY_ARROW, Int
50), (GroupName ItemKind
WEAK_ARROW, Int
50)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrCyan]
  , icount :: Dice
icount   = Dice
1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
4 Int -> Int -> Dice
`dL` Int
5
  , irarity :: Rarity
irarity  = [(Double
1, Int
10), (Double
10, Int
8)]
  , iverbHit :: Text
iverbHit = Text
"nick"
  , iweight :: Int
iweight  = Int
150
  , idamage :: Dice
idamage  = Int
2 Int -> Int -> Dice
`d` Int
1
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (-Dice
10 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Dice
`d` Int
2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Dice
`dL` Int
3) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* Dice
5
                   -- heavy vs armor
               , Flag -> Aspect
SetFlag Flag
MinorEffects
               , Int -> Aspect
toVelocity Int
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    = Text
"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    = [(COMMON_ITEM, 2), (ANY_ARROW, 1), (WEAK_ARROW, 1)]
  , iflavour = zipPlain [Cyan]
  , iverbHit = "penetrate"
  , iweight  = 200
  , idamage  = 4 `d` 1
  , iaspects = [ AddSkill SkHurtMelee $ (-10 + 1 `d` 2 + 1 `dL` 3) * 5
               , SetFlag MinorEffects
               , Odds (10 * 1 `dL` 10) [] [toVelocity 70] ]
                   -- at deep levels sometimes even don't limit velocity
  , idesc    = "A jagged skewer of rusty metal."
  }
slingStone :: ItemKind
slingStone = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolProjectile
  , iname :: Text
iname    = Text
"sling stone"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, Int
5), (GroupName ItemKind
ANY_ARROW, Int
100)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Blue]
  , icount :: Dice
icount   = Dice
1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
3 Int -> Int -> Dice
`dL` Int
4
  , irarity :: Rarity
irarity  = [(Double
1, Int
1), (Double
10, Int
20)]
  , iverbHit :: Text
iverbHit = Text
"batter"
  , iweight :: Int
iweight  = Int
200
  , idamage :: Dice
idamage  = Int
1 Int -> Int -> Dice
`d` Int
1
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (-Dice
10 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Dice
`d` Int
2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Dice
`dL` Int
3) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* Dice
5
                   -- heavy, to bludgeon through armor
               , Flag -> Aspect
SetFlag Flag
MinorEffects
               , Int -> Aspect
toVelocity Int
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    = Text
"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 = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolProjectile
  , iname :: Text
iname    = Text
"sling bullet"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, Int
5), (GroupName ItemKind
ANY_ARROW, Int
100)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrBlack]
  , icount :: Dice
icount   = Dice
1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
6 Int -> Int -> Dice
`dL` Int
4
  , irarity :: Rarity
irarity  = [(Double
1, Int
1), (Double
10, Int
15)]
  , iverbHit :: Text
iverbHit = Text
"slug"
  , iweight :: Int
iweight  = Int
28
  , idamage :: Dice
idamage  = Int
1 Int -> Int -> Dice
`d` Int
1
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (-Dice
17 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Dice
`d` Int
2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Dice
`dL` Int
3) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* Dice
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 Int
200 Int
100 Int
2  -- piercing
               , Flag -> Aspect
SetFlag Flag
Fragile ]
                   -- otherwise would rarely break and the player would have
                   -- unlimited resource and would have to pick up constantly
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = Text
"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 = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolProjectile
  , iname :: Text
iname    = Text
"bolas set"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, Int
100)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrGreen]
  , icount :: Dice
icount   = Int
1 Int -> Int -> Dice
`dL` Int
4
  , irarity :: Rarity
irarity  = [(Double
5, Int
5), (Double
10, Int
5)]
  , iverbHit :: Text
iverbHit = Text
"entangle"
  , iweight :: Int
iweight  = Int
500
  , idamage :: Dice
idamage  = Int
1 Int -> Int -> Dice
`d` Int
1
  , iaspects :: [Aspect]
iaspects = [Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ -Dice
14 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* Dice
5]
  , ieffects :: [Effect]
ieffects = [Dice -> Effect
Paralyze Dice
15, Int -> Dice -> Effect
Discharge Int
1 Dice
100]
  , idesc :: Text
idesc    = Text
"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 = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolProjectile
  , iname :: Text
iname    = Text
"harpoon"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, Int
100), (GroupName ItemKind
HARPOON, Int
100)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Brown]
  , icount :: Dice
icount   = Int
1 Int -> Int -> Dice
`dL` Int
5
  , irarity :: Rarity
irarity  = [(Double
10, Int
10)]
  , iverbHit :: Text
iverbHit = Text
"hook"
  , iweight :: Int
iweight  = Int
750
  , idamage :: Dice
idamage  = Int
5 Int -> Int -> Dice
`d` Int
1
  , iaspects :: [Aspect]
iaspects = [Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (-Dice
10 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Dice
`d` Int
2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Dice
`dL` Int
3) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* Dice
5]
  , ieffects :: [Effect]
ieffects = [ ThrowMod -> Effect
PullActor (Int -> Int -> Int -> ThrowMod
ThrowMod Int
200 Int
50 Int
1)  -- 1 step, fast
               , Effect
Yell ]  -- yell, because brutal
  , idesc :: Text
idesc    = Text
"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    = "The whaling Harpoon"
  , ifreq    = [(COMMON_ITEM, 10), (HARPOON, 2)]
  , icount   = 2 `dL` 5
  , iweight  = 1000
  , idamage  = 21 `d` 1
  , iaspects = SetFlag Unique : delete (SetFlag Durable) (iaspects harpoon)
  , idesc    = "With a brittle, barbed head and thick cord, this ancient weapon is designed for formidable prey. The age has made the edge thinner and sharper, but brittle and splintering, so it won't last beyond a single hit. "
  }
net :: ItemKind
net = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolProjectile
  , iname :: Text
iname    = Text
"net"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, Int
100)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrGreen]
  , icount :: Dice
icount   = Int
1 Int -> Int -> Dice
`dL` Int
3
  , irarity :: Rarity
irarity  = [(Double
5, Int
5), (Double
10, Int
7)]
  , iverbHit :: Text
iverbHit = Text
"entangle"
  , iweight :: Int
iweight  = Int
1000
  , idamage :: Dice
idamage  = Int
2 Int -> Int -> Dice
`d` Int
1
  , iaspects :: [Aspect]
iaspects = [Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ -Dice
14 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* Dice
5]
  , ieffects :: [Effect]
ieffects = [ GroupName ItemKind -> Dice -> Effect
toOrganBad GroupName ItemKind
S_SLOWED (Dice
3 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Dice
`d` Int
3)
               , Int -> Int -> CStore -> GroupName ItemKind -> Effect
DropItem Int
forall a. Bounded a => a
maxBound Int
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 Int
100 Int
50 Int
1) ]  -- 1 step; painful
  , idesc :: Text
idesc    = Text
"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 = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolProjectile
  , iname :: Text
iname    = Text
"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, Int
100), (GroupName ItemKind
EXPLOSIVE, Int
200)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Red]
  , icount :: Dice
icount   = Int
1 Int -> Int -> Dice
`dL` Int
5  -- many, because not very intricate
  , irarity :: Rarity
irarity  = [(Double
5, Int
8), (Double
10, Int
5)]
  , iverbHit :: Text
iverbHit = Text
"thud"
  , iweight :: Int
iweight  = Int
3000  -- low velocity due to weight
  , idamage :: Dice
idamage  = Dice
0  -- heavy and hard, but let's not confuse with blast damage
  , iaspects :: [Aspect]
iaspects = [ Text -> Aspect
ELabel Text
"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    = Text
"The practical application of science."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
concussionBomb :: ItemKind
concussionBomb = ItemKind
fragmentationBomb
  { 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 = zipPlain [Magenta]
  , iverbHit = "flap"
  , iweight  = 400
  , iaspects = [ ELabel "of mining charges"
               , SetFlag Lobable, SetFlag Fragile
               , toVelocity 70 ]  -- flappy and so slow
  , ieffects = [ Explode S_FOCUSED_CONCUSSION
               , OnSmash (Explode S_VIOLENT_CONCUSSION) ]
  , 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    = "magnesium ribbon"  -- filled with magnesium flash powder
  , iflavour = zipPlain [BrYellow]  -- avoid @BrWhite@; looks wrong in dark
  , iverbHit = "flash"
  , iweight  = 400
  , iaspects = [ SetFlag Lobable, SetFlag Fragile
               , toVelocity 70 ]  -- bad shape for throwing
  , ieffects = [Explode S_FOCUSED_FLASH, OnSmash (Explode S_VIOLENT_FLASH)]
  , idesc    = "For dramatic entrances and urgent exits."
  }
firecrackerBomb :: ItemKind
firecrackerBomb = ItemKind
fragmentationBomb
  { iname = "roll"  -- not fireworks, as they require outdoors
  , iflavour = zipPlain [BrMagenta]
  , irarity  = [(1, 5), (5, 6)]  -- a toy, if harmful
  , iverbHit = "crack"  -- a pun, matches the verb from "ItemKindBlast"
  , iweight  = 1000
  , iaspects = [SetFlag Lobable, SetFlag Fragile]
  , ieffects = [Explode S_FIRECRACKER, OnSmash (Explode S_FIRECRACKER)]
  , 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 = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolFlask
  , iname :: Text
iname    = Text
"flask"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
FLASK_UNKNOWN, Int
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   = Int
1 Int -> Int -> Dice
`dL` Int
3
  , irarity :: Rarity
irarity  = [(Double
1, Int
7), (Double
10, Int
3)]
  , iverbHit :: Text
iverbHit = Text
"splash"
  , iweight :: Int
iweight  = Int
500
  , idamage :: Dice
idamage  = Dice
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 Int
60 ]  -- oily, rather bad grip
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = Text
"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    = [ (COMMON_ITEM, 100), (ANY_FLASK, 100), (EXPLOSIVE, 100)
               , (ANY_GLASS, 100) ]
  , icount   = 1 `dL` 5
  , irarity  = [(10, 10)]
  , iaspects = ELabel "of strength brew"
               : iaspects flaskTemplate
  , ieffects = [ toOrganGood S_STRENGTHENED (20 + 1 `d` 5)
               , OnSmash (Explode S_DENSE_SHOWER) ]
  }
flask2 :: ItemKind
flask2 = ItemKind
flaskTemplate
  { ifreq    = [ (COMMON_ITEM, 100), (ANY_FLASK, 100), (EXPLOSIVE, 100)
               , (ANY_GLASS, 100) ]
  , iaspects = ELabel "of weakness brew"
               : iaspects flaskTemplate
  , ieffects = [ toOrganBad S_WEAKENED (20 + 1 `d` 5)
               , OnSmash (Explode S_SPARSE_SHOWER) ]
  }
flask3 :: ItemKind
flask3 = ItemKind
flaskTemplate
  { ifreq    = [ (COMMON_ITEM, 100), (ANY_FLASK, 100), (EXPLOSIVE, 100)
               , (ANY_GLASS, 100) ]
  , iaspects = ELabel "of melee protective balm"
               : iaspects flaskTemplate
  , ieffects = [ toOrganGood S_PROTECTED_FROM_MELEE (20 + 1 `d` 5)
               , OnSmash (Explode S_MELEE_PROTECTIVE_BALM) ]
  }
flask4 :: ItemKind
flask4 = ItemKind
flaskTemplate
  { ifreq    = [ (COMMON_ITEM, 100), (ANY_FLASK, 100), (EXPLOSIVE, 100)
               , (ANY_GLASS, 100) ]
  , iaspects = ELabel "of ranged protective balm"
               : iaspects flaskTemplate
  , ieffects = [ toOrganGood S_PROTECTED_FROM_RANGED (20 + 1 `d` 5)
               , OnSmash (Explode S_RANGE_PROTECTIVE_BALM) ]
  }
flask5 :: ItemKind
flask5 = ItemKind
flaskTemplate
  { ifreq    = [ (COMMON_ITEM, 100), (ANY_FLASK, 100), (EXPLOSIVE, 100)
               , (ANY_GLASS, 100) ]
  , iaspects = ELabel "of PhD defense questions"
               : iaspects flaskTemplate
  , ieffects = [ toOrganBad S_DEFENSELESS (20 + 1 `d` 5)
               , Impress
               , Detect DetectExit 20
               , OnSmash (Explode S_DEFENSELESSNESS_RUNOUT) ]
  }
flask6 :: ItemKind
flask6 = ItemKind
flaskTemplate
  { ifreq    = [ (COMMON_ITEM, 100), (ANY_FLASK, 100), (EXPLOSIVE, 100)
               , (ANY_GLASS, 100) ]
  , irarity  = [(1, 1)]  -- not every playthrough needs one
  , iaspects = ELabel "of resolution"
               : iaspects flaskTemplate
  , ieffects = [ toOrganGood S_RESOLUTE (100 + 1 `d` 20)  -- long, for scouting
               , RefillCalm 100  -- not to make it a drawback, via @calmEnough@
               , OnSmash (Explode S_RESOLUTION_DUST) ]
  }
flask7 :: ItemKind
flask7 = ItemKind
flaskTemplate
  { ifreq    = [ (COMMON_ITEM, 100), (ANY_FLASK, 100), (EXPLOSIVE, 100)
               , (ANY_GLASS, 100) ]
  , icount   = 1 `d` 2  -- too powerful en masse
  , iaspects = ELabel "of haste brew"
               : iaspects flaskTemplate
  , ieffects = [ toOrganGood S_HASTED (20 + 1 `d` 5)
               , OnSmash (Explode S_HASTE_SPRAY) ]
  }
flask8 :: ItemKind
flask8 = ItemKind
flaskTemplate
  { ifreq    = [ (COMMON_ITEM, 100), (ANY_FLASK, 100), (EXPLOSIVE, 100)
               , (ANY_GLASS, 100) ]
  , iaspects = ELabel "of eye drops"
               : iaspects flaskTemplate
  , ieffects = [ toOrganGood S_FAR_SIGHTED (40 + 1 `d` 10)
               , OnSmash (Explode S_EYE_DROP) ]
  }
flask9 :: ItemKind
flask9 = ItemKind
flaskTemplate
  { ifreq    = [ (COMMON_ITEM, 100), (ANY_FLASK, 100), (EXPLOSIVE, 100)
               , (ANY_GLASS, 100) ]
  , irarity  = [(10, 2)]  -- not very useful right now
  , iaspects = ELabel "of smelly concoction"
               : iaspects flaskTemplate
  , ieffects = [ toOrganGood S_KEEN_SMELLING (40 + 1 `d` 10)
               , Detect DetectActor 10  -- make it at least slightly useful
               , OnSmash (Explode S_SMELLY_DROPLET) ]
  }
flask10 :: ItemKind
flask10 = ItemKind
flaskTemplate
  { ifreq    = [ (COMMON_ITEM, 100), (ANY_FLASK, 100), (EXPLOSIVE, 100)
               , (ANY_GLASS, 100) ]
  , irarity  = [(10, 2)]  -- not very useful right now
  , iaspects = ELabel "of cat tears"
               : iaspects flaskTemplate
  , ieffects = [ toOrganGood S_SHINY_EYED (40 + 1 `d` 10)
               , OnSmash (Explode S_EYE_SHINE) ]
  }
flask11 :: ItemKind
flask11 = ItemKind
flaskTemplate
  { iname    = "bottle"
  , ifreq    = [ (COMMON_ITEM, 100), (ANY_FLASK, 100), (EXPLOSIVE, 100)
               , (ANY_GLASS, 100) ]
  , icount   = 1 `d` 3  -- the only one sometimes giving away its identity
  , iaspects = ELabel "of whiskey"
               : iaspects flaskTemplate
  , ieffects = [ toOrganGood S_DRUNK (20 + 1 `d` 5)
               , Burn 10, RefillHP 10, Yell
               , OnSmash (Explode S_WHISKEY_SPRAY) ]
  }
flask12 :: ItemKind
flask12 = ItemKind
flaskTemplate
  { ifreq    = [ (COMMON_ITEM, 100), (ANY_FLASK, 100), (EXPLOSIVE, 100)
               , (ANY_GLASS, 100) ]
  , iaspects = ELabel "of bait cocktail"
               : iaspects flaskTemplate
  , ieffects = [ toOrganGood S_DRUNK (20 + 1 `d` 5)
               , Burn 1, RefillHP 3  -- risky exploit possible, good
               , Summon MOBILE_ANIMAL 1
               , OnSmash (Summon MOBILE_ANIMAL 1)
               , OnSmash Impress  -- mildly useful when thrown
               , OnSmash (Explode S_WASTE) ]
  }
flask13 :: ItemKind
flask13 = ItemKind
flaskTemplate
  { ifreq    = [ (COMMON_ITEM, 100), (ANY_FLASK, 100), (EXPLOSIVE, 100)
               , (ANY_GLASS, 100) ]
  , iaspects = ELabel "of poison"
               : iaspects flaskTemplate
  , ieffects = [ toOrganNoTimer S_POISONED, toOrganNoTimer S_POISONED  -- x2
               , OnSmash (Explode S_POISON_CLOUD) ]
  }
flask14 :: ItemKind
flask14 = ItemKind
flaskTemplate
  { ifreq    = [ (COMMON_ITEM, 100), (ANY_FLASK, 100), (EXPLOSIVE, 100)
               , (ANY_GLASS, 100) ]
  , iaspects = ELabel "of calamity"
               : iaspects flaskTemplate
  , ieffects = [ toOrganNoTimer S_POISONED
               , toOrganBad S_WEAKENED (20 + 1 `d` 5)
               , toOrganBad S_DEFENSELESS (20 + 1 `d` 5)
               , OnSmash (Explode S_GLASS_HAIL) ]  -- enough glass to cause that
  }
flask15 :: ItemKind
flask15 = ItemKind
flaskTemplate
  { ifreq    = [ (COMMON_ITEM, 100), (ANY_FLASK, 100), (EXPLOSIVE, 100)
               , (ANY_GLASS, 100) ]
  , iaspects = ELabel "of snail gel"
               : iaspects flaskTemplate
  , ieffects = [ toOrganBad S_SLOWED (3 + 1 `d` 3)
               , OnSmash (Explode S_FOCUSED_SLOWNESS_MIST) ]
  }

-- Potions are often not intended to be thrown. They are 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 = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolPotion
  , iname :: Text
iname    = Text
"potion"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
POTION_UNKNOWN, Int
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   = Int
1 Int -> Int -> Dice
`dL` Int
3
  , irarity :: Rarity
irarity  = [(Double
1, Int
10), (Double
10, Int
6)]
  , iverbHit :: Text
iverbHit = Text
"splash"
  , iweight :: Int
iweight  = Int
200
  , idamage :: Dice
idamage  = Dice
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 Int
50 ]  -- oily, small momentum due to small size
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = Text
"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    = "vial"
  , ifreq    = [(COMMON_ITEM, 100), (ANY_POTION, 100), (ANY_GLASS, 100)]
  , icount   = 3 `dL` 1  -- very useful, despite appearances
  , iaspects = ELabel "of rose water"
               : iaspects potionTemplate
  , ieffects = [ Impress, toOrganGood S_ROSE_SMELLING (50 + 1 `d` 10)
               , OnSmash ApplyPerfume, OnSmash (Explode S_FRAGRANCE) ]
  }
potion2 :: ItemKind
potion2 = ItemKind
potionTemplate
  { iname    = "the Potion"
  , ifreq    = [(TREASURE, 100), (ANY_GLASS, 100)]
  , icount   = 1
  , irarity  = [(5, 8), (10, 8)]
  , iaspects = [SetFlag Unique, ELabel "of Attraction", SetFlag MetaGame]
               ++ iaspects potionTemplate
  , ieffects = [ Dominate
               , toOrganGood S_HASTED (20 + 1 `d` 5)
               , OnSmash (Explode S_PHEROMONE)
               , OnSmash (Explode S_HASTE_SPRAY) ]
  , idesc    = "The liquid fizzes with energy."
  }
potion3 :: ItemKind
potion3 = ItemKind
potionTemplate
  { ifreq    = [(COMMON_ITEM, 100), (ANY_POTION, 100), (ANY_GLASS, 100)]
  , ieffects = [ RefillHP 5, DropItem 1 maxBound COrgan S_POISONED
               , OnSmash (Explode S_HEALING_MIST) ]
  }
potion4 :: ItemKind
potion4 = ItemKind
potionTemplate
  { ifreq    = [(COMMON_ITEM, 100), (ANY_POTION, 100), (ANY_GLASS, 100)]
  , irarity  = [(1, 6), (10, 10)]
  , ieffects = [ RefillHP 10
               , DropItem maxBound maxBound COrgan CONDITION
               , OnSmash (Explode S_HEALING_MIST_2) ]
  }
potion5 :: ItemKind
potion5 = ItemKind
potionTemplate
  { iname    = "ampoule"  -- probably filled with nitroglycerine, but let's
                          -- not mix fantasy with too much technical jargon
  , ifreq    = [(COMMON_ITEM, 100), (ANY_POTION, 100), (ANY_GLASS, 100)]
  , icount   = 3 `dL` 1
  , ieffects = [ DropItem 1 maxBound COrgan CONDITION
               , OnSmash (Explode 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    = [(COMMON_ITEM, 100), (ANY_POTION, 100), (ANY_GLASS, 100)]
  , icount   = 3 `dL` 1  -- always as many as possible on this level
                         -- without giving away potion identity
  , irarity  = [(1, 12)]
  , ieffects = [ OneOf [ RefillHP 10, RefillHP 5, Burn 5
                       , DropItem 1 maxBound COrgan S_POISONED
                       , toOrganGood S_STRENGTHENED (20 + 1 `d` 5) ]
               , OnSmash (OneOf [ Explode S_DENSE_SHOWER
                                , Explode S_SPARSE_SHOWER
                                , Explode S_MELEE_PROTECTIVE_BALM
                                , Explode S_RANGE_PROTECTIVE_BALM
                                , Explode S_DEFENSELESSNESS_RUNOUT ]) ]
  }
potion7 :: ItemKind
potion7 = ItemKind
potionTemplate
  -- needs to be common to show at least a portion of effects
  { ifreq    = [(COMMON_ITEM, 100), (ANY_POTION, 100), (ANY_GLASS, 100)]
  , icount   = 3 `dL` 1
  , irarity  = [(10, 10)]
  , ieffects = [ Impress
               , OneOf [ RefillHP 20, RefillHP 10, Burn 10
                       , DropItem 1 maxBound COrgan S_POISONED
                       , toOrganGood S_HASTED (20 + 1 `d` 5)
                       , toOrganBad S_IMPATIENT (2 + 1 `d` 2) ]
               , OnSmash (OneOf [ Explode S_HEALING_MIST_2
                                , Explode S_WOUNDING_MIST
                                , Explode S_DISTRESSING_ODOR
                                , Explode $ blastNoStatOf S_IMPATIENT
                                , Explode S_HASTE_SPRAY
                                , Explode S_VIOLENT_SLOWNESS_MIST
                                , Explode S_FRAGRANCE
                                , Explode S_VIOLENT_FLASH ]) ]
  }
potion8 :: ItemKind
potion8 = ItemKind
potionTemplate
  { iname    = "the Potion"
  , ifreq    = [(TREASURE, 100), (ANY_GLASS, 100)]
  , icount   = 1
  , irarity  = [(10, 5)]
  , iaspects = [SetFlag Unique, ELabel "of Love", SetFlag MetaGame]
               ++ iaspects potionTemplate
  , ieffects = [ RefillHP 60, RefillCalm (-60)
               , toOrganGood S_ROSE_SMELLING (80 + 1 `d` 20)
               , OnSmash (Explode S_HEALING_MIST_2)
               , OnSmash (Explode S_DISTRESSING_ODOR) ]
  , idesc    = "Perplexing swirls of intense, compelling colour."
  }
potion9 :: ItemKind
potion9 = ItemKind
potionTemplate
  { ifreq    = [(COMMON_ITEM, 100), (ANY_POTION, 100), (ANY_GLASS, 100)]
  , irarity  = [(10, 5)]
  , iaspects = ELabel "of grenadier focus"
               : iaspects potionTemplate
  , ieffects = [ toOrganGood S_MORE_PROJECTING (40 + 1 `d` 10)
               , toOrganBad S_PACIFIED (5 + 1 `d` 3)
                   -- the malus has to be weak, or would be too good
                   -- when thrown at foes
               , OnSmash (Explode $ blastBonusStatOf S_MORE_PROJECTING)
               , OnSmash (Explode $ blastNoStatOf S_PACIFIED) ]
  , idesc    = "Thick, sluggish fluid with violently-bursting bubbles."
  }
potion10 :: ItemKind
potion10 = ItemKind
potionTemplate
  { ifreq    = [(COMMON_ITEM, 100), (ANY_POTION, 100), (ANY_GLASS, 100)]
  , irarity  = [(10, 8)]
  , iaspects = ELabel "of frenzy"
               : iaspects potionTemplate
  , ieffects = [ Yell
               , toOrganGood S_STRENGTHENED (20 + 1 `d` 5)
               , toOrganBad S_RETAINING (5 + 1 `d` 3)
               , toOrganBad S_FRENZIED (40 + 1 `d` 10)
               , OnSmash (Explode S_DENSE_SHOWER)
               , OnSmash (Explode $ blastNoStatOf S_RETAINING)    -- more
               , OnSmash (Explode $ blastNoStatOf S_RETAINING) ]  -- explosion
  }
potion11 :: ItemKind
potion11 = ItemKind
potionTemplate
  { ifreq    = [(COMMON_ITEM, 100), (ANY_POTION, 100), (ANY_GLASS, 100)]
  , irarity  = [(10, 8)]
  , iaspects = ELabel "of panic"
               : iaspects potionTemplate
  , ieffects = [ RefillCalm (-30)
               , toOrganGood S_HASTED (20 + 1 `d` 5)
               , toOrganBad S_WEAKENED (20 + 1 `d` 5)
               , toOrganBad S_WITHHOLDING (10 + 1 `d` 5)
               , OnSmash (Explode S_HASTE_SPRAY)
               , OnSmash (Explode S_SPARSE_SHOWER)
               , OnSmash (Explode $ blastNoStatOf S_WITHHOLDING) ]
  }
potion12 :: ItemKind
potion12 = ItemKind
potionTemplate
  { ifreq    = [(COMMON_ITEM, 100), (ANY_POTION, 100), (ANY_GLASS, 100)]
  , irarity  = [(10, 8)]
  , iaspects = ELabel "of quicksilver"
               : iaspects potionTemplate
  , ieffects = [ toOrganGood S_HASTED (20 + 1 `d` 5)
               , toOrganBad S_BLIND (10 + 1 `d` 5)
               , toOrganBad S_IMMOBILE (5 + 1 `d` 5)
               , OnSmash (Explode S_HASTE_SPRAY)
               , OnSmash (Explode S_IRON_FILING)
               , OnSmash (Explode $ blastNoStatOf S_IMMOBILE) ]
  }
potion13 :: ItemKind
potion13 = ItemKind
potionTemplate
  { ifreq    = [(COMMON_ITEM, 100), (ANY_POTION, 100), (ANY_GLASS, 100)]
  , irarity  = [(10, 4)]
  , iaspects = ELabel "of slow resistance"
               : iaspects potionTemplate
  , ieffects = [ toOrganNoTimer S_SLOW_RESISTANT
               , OnSmash (Explode S_ANTI_SLOW_MIST) ]
  }
potion14 :: ItemKind
potion14 = ItemKind
potionTemplate
  { ifreq    = [(COMMON_ITEM, 100), (ANY_POTION, 100), (ANY_GLASS, 100)]
  , irarity  = [(10, 4)]
  , iaspects = ELabel "of poison resistance"
               : iaspects potionTemplate
  , ieffects = [ toOrganNoTimer S_POISON_RESISTANT
               , OnSmash (Explode S_ANTIDOTE_MIST) ]
  }
-- The player has full control over throwing the potion 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    = [(COMMON_ITEM, 100), (ANY_POTION, 100), (ANY_GLASS, 100)]
  , irarity  = [(1, 2), (10, 12)]
  , iaspects = ELabel "of regeneration"
               : iaspects potionTemplate
  , ieffects = [ toOrganGood S_ROSE_SMELLING (80 + 1 `d` 20)
               , toOrganNoTimer S_REGENERATING
               , toOrganNoTimer S_REGENERATING  -- x2
               , OnSmash (Explode 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 = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolScroll
  , iname :: Text
iname    = Text
"scroll"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
SCROLL_UNKNOWN, Int
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   = Int
1 Int -> Int -> Dice
`dL` Int
3
  , irarity :: Rarity
irarity  = [(Double
1, Int
14), (Double
10, Int
7)]
  , iverbHit :: Text
iverbHit = Text
"thump"
  , iweight :: Int
iweight  = Int
50
  , idamage :: Dice
idamage  = Dice
0
  , iaspects :: [Aspect]
iaspects = [ GroupName ItemKind -> Aspect
PresentAs GroupName ItemKind
SCROLL_UNKNOWN
               , Int -> Aspect
toVelocity Int
30 ]  -- bad shape, even rolled up
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = Text
"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    = "the Scroll"
  , ifreq    = [(TREASURE, 100), (ANY_SCROLL, 100)]
  , icount   = 1
  , irarity  = [(5, 9), (10, 9)]  -- mixed blessing, so found early for a unique
  , iaspects = [SetFlag Unique, ELabel "of Reckless Beacon"]
               ++ iaspects scrollTemplate
  , ieffects = [Summon HERO 1, Summon MOBILE_ANIMAL (2 + 1 `d` 2)]
  , 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    = [(COMMON_ITEM, 100), (ANY_SCROLL, 100)]
  , irarity  = [(1, 6), (10, 2)]
  , ieffects = [Ascend False]
  }
scroll3 :: ItemKind
scroll3 = ItemKind
scrollTemplate
  -- needs to be common to show at least a portion of effects
  { ifreq    = [(COMMON_ITEM, 100), (ANY_SCROLL, 100)]
  , icount   = 3 `dL` 1
  , irarity  = [(1, 14)]
  , ieffects = [OneOf [ Teleport 5, Paralyze 10, InsertMove 30
                      , Detect DetectEmbed 12, Detect DetectHidden 20 ]]
  }
scroll4 :: ItemKind
scroll4 = ItemKind
scrollTemplate
  -- needs to be common to show at least a portion of effects
  { ifreq    = [(COMMON_ITEM, 100), (ANY_SCROLL, 100)]
  , icount   = 3 `dL` 1
  , irarity  = [(10, 14)]
  , ieffects = [ Impress
               , OneOf [ Teleport 20, Ascend False, Ascend True
                       , OneOf [Summon HERO 1, Summon MOBILE_ANIMAL $ 1 `d` 2]
                           -- gaining a hero particularly uncommon
                       , Detect DetectLoot 20  -- the most useful of detections
                       , CreateItem Nothing CGround COMMON_ITEM timerNone ] ]
  }
scroll5 :: ItemKind
scroll5 = ItemKind
scrollTemplate
  { ifreq    = [(COMMON_ITEM, 100), (ANY_SCROLL, 100)]
  , irarity  = [(1, 6)]  -- powerful, but low counts at the depths it appears on
  , ieffects = [InsertMove $ 20 + 1 `dL` 20]
  }
scroll6 :: ItemKind
scroll6 = ItemKind
scrollTemplate
  { ifreq    = [(COMMON_ITEM, 100), (ANY_SCROLL, 100)]
  , irarity  = [(10, 11)]
  , ieffects = [PullActor (ThrowMod 800 75 1)]  -- 6 steps, 1.5 turns
  }
scroll7 :: ItemKind
scroll7 = ItemKind
scrollTemplate
  { iname    = "the Scroll"
  , ifreq    = [(TREASURE, 100), (ANY_SCROLL, 100)]
  , icount   = 1
  , irarity  = [(10, 12)]
  , iaspects = [SetFlag Unique, ELabel "of Rescue Proclamation"]
               ++ iaspects scrollTemplate
  , ieffects = [Summon HERO 1]
  , 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    = [(COMMON_ITEM, 100), (ANY_SCROLL, 100)]
  , irarity  = [(10, 4)]  -- powerful, even if not ideal; scares newbies
  , ieffects = [Detect DetectAll 20]
  }
scroll9 :: ItemKind
scroll9 = ItemKind
scrollTemplate
  { ifreq    = [(COMMON_ITEM, 100), (ANY_SCROLL, 100)]
  , iaspects = ELabel "of cue interpretation"
               : iaspects scrollTemplate
  , ieffects = [Detect DetectActor 20]
  }
scroll10 :: ItemKind
scroll10 = ItemKind
scrollTemplate
  { ifreq    = [(COMMON_ITEM, 100), (ANY_SCROLL, 100)]
  , icount   = 3 `dL` 1
  , irarity  = [(1, 20)]  -- uncommon deep down, where all is known
  , iaspects = ELabel "of scientific explanation"
               : iaspects scrollTemplate
  , ieffects = [Identify `AndEffect` RefillCalm 10]
  , idesc    = "The most pressing existential concerns are met with a deeply satisfying scientific answer."
  }
scroll11 :: ItemKind
scroll11 = ItemKind
scrollTemplate
  { ifreq    = [(COMMON_ITEM, 100), (ANY_SCROLL, 100)]
  , irarity  = [(10, 20)]  -- at gameover a crucial item may be missing
  , iaspects = ELabel "of transmutation"
               : iaspects scrollTemplate
  , ieffects = [PolyItem `AndEffect` Explode S_FIRECRACKER]
  }
scroll12 :: ItemKind
scroll12 = ItemKind
scrollTemplate
  { ifreq    = [(COMMON_ITEM, 100), (ANY_SCROLL, 100)]
  , irarity  = [(10, 15)]
  , iaspects = ELabel "of transfiguration"
               : iaspects scrollTemplate
  , ieffects = [RerollItem]
  }
scroll13 :: ItemKind
scroll13 = ItemKind
scrollTemplate
  { ifreq    = [(COMMON_ITEM, 100), (ANY_SCROLL, 100)]
  , irarity  = [(10, 15)]
  , iaspects = ELabel "of similarity"
               : iaspects scrollTemplate
  , ieffects = [DupItem]
  }

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

ediblePlantTemplate :: ItemKind
ediblePlantTemplate = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolFood
  , iname :: Text
iname    = Text
"edible plant"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
EDIBLE_PLANT_UNKNOWN, Int
1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color]
stdCol
  , icount :: Dice
icount   = Int
1 Int -> Int -> Dice
`dL` Int
5
  , irarity :: Rarity
irarity  = [(Double
1, Int
12), (Double
10, Int
6)]  -- let's feed the animals
  , iverbHit :: Text
iverbHit = Text
"thump"
  , iweight :: Int
iweight  = Int
50
  , idamage :: Dice
idamage  = Dice
0
  , iaspects :: [Aspect]
iaspects = [ GroupName ItemKind -> Aspect
PresentAs GroupName ItemKind
EDIBLE_PLANT_UNKNOWN
               , Int -> Aspect
toVelocity Int
30 ]  -- low density, often falling apart
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = Text
"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    = "overripe berry"
  , ifreq    = [(COMMON_ITEM, 100), (EDIBLE_PLANT, 100)]
  , ieffects = [RefillHP 1, toOrganBad S_IMMOBILE (5 + 1 `d` 5)]
  }
ediblePlant2 :: ItemKind
ediblePlant2 = ItemKind
ediblePlantTemplate
  { iname    = "frayed fungus"
  , ifreq    = [(COMMON_ITEM, 100), (EDIBLE_PLANT, 100)]
  , ieffects = [toOrganNoTimer S_POISONED]
  }
ediblePlant3 :: ItemKind
ediblePlant3 = ItemKind
ediblePlantTemplate
  { iname    = "thick leaf"
  , ifreq    = [(COMMON_ITEM, 100), (EDIBLE_PLANT, 100)]
  , ieffects = [DropItem 1 maxBound COrgan S_POISONED]
  }
ediblePlant4 :: ItemKind
ediblePlant4 = ItemKind
ediblePlantTemplate
  { iname    = "shrunk fruit"
  , ifreq    = [(COMMON_ITEM, 100), (EDIBLE_PLANT, 100)]
  , ieffects = [toOrganBad S_BLIND (10 + 1 `d` 10)]
  }
ediblePlant5 :: ItemKind
ediblePlant5 = ItemKind
ediblePlantTemplate
  { iname    = "fragrant herb"
  , ifreq    = [(COMMON_ITEM, 100), (EDIBLE_PLANT, 100)]
  , icount   = 1 `dL` 9
  , irarity  = [(1, 12), (10, 5)]
  , iaspects = ELabel "of lethargy"
               : iaspects ediblePlantTemplate
  , ieffects = [ toOrganBad S_SLOWED (20 + 1 `d` 5)
               , toOrganNoTimer S_REGENERATING
               , toOrganNoTimer S_REGENERATING  -- x2
               , RefillCalm 5 ]
  }
ediblePlant6 :: ItemKind
ediblePlant6 = ItemKind
ediblePlantTemplate
  { iname    = "dull flower"
  , ifreq    = [(COMMON_ITEM, 100), (EDIBLE_PLANT, 100)]
  , ieffects = [PutToSleep]
  }
ediblePlant7 :: ItemKind
ediblePlant7 = ItemKind
ediblePlantTemplate
  { iname    = "spicy bark"
  , ifreq    = [(COMMON_ITEM, 100), (EDIBLE_PLANT, 100)]
  , ieffects = [InsertMove 20, toOrganBad S_FRENZIED (40 + 1 `d` 10)]
  }

-- ** Lights

light1 :: ItemKind
light1 = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolLight
  , iname :: Text
iname    = Text
"wooden torch"
  , ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
COMMON_ITEM, Int
100), (GroupName ItemKind
LIGHT_ATTENUATOR, Int
100)
               , (GroupName ItemKind
S_WOODEN_TORCH, Int
1) ]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Brown]
  , icount :: Dice
icount   = Int
1 Int -> Int -> Dice
`dL` Int
4
  , irarity :: Rarity
irarity  = [(Double
1, Int
40), (Double
4, Int
1)]
  , iverbHit :: Text
iverbHit = Text
"scorch"
  , iweight :: Int
iweight  = Int
1000
  , idamage :: Dice
idamage  = Dice
0
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkShine Dice
3  -- no malus, to lessen micromanagement
               , 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 Dice
1]
  , idesc :: Text
idesc    = Text
"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 = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolLight
  , iname :: Text
iname    = Text
"oil lamp"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, Int
100), (GroupName ItemKind
LIGHT_ATTENUATOR, Int
100)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrYellow]
  , icount :: Dice
icount   = Int
1 Int -> Int -> Dice
`dL` Int
2
  , irarity :: Rarity
irarity  = [(Double
4, Int
10)]
  , iverbHit :: Text
iverbHit = Text
"burn"
  , iweight :: Int
iweight  = Int
1500
  , idamage :: Dice
idamage  = Int
1 Int -> Int -> Dice
`d` Int
1
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkShine Dice
3
               , Flag -> Aspect
SetFlag Flag
Lobable, Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Equipable
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotShine ]
  , ieffects :: [Effect]
ieffects = [ GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_FOCUSED_BURNING_OIL_2
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_VIOLENT_BURNING_OIL_2) ]
  , idesc :: Text
idesc    = Text
"A small clay lamp filled with plant oil feeding a tiny wick."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
light3 :: ItemKind
light3 = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolLight
  , iname :: Text
iname    = Text
"brass lantern"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, Int
100), (GroupName ItemKind
LIGHT_ATTENUATOR, Int
100)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Red]
  , icount :: Dice
icount   = Dice
1
  , irarity :: Rarity
irarity  = [(Double
10, Int
6)]
  , iverbHit :: Text
iverbHit = Text
"burn"
  , iweight :: Int
iweight  = Int
3000
  , idamage :: Dice
idamage  = Int
2 Int -> Int -> Dice
`d` Int
1
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkShine Dice
4
               , Flag -> Aspect
SetFlag Flag
Lobable, Flag -> Aspect
SetFlag Flag
Fragile, Flag -> Aspect
SetFlag Flag
Equipable
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotShine ]
  , ieffects :: [Effect]
ieffects = [ GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_FOCUSED_BURNING_OIL_4
               , Effect -> Effect
OnSmash (GroupName ItemKind -> Effect
Explode GroupName ItemKind
S_VIOLENT_BURNING_OIL_4) ]
  , idesc :: Text
idesc    = Text
"Very bright and very heavy brass lantern."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
blanket :: ItemKind
blanket = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolLight
  , iname :: Text
iname    = Text
"wool blanket"
  , ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
COMMON_ITEM, Int
100), (GroupName ItemKind
LIGHT_ATTENUATOR, Int
100)
               , (GroupName ItemKind
FIREPROOF_CLOTH, Int
1) ]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrBlack]
  , icount :: Dice
icount   = Dice
1
  , irarity :: Rarity
irarity  = [(Double
1, Int
1)]  -- not every playthrough needs one
  , iverbHit :: Text
iverbHit = Text
"swoosh"
  , iweight :: Int
iweight  = Int
1000
  , idamage :: Dice
idamage  = Dice
0
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkShine (-Dice
10)
               , Skill -> Dice -> Aspect
AddSkill Skill
SkArmorMelee Dice
3, Skill -> Dice -> Aspect
AddSkill Skill
SkMaxCalm Dice
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    = Text
"Warm, comforting, and concealing, woven from soft wool."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }

-- ** Periodic jewelry

-- This looks like a necklace, but is not periodic. Instead, it auto-activates
-- when under melee attack.
gorget :: ItemKind
gorget = ItemKind
necklaceTemplate
  { iname    = "Old Gorget"
  , ifreq    = [(COMMON_ITEM, 25), (TREASURE, 25)]
  , iflavour = zipFancy [BrCyan]  -- looks exactly the same as one of necklaces,
                                  -- but it's OK, it's an artifact
  , iaspects = [ SetFlag Unique
               , Timeout $ 7 - 1 `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
               , AddSkill SkArmorMelee 3, AddSkill SkHearing 3
               , SetFlag UnderMelee, SetFlag Durable ]
               ++ delete (SetFlag Periodic) iaspects_necklaceTemplate
  , ieffects = [RefillCalm 15]
  , 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."
  }
-- 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 Int
50 ]  -- not dense enough
-- Not identified, because id by use, e.g., via periodic activations. Fun.
necklaceTemplate :: ItemKind
necklaceTemplate = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolNecklace
  , iname :: Text
iname    = Text
"necklace"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
NECKLACE_UNKNOWN, Int
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   = Dice
1
  , irarity :: Rarity
irarity  = [(Double
4, Int
3), (Double
10, Int
6)]
  , iverbHit :: Text
iverbHit = Text
"whip"
  , iweight :: Int
iweight  = Int
30
  , idamage :: Dice
idamage  = Dice
0
  , iaspects :: [Aspect]
iaspects = Dice -> Aspect
Timeout Dice
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    = Text
"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    = "the Necklace"
  , ifreq    = [(TREASURE, 100), (ANY_JEWELRY, 100)]
  , irarity  = [(10, 3)]
  , iaspects = [ SetFlag Unique, ELabel "of Aromata"
               , Timeout $ (4 - 1 `dL` 3) * 10
                   -- priceless, so worth the long wait and Calm drain
               , SetFlag Durable ]
               ++ iaspects_necklaceTemplate
  , ieffects = [ RefillCalm (-5)
               , When (TriggeredBy ActivationPeriodic) $ RefillHP 1 ]
  , idesc    = "A cord of freshly dried herbs and healing berries."
  }
necklace2 :: ItemKind
necklace2 = ItemKind
necklaceTemplate
  { iname    = "the Necklace"
  , ifreq    = [(TREASURE, 100), (ANY_JEWELRY, 100)]
      -- too nasty to call it just a COMMON_ITEM
  , irarity  = [(10, 3)]
  , iaspects = [ SetFlag Unique, ELabel "of Live Bait"
               , Timeout 30
               , AddSkill SkOdor 2
               , SetFlag Durable ]
               ++ iaspects_necklaceTemplate
  , ieffects = [ DropItem 1 1 COrgan CONDITION  -- mildly useful when applied
               , When (TriggeredBy ActivationPeriodic) $ SeqEffect
                   [ Impress
                   , Summon MOBILE_ANIMAL $ 1 `dL` 2
                   , Explode S_WASTE ] ]
  , idesc    = "A cord hung with lumps of decaying meat. It's better not to think about the source."
  }
necklace3 :: ItemKind
necklace3 = ItemKind
necklaceTemplate
  { ifreq    = [(COMMON_ITEM, 100), (ANY_JEWELRY, 100)]
  , iaspects = [ ELabel "of fearful listening"
               , Timeout 40
                   -- has to be larger than Calm drain or item not removable;
                   -- equal is not enough if enemies drained Calm already
               , AddSkill SkHearing 6 ]
               ++ iaspects_necklaceTemplate
  , ieffects = [ Detect DetectActor 20  -- can be applied; destroys the item
               , When (TriggeredBy ActivationPeriodic) $ RefillCalm (-30) ]
  }
necklace4 :: ItemKind
necklace4 = ItemKind
necklaceTemplate
  { ifreq    = [(COMMON_ITEM, 100), (ANY_JEWELRY, 100)]
  , iaspects = [ ELabel "of escape"
               , Timeout $ (7 - 1 `dL` 5) * 10 ]
               ++ iaspects_necklaceTemplate
  , ieffects = [ Teleport $ 14 + 3 `d` 3  -- can be applied; destroys the item
               , Detect DetectExit 20
               , Yell ]  -- drawback when used for quick exploring
  , idesc    = "A supple chain that slips through your fingers."
  }
necklace5 :: ItemKind
necklace5 = ItemKind
necklaceTemplate
  { ifreq    = [(COMMON_ITEM, 100), (ANY_JEWELRY, 100)]
  , iaspects = [ ELabel "of greed"
               , Timeout ((2 + 1 `d` 3) * 10) ]
               ++ iaspects_necklaceTemplate
  , ieffects = [ Detect DetectLoot 20
               , toOrganBad S_PARSIMONIOUS (5 + 1 `d` 3)  -- hard to flee
               , When (TriggeredBy ActivationPeriodic) $ Teleport 40 ]  -- risky
  }
necklace6 :: ItemKind
necklace6 = ItemKind
necklaceTemplate
  { ifreq    = [(COMMON_ITEM, 100), (ANY_JEWELRY, 100)]
  , iaspects = Timeout ((3 + 1 `d` 3 - 1 `dL` 3) * 2)
               : iaspects_necklaceTemplate  -- OP if Durable; free blink
  , ieffects = [Teleport $ 3 `d` 2]
  }
necklace7 :: ItemKind
necklace7 = ItemKind
necklaceTemplate
  { ifreq    = [(COMMON_ITEM, 100), (ANY_JEWELRY, 100)]
  , iaspects = Timeout ((1 `d` 3) * 2)
               : iaspects_necklaceTemplate
  , ieffects = [PushActor (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    = "the Necklace"
  , ifreq    = [(TREASURE, 100), (ANY_JEWELRY, 100)]
  , irarity  = [(10, 1)]  -- different gameplay for the actor that wears it
  , iaspects = [ SetFlag Unique, ELabel "of Overdrive"
               , Timeout 4
               , AddSkill SkMaxHP 25  -- give incentive to cope with impatience
               , SetFlag Durable ]
               ++ iaspects_necklaceTemplate
  , ieffects = [ InsertMove $ 9 + 1 `d` 11  -- unpredictable
               , toOrganBad S_IMPATIENT 4]
                 -- The same duration as timeout, to avoid spurious messages
                 -- as well as unlimited accumulation of the duration.
  , idesc    = "A string of beads in various colours, with no discernable pattern."
  }
necklace9 :: ItemKind
necklace9 = ItemKind
necklaceTemplate
  { ifreq    = [(COMMON_ITEM, 100), (ANY_JEWELRY, 100)]
  , irarity  = [(4, 3)]  -- entirely optional
  , iaspects = Timeout ((1 + 1 `d` 3) * 5)  -- low timeout for offensive use
               : iaspects_necklaceTemplate
  , ieffects = [Explode S_SPARK]
  }
necklace10 :: ItemKind
necklace10 = ItemKind
necklaceTemplate
  { ifreq    = [(COMMON_ITEM, 100), (ANY_JEWELRY, 100)]
  , iaspects = Timeout ((3 + 1 `d` 3) * 10)
               : iaspects_necklaceTemplate
                   -- high timeout to prevent spam obscuring messages
                   -- when other actors act and annoying bumping into
                   -- projectiles caused by own necklace when walking
  , ieffects = [Explode S_FRAGRANCE]
  }
motionScanner :: ItemKind
motionScanner = ItemKind
necklaceTemplate
  { iname    = "draft detector"
  , ifreq    = [(COMMON_ITEM, 100), (ADD_NOCTO_1, 20)]
  , irarity  = [(5, 2)]
  , iverbHit = "jingle"
  , iweight  = 300  -- almost gives it away
  , iaspects = [ Timeout $ 4 + 1 `dL` 6
                   -- positive dL dice, since the periodic effect is detrimental
               , AddSkill SkNocto 1
               , AddSkill SkArmorMelee $ (-4 + 1 `dL` 3) * 5
               , EqpSlot EqpSlotMiscBonus ]
               ++ iaspects_necklaceTemplate
  , ieffects = [Explode S_PING_PLASH]
  , 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 = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolRing
  , iname :: Text
iname    = Text
"light cone"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
TREASURE, Int
100), (GroupName ItemKind
ADD_NOCTO_1, Int
80)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color
BrYellow]
  , icount :: Dice
icount   = Dice
1
  , irarity :: Rarity
irarity  = [(Double
5, Int
2)]
  , iverbHit :: Text
iverbHit = Text
"bang"
  , iweight :: Int
iweight  = Int
500
  , idamage :: Dice
idamage  = Dice
0
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkNocto Dice
1
               , Skill -> Dice -> Aspect
AddSkill Skill
SkArmorMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (-Dice
6 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Dice
`dL` Int
3) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* Dice
5
               , Flag -> Aspect
SetFlag Flag
Precious, Flag -> Aspect
SetFlag Flag
Equipable
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotMiscBonus ]
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = Text
"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    = "sharp monocle"
  , ifreq    = [(TREASURE, 20), (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  = [(7, 1), (10, 12)]  -- low @ifreq@
  , iweight  = 50  -- heavier that it looks, due to glass
  , iaspects = [ AddSkill SkSight $ 1 + 1 `dL` 2
               , AddSkill SkHurtMelee $ (1 `d` 3) * 3
               , EqpSlot EqpSlotSight ]
               ++ iaspects ringTemplate
  , 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 = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolRing
  , iname :: Text
iname    = Text
"ring"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
RING_UNKNOWN, Int
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   = Dice
1
  , irarity :: Rarity
irarity  = [(Double
10, Int
2)]  -- the default very low
  , iverbHit :: Text
iverbHit = Text
"knock"
  , iweight :: Int
iweight  = Int
15
  , idamage :: Dice
idamage  = Dice
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    = Text
"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    = [(COMMON_ITEM, 100), (ANY_JEWELRY, 100)]
  , irarity  = [(8, 4)]
  , iaspects = [ AddSkill SkSpeed $ 1 `dL` 2
               , AddSkill SkMaxHP (-20)
               , EqpSlot EqpSlotSpeed ]
               ++ iaspects ringTemplate
  }
ring2 :: ItemKind
ring2 = ItemKind
ringTemplate
  { ifreq    = [(COMMON_ITEM, 100), (ANY_JEWELRY, 100)]
  , irarity  = [(8, 4)]
  , iaspects = [ AddSkill SkSpeed $ 1 + 1 `dL` 3
               , AddSkill SkArmorMelee (-40)
               , EqpSlot EqpSlotSpeed ]
               ++ iaspects ringTemplate
  }
ring3 :: ItemKind
ring3 = ItemKind
ringTemplate
  { iname    = "the Ring"
  , ifreq    = [(TREASURE, 100), (ANY_JEWELRY, 100)]
  , iaspects = [ SetFlag Unique, ELabel "of Rush"
               , AddSkill SkSpeed $ (1 + 1 `dL` 2) * 2
               , AddSkill SkMaxHP (-20)
               , AddSkill SkArmorMelee (-20)
               , SetFlag Durable, EqpSlot EqpSlotSpeed ]
               ++ iaspects ringTemplate
  , idesc    = "Roughly-shaped metal with shallow scratches marking it."
  }
ring4 :: ItemKind
ring4 = ItemKind
ringTemplate
  { ifreq    = [(COMMON_ITEM, 100), (ANY_JEWELRY, 100)]
  , irarity  = [(3, 4), (10, 8)]
  , iaspects = [ AddSkill SkHurtMelee $ (2 + 1 `d` 3 + (1 `dL` 2) * 2 ) * 3
               , AddSkill SkMaxHP (-10)
               , EqpSlot EqpSlotHurtMelee ]
               ++ iaspects ringTemplate
  }
ring5 :: ItemKind
ring5 = ItemKind
ringTemplate
  { ifreq    = [(COMMON_ITEM, 100), (ANY_JEWELRY, 100)]
  , iaspects = [ AddSkill SkHurtMelee $ (4 + 1 `d` 3 + (1 `dL` 2) * 2 ) * 3
               , AddSkill SkArmorMelee (-20)
               , EqpSlot EqpSlotHurtMelee ]
               ++ iaspects ringTemplate
  }
ring6 :: ItemKind
ring6 = ItemKind
ringTemplate
  { ifreq    = [(COMMON_ITEM, 100), (ANY_JEWELRY, 100)]
  , irarity  = [(10, 8)]
  , iaspects = [ AddSkill SkMaxHP $ 5 + (1 `d` 2 + 1 `dL` 2) * 5
               , AddSkill SkMaxCalm $ -30 + (1 `dL` 3) * 5
               , EqpSlot EqpSlotMaxHP ]
               ++ iaspects ringTemplate
  }
ring7 :: ItemKind
ring7 = ItemKind
ringTemplate
  { ifreq    = [(COMMON_ITEM, 100), (ANY_JEWELRY, 100)]
  , irarity  = [(5, 1), (10, 9)]  -- needed after other items drop Calm
  , iaspects = [ AddSkill SkMaxCalm $ 30 + (1 `dL` 4) * 5
               , AddSkill SkHearing 6
               , EqpSlot EqpSlotMiscBonus ]
               ++ iaspects ringTemplate
  , idesc    = "Cold, solid to the touch, perfectly round, engraved with solemn, strangely comforting, worn out words."
  }
ring8 :: ItemKind
ring8 = ItemKind
ringTemplate  -- weak skill per eqp slot, so can be without drawbacks
  { ifreq    = [(COMMON_ITEM, 100), (ANY_JEWELRY, 100)]
  , irarity  = [(10, 3)]
  , iaspects = [ AddSkill SkShine 1
               , EqpSlot EqpSlotShine ]
               ++ iaspects ringTemplate
  , idesc    = "A sturdy ring with a large, shining stone."
  }
ring9 :: ItemKind
ring9 = ItemKind
ringTemplate
  { ifreq    = [(RING_OF_OPPORTUNITY_SNIPER, 1) ]  -- only for scenarios
  , irarity  = [(1, 1)]
  , iaspects = [ ELabel "of opportunity sniper"
               , AddSkill SkProject 8
               , EqpSlot EqpSlotProject ]
               ++ iaspects ringTemplate
  }
ring10 :: ItemKind
ring10 = ItemKind
ringTemplate
  { ifreq    = [(RING_OF_OPPORTUNITY_GRENADIER, 1) ]  -- only for scenarios
  , irarity  = [(1, 1)]
  , iaspects = [ ELabel "of opportunity grenadier"
               , AddSkill SkProject 11
               , EqpSlot EqpSlotProject ]
               ++ iaspects ringTemplate
  }

-- ** Armor

armorLeather :: ItemKind
armorLeather = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolTorsoArmor
  , iname :: Text
iname    = Text
"leather armor"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, Int
100), (GroupName ItemKind
ARMOR_LOOSE, Int
1), (GroupName ItemKind
STARTING_ARMOR, Int
100)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Brown]
  , icount :: Dice
icount   = Dice
1
  , irarity :: Rarity
irarity  = [(Double
1, Int
9), (Double
10, Int
2)]
  , iverbHit :: Text
iverbHit = Text
"thud"
  , iweight :: Int
iweight  = Int
7000
  , idamage :: Dice
idamage  = Dice
0
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (-Dice
2)
               , Skill -> Dice -> Aspect
AddSkill Skill
SkArmorMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (Dice
2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Dice
`dL` Int
4) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* Dice
5
               , Skill -> Dice -> Aspect
AddSkill Skill
SkArmorRanged (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (Dice
1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Dice
`dL` Int
2) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* Dice
3
               , Flag -> Aspect
SetFlag Flag
Durable, Flag -> Aspect
SetFlag Flag
Equipable
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotArmorMelee ]
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = Text
"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    = "ring armor"
  , ifreq    = [ (COMMON_ITEM, 100), (ARMOR_LOOSE, 1), (ARMOR_RANGED, 50)
               , (STARTING_ARMOR, 50) ]
  , iflavour = zipPlain [Cyan]
  , irarity  = [(6, 9), (10, 3)]
  , iweight  = 12000
  , idamage  = 0
  , iaspects = [ AddSkill SkHurtMelee (-3)
               , AddSkill SkArmorMelee $ (2 + 1 `dL` 4) * 5
               , AddSkill SkArmorRanged $ (4 + 1 `dL` 2) * 3
               , AddSkill SkOdor 2
               , SetFlag Durable, SetFlag Equipable
               , EqpSlot EqpSlotArmorRanged ]
  , ieffects = []
  , 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 = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolTool
  , iname :: Text
iname    = Text
"whetstone"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, Int
100)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Blue]
  , icount :: Dice
icount   = Dice
1
  , irarity :: Rarity
irarity  = [(Double
10, Int
10)]
  , iverbHit :: Text
iverbHit = Text
"smack"
  , iweight :: Int
iweight  = Int
400
  , idamage :: Dice
idamage  = Dice
0
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (Int
1 Int -> Int -> Dice
`dL` Int
7) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* Dice
5
               , Skill -> Dice -> Aspect
AddSkill Skill
SkArmorMelee Dice
2
               , Flag -> Aspect
SetFlag Flag
Equipable, EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotHurtMelee ]
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = Text
"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 = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolMiscArmor
  , iname :: Text
iname    = Text
"leather glove"
  , ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
COMMON_ITEM, Int
100), (GroupName ItemKind
ARMOR_MISC, Int
1), (GroupName ItemKind
ARMOR_RANGED, Int
50)
               , (GroupName ItemKind
STARTING_ARMOR, Int
50) ]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
White]
  , icount :: Dice
icount   = Dice
1
  , irarity :: Rarity
irarity  = [(Double
5, Int
9), (Double
10, Int
9)]
  , iverbHit :: Text
iverbHit = Text
"flap"
  , iweight :: Int
iweight  = Int
100
  , idamage :: Dice
idamage  = Int
1 Int -> Int -> Dice
`d` Int
1
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (Dice
2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Dice
`d` Int
2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Dice
`dL` Int
2) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* Dice
3
               , Skill -> Dice -> Aspect
AddSkill Skill
SkArmorRanged (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (Int
1 Int -> Int -> Dice
`dL` Int
2) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* Dice
3
               , Flag -> Aspect
SetFlag Flag
Durable, Flag -> Aspect
SetFlag Flag
Equipable
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotHurtMelee
               , Int -> Aspect
toVelocity Int
50 ]  -- flaps and flutters
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = Text
"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    = "steel gauntlet"
  , ifreq    = [(COMMON_ITEM, 100), (ARMOR_MISC, 1), (STARTING_ARMOR, 50)]
  , iflavour = zipPlain [BrCyan]
  , irarity  = [(1, 9), (10, 3)]
  , iverbHit = "mow"
  , iweight  = 300
  , idamage  = 2 `d` 1
  , iaspects = [ AddSkill SkArmorMelee $ (1 + 1 `dL` 4) * 5
               , SetFlag Durable, SetFlag Equipable
               , EqpSlot EqpSlotArmorMelee
               , toVelocity 50 ]  -- flaps and flutters
  , idesc    = "Long leather gauntlet covered in overlapping steel plates."
  }
gloveJousting :: ItemKind
gloveJousting = ItemKind
gloveFencing
  { iname    = "Tournament Gauntlet"
  , ifreq    = [(COMMON_ITEM, 100), (ARMOR_MISC, 1)]
  , iflavour = zipFancy [BrRed]
  , irarity  = [(1, 3), (10, 3)]
  , iverbHit = "ram"
  , iweight  = 3000
  , idamage  = 3 `d` 1
  , iaspects = [ SetFlag Unique
               , AddSkill SkHurtMelee $ (-7 + 1 `dL` 5) * 3
               , AddSkill SkArmorMelee $ (2 + 1 `d` 2 + 1 `dL` 2) * 5
               , AddSkill SkArmorRanged $ (1 + 1 `dL` 2) * 3
                 -- very random on purpose and can even be good on occasion
                 -- or when ItemRerolled enough times
               , SetFlag Durable, SetFlag Equipable
               , EqpSlot EqpSlotArmorMelee
               , toVelocity 50 ]  -- flaps and flutters
  , idesc    = "Rigid, steel jousting handgear. If only you had a lance. And a horse to carry it all."
  }
hatUshanka :: ItemKind
hatUshanka = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolMiscArmor
  , iname :: Text
iname    = Text
"ushanka hat"
  , ifreq :: Freqs ItemKind
ifreq    = [ (GroupName ItemKind
COMMON_ITEM, Int
100), (GroupName ItemKind
ARMOR_MISC, Int
1), (GroupName ItemKind
CLOTHING_MISC, Int
1)
               , (GroupName ItemKind
STARTING_ARMOR, Int
50) ]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Brown]
  , icount :: Dice
icount   = Dice
1
  , irarity :: Rarity
irarity  = [(Double
1, Int
6), (Double
10, Int
1)]
  , iverbHit :: Text
iverbHit = Text
"tickle"
  , iweight :: Int
iweight  = Int
500
  , idamage :: Dice
idamage  = Dice
0
  , iaspects :: [Aspect]
iaspects = [ Dice -> Aspect
Timeout (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (Dice
2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Dice
`d` Int
2) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* Dice
3
               , Skill -> Dice -> Aspect
AddSkill Skill
SkArmorMelee Dice
5, Skill -> Dice -> Aspect
AddSkill Skill
SkHearing (-Dice
6)
               , Flag -> Aspect
SetFlag Flag
Periodic, Flag -> Aspect
SetFlag Flag
Durable, Flag -> Aspect
SetFlag Flag
Equipable
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotArmorMelee
               , Int -> Aspect
toVelocity Int
50 ]  -- flaps and flutters
  , ieffects :: [Effect]
ieffects = [Int -> Effect
RefillCalm Int
1]
  , idesc :: Text
idesc    = Text
"Soft and warm fur. It keeps your ears warm."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
capReinforced :: ItemKind
capReinforced = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolMiscArmor
  , iname :: Text
iname    = Text
"leather cap"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, Int
100), (GroupName ItemKind
ARMOR_MISC, Int
1), (GroupName ItemKind
STARTING_ARMOR, Int
50)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrYellow]
  , icount :: Dice
icount   = Dice
1
  , irarity :: Rarity
irarity  = [(Double
6, Int
9), (Double
10, Int
3)]
  , iverbHit :: Text
iverbHit = Text
"cut"
  , iweight :: Int
iweight  = Int
1000
  , idamage :: Dice
idamage  = Dice
0
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkArmorMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (Int
1 Int -> Int -> Dice
`d` Int
2) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* Dice
5
               , Skill -> Dice -> Aspect
AddSkill Skill
SkProject Dice
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    = Text
"Boiled leather with a wide brim. It might soften a blow."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
helmArmored :: ItemKind
helmArmored = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolMiscArmor
  , iname :: Text
iname    = Text
"bucket helm"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, Int
100), (GroupName ItemKind
ARMOR_MISC, Int
1), (GroupName ItemKind
STARTING_ARMOR, Int
50)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrCyan]
  , icount :: Dice
icount   = Dice
1
  , irarity :: Rarity
irarity  = [(Double
6, Int
9), (Double
10, Int
3)]
  , iverbHit :: Text
iverbHit = Text
"bounce"
  , iweight :: Int
iweight  = Int
2000
  , idamage :: Dice
idamage  = Dice
0
  , iaspects :: [Aspect]
iaspects = [ Skill -> Dice -> Aspect
AddSkill Skill
SkArmorMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (Dice
1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Dice
`dL` Int
4) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* Dice
5
               , Skill -> Dice -> Aspect
AddSkill Skill
SkArmorRanged (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (Dice
2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Dice
`dL` Int
2) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* Dice
3  -- headshot
               , Skill -> Dice -> Aspect
AddSkill Skill
SkSight (-Dice
2)
               , Skill -> Dice -> Aspect
AddSkill Skill
SkHearing (-Dice
3), Skill -> Dice -> Aspect
AddSkill Skill
SkSmell (-Dice
5)
               , Flag -> Aspect
SetFlag Flag
Durable, Flag -> Aspect
SetFlag Flag
Equipable
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotArmorRanged ]
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = Text
"Blocks out everything, including your senses."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
smokingJacket :: ItemKind
smokingJacket = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolClothes
  , iname :: Text
iname    = Text
"smoking jacket"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, Int
100), (GroupName ItemKind
CLOTHING_MISC, Int
1), (GroupName ItemKind
CHIC_GEAR, Int
100)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color
BrGreen]
  , icount :: Dice
icount   = Dice
1
  , irarity :: Rarity
irarity  = [(Double
1, Int
9), (Double
10, Int
3)]
  , iverbHit :: Text
iverbHit = Text
"stroke"
  , iweight :: Int
iweight  = Int
5000
  , idamage :: Dice
idamage  = Dice
0
  , iaspects :: [Aspect]
iaspects = [ Dice -> Aspect
Timeout (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (Int
1 Int -> Int -> Dice
`d` Int
2) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* Dice
3
               , Skill -> Dice -> Aspect
AddSkill Skill
SkSpeed Dice
2
               , Skill -> Dice -> Aspect
AddSkill Skill
SkOdor Dice
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 Int
1]
  , idesc :: Text
idesc    = Text
"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 = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolShield
  , iname :: Text
iname    = Text
"buckler"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, Int
100), (GroupName ItemKind
ARMOR_LOOSE, Int
1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Blue]
  , icount :: Dice
icount   = Dice
1
  , irarity :: Rarity
irarity  = [(Double
4, Int
5)]
  , iverbHit :: Text
iverbHit = Text
"bash"
  , iweight :: Int
iweight  = Int
2000
  , idamage :: Dice
idamage  = Dice
0  -- safe to be used on self
  , iaspects :: [Aspect]
iaspects = [ Dice -> Aspect
Timeout (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (Dice
3 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Dice
`d` Int
3 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
- Int
1 Int -> Int -> Dice
`dL` Int
3) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* Dice
2
               , Skill -> Dice -> Aspect
AddSkill Skill
SkArmorMelee Dice
40
                   -- not enough to compensate; won't be in AI's eqp
               , Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (-Dice
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 Int
200 Int
50 Int
1)]  -- 1 step, fast
  , idesc :: Text
idesc    = Text
"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    = "shield"
  , irarity  = [(8, 4)]  -- the stronger variants add to total probability
  , iflavour = zipPlain [Green]
  , iweight  = 4000
  , idamage  = 4 `d` 1
  , iaspects = [ Timeout $ (3 + 1 `d` 3 - 1 `dL` 3) * 4
               , AddSkill SkArmorMelee 80
                   -- not enough to compensate; won't be in AI's eqp
               , AddSkill SkHurtMelee (-70)
                   -- too harmful; won't be wielded as weapon
               , SetFlag Durable, SetFlag Meleeable
               , EqpSlot EqpSlotArmorMelee
               , toVelocity 50 ]  -- unwieldy to throw
  , ieffects = [PushActor (ThrowMod 400 50 1)]  -- 2 steps, fast
  , 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    = [(COMMON_ITEM, 3 * 3)]  -- very low base rarity
  , iweight  = 5000
  , idamage  = 8 `d` 1
  , idesc    = "A relic of long-past wars, heavy and with a central spike."
  }
shield3 :: ItemKind
shield3 = ItemKind
shield2
  { ifreq    = [(COMMON_ITEM, 1 * 3)]  -- very low base rarity
  , iweight  = 6000
  , idamage  = 12 `d` 1
  }

-- ** Weapons

knife :: ItemKind
knife = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolEdged
  , iname :: Text
iname    = Text
"dagger"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, Int
100), (GroupName ItemKind
STARTING_WEAPON, Int
200)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrCyan]
  , icount :: Dice
icount   = Dice
1
  , irarity :: Rarity
irarity  = [(Double
2, Int
45), (Double
4, Int
1)]
  , iverbHit :: Text
iverbHit = Text
"cut"
  , iweight :: Int
iweight  = Int
800
  , idamage :: Dice
idamage  = Int
6 Int -> Int -> Dice
`d` Int
1
  , iaspects :: [Aspect]
iaspects = [ Dice -> Aspect
Timeout Dice
2
               , Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (-Dice
1 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Dice
`d` Int
2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Dice
`dL` Int
2) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* Dice
3
               , Skill -> Dice -> Aspect
AddSkill Skill
SkArmorMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (Int
1 Int -> Int -> Dice
`d` Int
2) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* Dice
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 Int
40 ]  -- ensuring it hits with the tip costs speed
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = Text
"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     = []
  }
daggerDischarge :: ItemKind
daggerDischarge = ItemKind
knife
  { iname    = "The Double Dagger"
  , ifreq    = [(TREASURE, 20)]
  , irarity  = [(1, 3), (10, 3)]
  , iaspects = SetFlag Unique
               : iaspects knife
  , ieffects = [Discharge 1 50, Yell]  -- powerful and low timeout, but noisy
                                       -- and no effect if no weapons charged
  , idesc    = "A double dagger that a focused fencer can use to catch and twist away an opponent's blade."
  }
hammerTemplate :: ItemKind
hammerTemplate = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolHafted
  , iname :: Text
iname    = Text
"war hammer"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
HAMMER_UNKNOWN, Int
1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color
BrMagenta]  -- avoid "pink"
  , icount :: Dice
icount   = Dice
1
  , irarity :: Rarity
irarity  = [(Double
3, Int
25), (Double
5, Int
1)]
  , iverbHit :: Text
iverbHit = Text
"club"
  , iweight :: Int
iweight  = Int
1600
  , idamage :: Dice
idamage  = Int
8 Int -> Int -> Dice
`d` Int
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 Int
40 ]  -- ensuring it hits with the tip costs speed
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = Text
"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    = [(COMMON_ITEM, 100), (STARTING_WEAPON, 70)]
  , iaspects = [Timeout 5, EqpSlot EqpSlotWeaponBig]
               ++ iaspects hammerTemplate
  }
hammer2 :: ItemKind
hammer2 = ItemKind
hammerTemplate
  { ifreq    = [(COMMON_ITEM, 20), (STARTING_WEAPON, 7)]
  , iverbHit = "gouge"
  , iaspects = [Timeout 3, EqpSlot EqpSlotWeaponFast]
               ++ iaspects hammerTemplate
  , 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    = [(COMMON_ITEM, 3), (STARTING_WEAPON, 1)]
  , iverbHit = "puncture"
  , iweight  = 2400
  , idamage  = 12 `d` 1
  , iaspects = [ Timeout 12  -- balance, or @DupItem@ would break the game
               , SetFlag MetaGame  -- weight gives it away after seen once
               , EqpSlot EqpSlotWeaponBig]
               ++ iaspects hammerTemplate
  , 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    = "The Brute Hammer"
  , ifreq    = [(TREASURE, 20)]
  , irarity  = [(5, 1), (8, 6)]
  , iaspects = [ SetFlag Unique
               , Timeout 5
               , EqpSlot EqpSlotWeaponBig ]
               ++ iaspects hammerTemplate
  , ieffects = [Paralyze 10]
  , 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    = "The Grand Smithhammer"
  , ifreq    = [(TREASURE, 20)]
  , irarity  = [(5, 1), (8, 6)]
  , iweight  = 2400
  , idamage  = 12 `d` 1
  , iaspects = [ SetFlag Unique
               , SetFlag MetaGame  -- weight gives it away after seen once
               , Timeout 10
               , EqpSlot EqpSlotWeaponBig
               , AddSkill SkShine 3]
               ++ iaspects hammerTemplate
  , ieffects = [Explode S_SPARK]
      -- we can't use a focused explosion, because it would harm the hammer
      -- wielder as well, unlike this one
  , idesc    = "Smiths of old wielded this heavy hammer and its sparks christened many a potent blade."
  }
sword :: ItemKind
sword = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolEdged
  , iname :: Text
iname    = Text
"sword"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, Int
100), (GroupName ItemKind
STARTING_WEAPON, Int
30)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrBlue]
  , icount :: Dice
icount   = Dice
1
  , irarity :: Rarity
irarity  = [(Double
4, Int
1), (Double
6, Int
15)]
  , iverbHit :: Text
iverbHit = Text
"slash"
  , iweight :: Int
iweight  = Int
2000
  , idamage :: Dice
idamage  = Int
10 Int -> Int -> Dice
`d` Int
1
  , iaspects :: [Aspect]
iaspects = [ Dice -> Aspect
Timeout Dice
7
               , Flag -> Aspect
SetFlag Flag
Durable, Flag -> Aspect
SetFlag Flag
Meleeable
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotWeaponBig
               , Int -> Aspect
toVelocity Int
40 ]  -- ensuring it hits with the tip costs speed
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = Text
"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    = "The Master's Sword"
  , ifreq    = [(TREASURE, 20)]
  , irarity  = [(5, 1), (8, 6)]
  , iaspects = SetFlag Unique
               : iaspects sword
  , ieffects = [Impress]
  , idesc    = "A particularly well-balance blade, lending itself to impressive shows of fencing skill."
  }
swordNullify :: ItemKind
swordNullify = ItemKind
sword
  { iname    = "The Gutting Sword"
  , ifreq    = [(TREASURE, 20)]
  , iverbHit = "pierce"
  , irarity  = [(5, 1), (8, 6)]
  , iaspects = [SetFlag Unique, Timeout 3, EqpSlot EqpSlotWeaponFast]
               ++ (iaspects sword \\ [Timeout 7, EqpSlot EqpSlotWeaponBig])
  , ieffects = [ DropItem 1 maxBound COrgan CONDITION
               , RefillCalm (-10)
               , Yell ]
  , idesc    = "Cold, thin blade that pierces deeply and sends its victim into abrupt, sobering shock."
  }
halberd :: ItemKind
halberd = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolPolearm
  , iname :: Text
iname    = Text
"war scythe"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, Int
100), (GroupName ItemKind
STARTING_WEAPON, Int
20)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrYellow]
  , icount :: Dice
icount   = Dice
1
  , irarity :: Rarity
irarity  = [(Double
5, Int
1), (Double
8, Int
12)]
  , iverbHit :: Text
iverbHit = Text
"impale"
  , iweight :: Int
iweight  = Int
3000
  , idamage :: Dice
idamage  = Int
12 Int -> Int -> Dice
`d` Int
1
  , iaspects :: [Aspect]
iaspects = [ Dice -> Aspect
Timeout Dice
10
               , Skill -> Dice -> Aspect
AddSkill Skill
SkHurtMelee (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (-Dice
5 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Dice
`dL` Int
3) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* Dice
5
                   -- useless against armor at game start
               , Skill -> Dice -> Aspect
AddSkill Skill
SkArmorMelee Dice
20
               , Flag -> Aspect
SetFlag Flag
Durable, Flag -> Aspect
SetFlag Flag
Meleeable
               , EqpSlot -> Aspect
EqpSlot EqpSlot
EqpSlotWeaponBig
               , Int -> Aspect
toVelocity Int
20 ]  -- not balanced
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = Text
"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    = "halberd"
  , ifreq    = [(COMMON_ITEM, 3 * 2), (STARTING_WEAPON, 1)]
  , iweight  = 4000
  , iaspects = AddSkill SkHurtMelee ((-6 + 1 `dL` 4) * 10)
                 -- balance, or @DupItem@ would break the game;
                 -- together with @RerollItem@, it's allowed to, though
               : (iaspects halberd
                  \\ [AddSkill SkHurtMelee $ (-6 + 1 `dL` 4) * 5])
  , idamage  = 18 `d` 1
  , idesc    = "A long haft with a sharp blade. Designed and refined for war."
  }
halberd3 :: ItemKind
halberd3 = ItemKind
halberd2
  { iname    = "bardiche"
  , ifreq    = [(COMMON_ITEM, 1 * 2)]  -- compensating for low base rarity
  , iverbHit = "carve"
  , iweight  = 5000
  , idamage  = 24 `d` 1
  , idesc    = "The reach of a spear but the edge of an axe."
  }
halberdPushActor :: ItemKind
halberdPushActor = ItemKind
halberd
  { iname    = "The Swiss Halberd"
  , ifreq    = [(TREASURE, 20)]
  , irarity  = [(7, 0), (9, 15)]
  , iaspects = SetFlag Unique
               : iaspects halberd
  , ieffects = [PushActor (ThrowMod 200 100 1)]  -- 2 steps, slow
  , idesc    = "A versatile polearm, with great reach and leverage. Foes are held at a distance."
  }

-- ** Treasure

gemTemplate :: ItemKind
gemTemplate = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolGold
  , iname :: Text
iname    = Text
"gem"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
GEM_UNKNOWN, Int
1), (GroupName ItemKind
VALUABLE, Int
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   = Dice
1
  , irarity :: Rarity
irarity  = [(Double
3, Int
0), (Double
10, Int
24)]
  , iverbHit :: Text
iverbHit = Text
"tap"
  , iweight :: Int
iweight  = Int
50
  , idamage :: Dice
idamage  = Dice
0
  , iaspects :: [Aspect]
iaspects = [GroupName ItemKind -> Aspect
PresentAs GroupName ItemKind
GEM_UNKNOWN, Flag -> Aspect
SetFlag Flag
Precious]
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = Text
"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    = [ (TREASURE, 100), (GEM, 100), (ANY_JEWELRY, 10)
               , (VALUABLE, 100) ]
  , irarity  = [(3, 0), (6, 12), (10, 8)]
  , iaspects = [AddSkill SkShine 1, AddSkill SkSpeed (-1)]
                 -- reflects strongly, distracts; so it glows in the dark,
                 -- is visible on dark floor, but not too tempting to wear
               ++ iaspects gemTemplate
  }
gem2 :: ItemKind
gem2 = ItemKind
gem1
  { ifreq    = [ (TREASURE, 150), (GEM, 100), (ANY_JEWELRY, 10)
               , (VALUABLE, 100) ]
  , irarity  = [(5, 0), (7, 25), (10, 8)]
  }
gem3 :: ItemKind
gem3 = ItemKind
gem1
  { ifreq    = [ (TREASURE, 150), (GEM, 100), (ANY_JEWELRY, 10)
               , (VALUABLE, 100) ]
  , irarity  = [(7, 0), (8, 20), (10, 8)]
  }
gem4 :: ItemKind
gem4 = ItemKind
gem1
  { ifreq    = [ (TREASURE, 150), (GEM, 100), (ANY_JEWELRY, 30)
               , (VALUABLE, 100) ]
  , irarity  = [(9, 0), (10, 70)]
  }
gem5 :: ItemKind
gem5 = ItemKind
gem1
  { isymbol  = symbolSpecial
  , iname    = "elixir"
  , ifreq    = [ (TREASURE, 100), (GEM, 25), (ANY_JEWELRY, 10)
               , (VALUABLE, 100) ]
  , iflavour = zipPlain [BrYellow]
  , irarity  = [(1, 40), (10, 10)]
  , iaspects = [ ELabel "of youth", SetFlag Precious  -- not hidden
               , AddSkill SkOdor (-1) ]
  , ieffects = [RefillCalm 10, RefillHP 40]
  , 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 = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolGold
  , iname :: Text
iname    = Text
"gold piece"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
CURRENCY_UNKNOWN, Int
1), (GroupName ItemKind
VALUABLE, Int
1)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
BrYellow]
  , icount :: Dice
icount   = Dice
10 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Dice
`d` Int
20 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Dice
`dL` Int
20
  , irarity :: Rarity
irarity  = [(Double
1, Int
25), (Double
10, Int
10)]
  , iverbHit :: Text
iverbHit = Text
"tap"
  , iweight :: Int
iweight  = Int
31
  , idamage :: Dice
idamage  = Dice
0
  , iaspects :: [Aspect]
iaspects = [GroupName ItemKind -> Aspect
PresentAs GroupName ItemKind
CURRENCY_UNKNOWN, Flag -> Aspect
SetFlag Flag
Precious]
  , ieffects :: [Effect]
ieffects = []
  , idesc :: Text
idesc    = Text
"Reliably valuable in every civilized plane of existence."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
currency :: ItemKind
currency = ItemKind
currencyTemplate
  { ifreq    = [(TREASURE, 100), (S_CURRENCY, 100), (VALUABLE, 1)]
  , iaspects = [AddSkill SkShine 1, AddSkill SkSpeed (-1)]
               ++ iaspects currencyTemplate
  }

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

jumpingPole :: ItemKind
jumpingPole = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolWand
  , iname :: Text
iname    = Text
"jumping pole"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, Int
90)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipFancy [Color
White]
  , icount :: Dice
icount   = Dice
1
  , irarity :: Rarity
irarity  = [(Double
1, Int
3)]
  , iverbHit :: Text
iverbHit = Text
"prod"
  , iweight :: Int
iweight  = Int
10000
  , idamage :: Dice
idamage  = Dice
0
  , iaspects :: [Aspect]
iaspects = [ Dice -> Aspect
Timeout (Dice -> Aspect) -> Dice -> Aspect
forall a b. (a -> b) -> a -> b
$ (Dice
2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
+ Int
1 Int -> Int -> Dice
`d` Int
2 Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
- Int
1 Int -> Int -> Dice
`dL` Int
2) Dice -> Dice -> Dice
forall a. Num a => a -> a -> a
* Dice
5
               , Flag -> Aspect
SetFlag Flag
Durable ]
  , ieffects :: [Effect]
ieffects = [GroupName ItemKind -> Dice -> Effect
toOrganGood GroupName ItemKind
S_HASTED Dice
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    = Text
"Makes you vulnerable at take-off, but then you are free like a bird."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }
seeingItem :: ItemKind
seeingItem = ItemKind
  { isymbol :: ContentSymbol ItemKind
isymbol  = ContentSymbol ItemKind
symbolFood
  , iname :: Text
iname    = Text
"giant pupil"
  , ifreq :: Freqs ItemKind
ifreq    = [(GroupName ItemKind
COMMON_ITEM, Int
100)]
  , iflavour :: [Flavour]
iflavour = [Color] -> [Flavour]
zipPlain [Color
Red]
  , icount :: Dice
icount   = Dice
1
  , irarity :: Rarity
irarity  = [(Double
1, Int
2)]
  , iverbHit :: Text
iverbHit = Text
"gaze at"
  , iweight :: Int
iweight  = Int
100
  , idamage :: Dice
idamage  = Dice
0
  , iaspects :: [Aspect]
iaspects = [ Dice -> Aspect
Timeout Dice
3
               , Skill -> Dice -> Aspect
AddSkill Skill
SkSight Dice
10  -- a spyglass for quick wields
               , Skill -> Dice -> Aspect
AddSkill Skill
SkMaxCalm Dice
30  -- to diminish clipping sight by Calm
               , Skill -> Dice -> Aspect
AddSkill Skill
SkShine Dice
2  -- to lit corridors when flying
               , Flag -> Aspect
SetFlag Flag
Periodic ]
  , ieffects :: [Effect]
ieffects = [ DetectKind -> Int -> Effect
Detect DetectKind
DetectActor Int
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 Dice
1 ] ]
  , idesc :: Text
idesc    = Text
"A slimy, dilated green pupil torn out from some giant eye. Clear and focused, as if still alive."
  , ikit :: [(GroupName ItemKind, CStore)]
ikit     = []
  }