LambdaHack-0.10.2.0: A game engine library for tactical squad ASCII roguelike dungeon crawlers
Safe HaskellNone
LanguageHaskell2010

Game.LambdaHack.Content.ItemKind

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. Of these, aspects and effects are jointly called item powers. Note that this type is mutually recursive with Effect and Aspect.

Constructors

ItemKind 

Fields

Instances

Instances details
Show ItemKind Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

data Aspect Source #

Aspects of items. Aspect AddSkill is additive (starting at 0) for all items wielded by an actor and it affects the actor. The others affect only the item in question, not the actor carrying it, and so are not additive in any sense.

Constructors

Timeout Dice

specifies the cooldown before an item may be applied again; if a copy of an item is applied manually (not via periodic activation), all effects on a single copy of the item are disabled until the copy recharges for the given time expressed in game turns; all copies recharge concurrently

AddSkill Skill Dice

bonus to a skill; in content, avoid boosting skills such as SkApply via permanent equipment, to avoid micromanagement through swapping items among party members before each skill use

SetFlag Flag

item feature

ELabel Text

extra label of the item; it's not pluralized

ToThrow ThrowMod

parameters modifying a throw

PresentAs (GroupName ItemKind)

until identified, presents as this unique kind

EqpSlot EqpSlot

AI and UI flag that leaks item intended use

Odds Dice [Aspect] [Aspect]

if level-scaled dice roll > 50, pick the former aspects, otherwise the latter

Instances

Instances details
Eq Aspect Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Methods

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

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

Show Aspect Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

data Effect Source #

Effects of items. Can be invoked by the item wielder to affect another actor or the wielder himself.

Various effects of an item kind are all groupped in one list, at the cost of conditionals, sequences, etc., to ensure brevity and simplicity of content definitions. Most effects fire regardless of activation kind (the only exceptions are OnSmash and OnCombine effects) so the deviations, handled via the conditionals, are rare and the definitions remain simple. Whether an item can be activated in any particular way, OTOH, is specified via simple flags elsewhere, again, by default, assuming that most activations are possible for all.

Constructors

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

PutToSleep

put actor to sleep, also calming him

Yell

make the actor yell/yawn, waking him and others up

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

ParalyzeInWater Dice

paralyze for this many game clips due to water

InsertMove Dice

give actor this many extra tenths of actor move

Teleport Dice

teleport actor across rougly this distance

CreateItem (Maybe Int) CStore (GroupName ItemKind) TimerDice

create an item of the group and insert into the store with the given random timer; it cardinality not specified, roll it

DestroyItem Int Int CStore (GroupName ItemKind)

destroy some items of the group from the store; see below about Ints

ConsumeItems [(Int, GroupName ItemKind)] [(Int, GroupName ItemKind)]

ConsumeItems toUse toDestroy uses items matching toUse (destroys non-durable, without invoking OnSmash effects; applies normal effects of durable, without destroying them; the same behaviour as when transforming terrain using items) and destroys items matching toDestroy, invoking no effects, regardless of durability; the items are taken from CGround (but not from CEqp), preferring non-durable (since durable can harm when used and may be more vauable when destroyed); if not all required items are present, no item are destroyed; if an item belongs to many groups in the sum of toUse and toDestroy, it counts for all (otherwise, some orders of destroying would succeed, while others would not); even if item durable, as many copies are needed as specified, not just one applied many times; items are first destroyed and then, if any copies left, applied

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 copies of each kind to drop; for non-organs, beware of not dropping all kinds, or cluttering store with rubbish becomes beneficial

Recharge Int Dice

reduce the cooldown period of this number of discharged items in the victim's equipment and organs by this dice of game clips; if the result is negative, set to 0, instantly recharging the item; starts with weapons with highest raw damage in equipment, then among organs, then non-weapons in equipment and among organs; beware of exploiting for healing periodic items

Discharge Int Dice

increase the cooldown period of this number of fully recharged items in the victim's equipment and organs by this dice of game clips; starts with weapons with highest raw damage in equipment, then among organs, then non-weapons in equipment and among organs; beware of exploiting for hunger inducing and similar organs

PolyItem

get a suitable (i.e., numerous enough) non-unique common item stack on the floor and polymorph it to a stack of random common items, with current depth coefficient

RerollItem

get a suitable (i.e., with any random aspects) single item (even unique) on the floor and change the random bonuses of the items randomly, with maximal depth coefficient

DupItem

exactly duplicate a single non-unique, non-valuable item on the floor

Identify

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

Detect DetectKind Int

detect something on the map in the given radius

SendFlying ThrowMod

send an actor flying (push or pull, depending)

PushActor ThrowMod

push an actor

PullActor ThrowMod

pull an actor

ApplyPerfume

remove all smell on the level

AtMostOneOf [Effect]

try to trigger a single random effect of the list

OneOf [Effect]

trigger, with equal probability, one of the effects that don't end with UseDud

OnSmash Effect

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

OnCombine Effect

trigger the effect only when the actor explicitly desires to combine items or otherwise subtly tinker with an item or a tile, e.g., craft items from other items in a workshop; in particular, don't trigger the effects when entering a tile; trigger exclusively the effects when activating walkable terrain

OnUser Effect

apply the effect to the user, not the victim

NopEffect

nothing happens, UseDud, no description

AndEffect Effect Effect

only fire second effect if first activated

OrEffect Effect Effect

only fire second effect if first not activated

SeqEffect [Effect]

fire all effects in order; always suceed

When Condition Effect

if condition not met, fail without a message; better avoided, since AI can't value it well

Unless Condition Effect

if condition met, fail without a message; better avoided, since AI can't value it well

IfThenElse Condition Effect Effect

conditional effect; better avoided, since AI can't value it well

VerbNoLonger Text Text

a sentence with the actor causing the effect as subject, the given texts as the verb and the ending of the sentence (that may be ignored when the message is cited, e.g., as heard by someone) that is emitted when an activation causes an item to expire; no spam is emitted if a projectile; the ending is appended without a space in-between

VerbMsg Text Text

as VerbNoLonger but that is emitted whenever the item is activated;

VerbMsgFail Text Text

as VerbMsg, but a failed effect (returns UseId)

Instances

Instances details
Eq Effect Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Methods

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

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

Show Effect Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

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

Instances details
Eq TimerDice Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Show TimerDice Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

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

Instances details
Eq ThrowMod Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Ord ThrowMod Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Show ThrowMod Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Generic ThrowMod Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Associated Types

type Rep ThrowMod :: Type -> Type #

Methods

from :: ThrowMod -> Rep ThrowMod x #

to :: Rep ThrowMod x -> ThrowMod #

Binary ThrowMod Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Methods

put :: ThrowMod -> Put #

get :: Get ThrowMod #

putList :: [ThrowMod] -> Put #

Hashable ThrowMod Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Methods

hashWithSalt :: Int -> ThrowMod -> Int #

hash :: ThrowMod -> Int #

type Rep ThrowMod Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

type Rep ThrowMod = D1 ('MetaData "ThrowMod" "Game.LambdaHack.Content.ItemKind" "LambdaHack-0.10.2.0-inplace" 'False) (C1 ('MetaCons "ThrowMod" 'PrefixI 'True) (S1 ('MetaSel ('Just "throwVelocity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Just "throwLinger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "throwHP") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int))))

forApplyEffect :: Effect -> Bool Source #

Whether the effect has a chance of exhibiting any potentially noticeable behaviour, except when the item is destroyed or combined. We assume at least one of OneOf effects must be noticeable.

forDamageEffect :: Effect -> Bool Source #

Whether a non-nested effect always applies raw damage.

isDamagingKind :: ItemKind -> Bool Source #

Whether an item is damaging. Such items may trigger embedded items and may collide with bursting items mid-air.

foldTimer :: a -> (Dice -> a) -> (Dice -> a) -> TimerDice -> a Source #

Internal operations

validateSingle :: ItemKind -> [Text] Source #

Catch invalid item kind definitions.

validateAll :: [ItemKind] -> ContentData ItemKind -> [Text] Source #

Validate all item kinds.