LambdaHack-0.7.0.0: A game engine library for roguelike dungeon crawlers

Safe HaskellNone
LanguageHaskell2010

Game.LambdaHack.Content.ItemKind

Contents

Description

The type of kinds of weapons, treasure, organs, blasts, etc.

Synopsis

Documentation

data ItemKind Source #

Item properties that are fixed for a given kind of items.

Constructors

ItemKind 

Fields

data Effect Source #

Effects of items. Can be invoked by the item wielder to affect another actor or the wielder himself. Many occurences in the same item are possible.

Constructors

ELabel Text

secret (learned as effect) name of the item

EqpSlot EqpSlot

AI and UI flag that leaks item properties

Burn Dice

burn with this damage

Explode (GroupName ItemKind)

explode producing this group of blasts

RefillHP Int

modify HP of the actor by this amount

RefillCalm Int

modify Calm of the actor by this amount

Dominate

change actor's allegiance

Impress

make actor susceptible to domination

Summon (GroupName ItemKind) Dice

summon the given number of actors of this group

Ascend Bool

ascend to another level of the dungeon

Escape

escape from the dungeon

Paralyze Dice

paralyze for this many game clips

InsertMove Dice

give free time to actor of this many game turns

Teleport Dice

teleport actor across rougly this distance

CreateItem CStore (GroupName ItemKind) TimerDice

create an item of the group and insert into the store with the given random timer

DropItem Int Int CStore (GroupName ItemKind)

make the actor drop items of the given group from the given store; the first integer says how many item kinds to drop, the second, how many copie of each kind to drop

PolyItem

find a suitable (i.e., numerous enough) item, starting from the floor, and polymorph it randomly

Identify

find a suitable (i.e., not identified) item, starting from the floor, and identify it

Detect Int

detect all on the map in the given radius

DetectActor Int

detect actors on the map in the given radius

DetectItem Int

detect items on the map in the given radius

DetectExit Int

detect exits on the map in the given radius

DetectHidden Int

detect hidden tiles on the map in the radius

SendFlying ThrowMod

send an actor flying (push or pull, depending)

PushActor ThrowMod

push an actor

PullActor ThrowMod

pull an actor

DropBestWeapon

make the actor drop its best weapon

ActivateInv Char

activate all items with this symbol in inventory; space character means all symbols

ApplyPerfume

remove all smell on the level

OneOf [Effect]

trigger one of the effects with equal probability

OnSmash Effect

trigger the effect when item smashed (not when applied nor meleed)

Recharging Effect

this effect inactive until timeout passes

Temporary Text

the item is temporary, vanishes at even void Periodic activation, unless Durable and not Fragile, and shows message with this verb at last copy activation or at each activation unless Durable and Fragile

Unique

at most one copy can ever be generated

Periodic

in equipment, triggered as often as Timeout permits

Composite [Effect]

only fire next effect if previous was triggered

Instances

Eq Effect Source # 

Methods

(==) :: Effect -> Effect -> Bool #

(/=) :: Effect -> Effect -> Bool #

Show Effect Source # 
Generic Effect Source # 

Associated Types

type Rep Effect :: * -> * #

Methods

from :: Effect -> Rep Effect x #

to :: Rep Effect x -> Effect #

Binary Effect Source # 

Methods

put :: Effect -> Put #

get :: Get Effect #

putList :: [Effect] -> Put #

NFData Effect Source # 

Methods

rnf :: Effect -> () #

Hashable Effect Source # 

Methods

hashWithSalt :: Int -> Effect -> Int #

hash :: Effect -> Int #

type Rep Effect Source # 
type Rep Effect = D1 * (MetaData "Effect" "Game.LambdaHack.Content.ItemKind" "LambdaHack-0.7.0.0-3XPyz9bw1i28qJIoWU6CaM" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "ELabel" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Text))) (C1 * (MetaCons "EqpSlot" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * EqpSlot)))) ((:+:) * (C1 * (MetaCons "Burn" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Dice))) (C1 * (MetaCons "Explode" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * (GroupName ItemKind)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "RefillHP" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Int))) (C1 * (MetaCons "RefillCalm" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Int)))) ((:+:) * (C1 * (MetaCons "Dominate" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Impress" PrefixI False) (U1 *)) (C1 * (MetaCons "Summon" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * (GroupName ItemKind))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Dice)))))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Ascend" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Bool))) (C1 * (MetaCons "Escape" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Paralyze" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Dice))) (C1 * (MetaCons "InsertMove" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Dice))))) ((:+:) * ((:+:) * (C1 * (MetaCons "Teleport" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Dice))) (C1 * (MetaCons "CreateItem" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * CStore)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * (GroupName ItemKind))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * TimerDice)))))) ((:+:) * (C1 * (MetaCons "DropItem" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Int)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Int))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * CStore)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * (GroupName ItemKind)))))) ((:+:) * (C1 * (MetaCons "PolyItem" PrefixI False) (U1 *)) (C1 * (MetaCons "Identify" PrefixI False) (U1 *))))))) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Detect" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Int))) (C1 * (MetaCons "DetectActor" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Int)))) ((:+:) * (C1 * (MetaCons "DetectItem" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Int))) (C1 * (MetaCons "DetectExit" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Int))))) ((:+:) * ((:+:) * (C1 * (MetaCons "DetectHidden" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Int))) (C1 * (MetaCons "SendFlying" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * ThrowMod)))) ((:+:) * (C1 * (MetaCons "PushActor" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * ThrowMod))) ((:+:) * (C1 * (MetaCons "PullActor" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * ThrowMod))) (C1 * (MetaCons "DropBestWeapon" PrefixI False) (U1 *)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "ActivateInv" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Char))) (C1 * (MetaCons "ApplyPerfume" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "OneOf" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * [Effect]))) (C1 * (MetaCons "OnSmash" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Effect))))) ((:+:) * ((:+:) * (C1 * (MetaCons "Recharging" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Effect))) (C1 * (MetaCons "Temporary" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Text)))) ((:+:) * (C1 * (MetaCons "Unique" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Periodic" PrefixI False) (U1 *)) (C1 * (MetaCons "Composite" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * [Effect])))))))))

data TimerDice Source #

Specification of how to randomly roll a timer at item creation to obtain a fixed timer for the item's lifetime.

Instances

Eq TimerDice Source # 
Show TimerDice Source # 
Generic TimerDice Source # 

Associated Types

type Rep TimerDice :: * -> * #

Binary TimerDice Source # 
NFData TimerDice Source # 

Methods

rnf :: TimerDice -> () #

Hashable TimerDice Source # 
type Rep TimerDice Source # 
type Rep TimerDice = D1 * (MetaData "TimerDice" "Game.LambdaHack.Content.ItemKind" "LambdaHack-0.7.0.0-3XPyz9bw1i28qJIoWU6CaM" False) ((:+:) * (C1 * (MetaCons "TimerNone" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "TimerGameTurn" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Dice))) (C1 * (MetaCons "TimerActorTurn" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Dice)))))

data Aspect Source #

Aspects of items. Those that are named Add* are additive (starting at 0) for all items wielded by an actor and they affect the actor.

Constructors

Timeout Dice

some effects disabled until item recharges; expressed in game turns

AddHurtMelee Dice

percentage damage bonus in melee

AddArmorMelee Dice

percentage armor bonus against melee

AddArmorRanged Dice

percentage armor bonus against ranged

AddMaxHP Dice

maximal hp

AddMaxCalm Dice

maximal calm

AddSpeed Dice

speed in m/10s (not when pushed or pulled)

AddSight Dice

FOV radius, where 1 means a single tile FOV

AddSmell Dice

smell radius

AddShine Dice

shine radius

AddNocto Dice

noctovision radius

AddAggression Dice

aggression, e.g., when closing in for melee

AddAbility Ability Dice

bonus to an ability

Instances

Eq Aspect Source # 

Methods

(==) :: Aspect -> Aspect -> Bool #

(/=) :: Aspect -> Aspect -> Bool #

Ord Aspect Source # 
Show Aspect Source # 
Generic Aspect Source # 

Associated Types

type Rep Aspect :: * -> * #

Methods

from :: Aspect -> Rep Aspect x #

to :: Rep Aspect x -> Aspect #

Binary Aspect Source # 

Methods

put :: Aspect -> Put #

get :: Get Aspect #

putList :: [Aspect] -> Put #

Hashable Aspect Source # 

Methods

hashWithSalt :: Int -> Aspect -> Int #

hash :: Aspect -> Int #

type Rep Aspect Source # 
type Rep Aspect = D1 * (MetaData "Aspect" "Game.LambdaHack.Content.ItemKind" "LambdaHack-0.7.0.0-3XPyz9bw1i28qJIoWU6CaM" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Timeout" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Dice))) ((:+:) * (C1 * (MetaCons "AddHurtMelee" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Dice))) (C1 * (MetaCons "AddArmorMelee" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Dice))))) ((:+:) * (C1 * (MetaCons "AddArmorRanged" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Dice))) ((:+:) * (C1 * (MetaCons "AddMaxHP" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Dice))) (C1 * (MetaCons "AddMaxCalm" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Dice)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "AddSpeed" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Dice))) ((:+:) * (C1 * (MetaCons "AddSight" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Dice))) (C1 * (MetaCons "AddSmell" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Dice))))) ((:+:) * ((:+:) * (C1 * (MetaCons "AddShine" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Dice))) (C1 * (MetaCons "AddNocto" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Dice)))) ((:+:) * (C1 * (MetaCons "AddAggression" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Dice))) (C1 * (MetaCons "AddAbility" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Ability)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Dice))))))))

data ThrowMod Source #

Parameters modifying a throw of a projectile or flight of pushed actor. Not additive and don't start at 0.

Constructors

ThrowMod 

Fields

Instances

Eq ThrowMod Source # 
Ord ThrowMod Source # 
Show ThrowMod Source # 
Generic ThrowMod Source # 

Associated Types

type Rep ThrowMod :: * -> * #

Methods

from :: ThrowMod -> Rep ThrowMod x #

to :: Rep ThrowMod x -> ThrowMod #

Binary ThrowMod Source # 

Methods

put :: ThrowMod -> Put #

get :: Get ThrowMod #

putList :: [ThrowMod] -> Put #

NFData ThrowMod Source # 

Methods

rnf :: ThrowMod -> () #

Hashable ThrowMod Source # 

Methods

hashWithSalt :: Int -> ThrowMod -> Int #

hash :: ThrowMod -> Int #

type Rep ThrowMod Source # 
type Rep ThrowMod = D1 * (MetaData "ThrowMod" "Game.LambdaHack.Content.ItemKind" "LambdaHack-0.7.0.0-3XPyz9bw1i28qJIoWU6CaM" False) (C1 * (MetaCons "ThrowMod" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "throwVelocity") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "throwLinger") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Int))))

data Feature Source #

Features of item. Publicly visible. Affect only the item in question, not the actor, and so not additive in any sense.

Constructors

Fragile

drop and break at target tile, even if no hit

Lobable

drop at target tile, even if no hit

Durable

don't break even when hitting or applying

ToThrow ThrowMod

parameters modifying a throw

Identified

the item starts identified

Applicable

AI and UI flag: consider applying

Equipable

AI and UI flag: consider equipping (independent of EqpSlot, e.g., in case of mixed blessings)

Meleeable

AI and UI flag: consider meleeing with

Precious

AI and UI flag: don't risk identifying by use; also, can't throw or apply if not calm enough

Tactic Tactic

overrides actor's tactic

Instances

Eq Feature Source # 

Methods

(==) :: Feature -> Feature -> Bool #

(/=) :: Feature -> Feature -> Bool #

Ord Feature Source # 
Show Feature Source # 
Generic Feature Source # 

Associated Types

type Rep Feature :: * -> * #

Methods

from :: Feature -> Rep Feature x #

to :: Rep Feature x -> Feature #

Binary Feature Source # 

Methods

put :: Feature -> Put #

get :: Get Feature #

putList :: [Feature] -> Put #

Hashable Feature Source # 

Methods

hashWithSalt :: Int -> Feature -> Int #

hash :: Feature -> Int #

type Rep Feature Source # 
type Rep Feature = D1 * (MetaData "Feature" "Game.LambdaHack.Content.ItemKind" "LambdaHack-0.7.0.0-3XPyz9bw1i28qJIoWU6CaM" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Fragile" PrefixI False) (U1 *)) (C1 * (MetaCons "Lobable" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Durable" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ToThrow" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * ThrowMod))) (C1 * (MetaCons "Identified" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "Applicable" PrefixI False) (U1 *)) (C1 * (MetaCons "Equipable" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Meleeable" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Precious" PrefixI False) (U1 *)) (C1 * (MetaCons "Tactic" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Tactic)))))))

data EqpSlot Source #

AI and UI hints about the role of the item.

Instances

Bounded EqpSlot Source # 
Enum EqpSlot Source # 
Eq EqpSlot Source # 

Methods

(==) :: EqpSlot -> EqpSlot -> Bool #

(/=) :: EqpSlot -> EqpSlot -> Bool #

Ord EqpSlot Source # 
Show EqpSlot Source # 
Generic EqpSlot Source # 

Associated Types

type Rep EqpSlot :: * -> * #

Methods

from :: EqpSlot -> Rep EqpSlot x #

to :: Rep EqpSlot x -> EqpSlot #

Binary EqpSlot Source # 

Methods

put :: EqpSlot -> Put #

get :: Get EqpSlot #

putList :: [EqpSlot] -> Put #

NFData EqpSlot Source # 

Methods

rnf :: EqpSlot -> () #

Hashable EqpSlot Source # 

Methods

hashWithSalt :: Int -> EqpSlot -> Int #

hash :: EqpSlot -> Int #

type Rep EqpSlot Source # 
type Rep EqpSlot = D1 * (MetaData "EqpSlot" "Game.LambdaHack.Content.ItemKind" "LambdaHack-0.7.0.0-3XPyz9bw1i28qJIoWU6CaM" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "EqpSlotMiscBonus" PrefixI False) (U1 *)) (C1 * (MetaCons "EqpSlotAddHurtMelee" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "EqpSlotAddArmorMelee" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "EqpSlotAddArmorRanged" PrefixI False) (U1 *)) (C1 * (MetaCons "EqpSlotAddMaxHP" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "EqpSlotAddSpeed" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "EqpSlotAddSight" PrefixI False) (U1 *)) (C1 * (MetaCons "EqpSlotLightSource" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "EqpSlotWeapon" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "EqpSlotMiscAbility" PrefixI False) (U1 *)) (C1 * (MetaCons "EqpSlotAbMove" PrefixI False) (U1 *)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "EqpSlotAbMelee" PrefixI False) (U1 *)) (C1 * (MetaCons "EqpSlotAbDisplace" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "EqpSlotAbAlter" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "EqpSlotAbProject" PrefixI False) (U1 *)) (C1 * (MetaCons "EqpSlotAbApply" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "EqpSlotAddMaxCalm" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "EqpSlotAddSmell" PrefixI False) (U1 *)) (C1 * (MetaCons "EqpSlotAddNocto" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "EqpSlotAddAggression" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "EqpSlotAbWait" PrefixI False) (U1 *)) (C1 * (MetaCons "EqpSlotAbMoveItem" PrefixI False) (U1 *)))))))

forApplyEffect :: Effect -> Bool Source #

Whether the effect has a chance of exhibiting any potentially noticeable behaviour.

toDmg :: Dice -> [(Int, Dice)] Source #

validateSingleItemKind :: ItemKind -> [Text] Source #

Catch invalid item kind definitions.

validateAllItemKind :: [ItemKind] -> [Text] Source #

Validate all item kinds.

Internal operations