LambdaHack-0.9.3.1: A game engine library for tactical squad ASCII 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. 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
Show ItemKind Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Generic ItemKind Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Associated Types

type Rep ItemKind :: Type -> Type #

Methods

from :: ItemKind -> Rep ItemKind x #

to :: Rep ItemKind x -> ItemKind #

type Rep ItemKind Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

type Rep ItemKind = D1 (MetaData "ItemKind" "Game.LambdaHack.Content.ItemKind" "LambdaHack-0.9.3.1-inplace" False) (C1 (MetaCons "ItemKind" PrefixI True) (((S1 (MetaSel (Just "isymbol") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Char) :*: (S1 (MetaSel (Just "iname") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "ifreq") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Freqs ItemKind)))) :*: (S1 (MetaSel (Just "iflavour") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Flavour]) :*: (S1 (MetaSel (Just "icount") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Dice) :*: S1 (MetaSel (Just "irarity") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Rarity)))) :*: ((S1 (MetaSel (Just "iverbHit") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text) :*: (S1 (MetaSel (Just "iweight") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "idamage") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Dice))) :*: ((S1 (MetaSel (Just "iaspects") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Aspect]) :*: S1 (MetaSel (Just "ieffects") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Effect])) :*: (S1 (MetaSel (Just "ikit") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [(GroupName ItemKind, CStore)]) :*: S1 (MetaSel (Just "idesc") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text))))))

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

HideAs (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
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

Generic Aspect Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Associated Types

type Rep Aspect :: Type -> Type #

Methods

from :: Aspect -> Rep Aspect x #

to :: Rep Aspect x -> Aspect #

type Rep Aspect Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

type Rep Aspect = D1 (MetaData "Aspect" "Game.LambdaHack.Content.ItemKind" "LambdaHack-0.9.3.1-inplace" False) (((C1 (MetaCons "Timeout" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Dice)) :+: C1 (MetaCons "AddSkill" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Skill) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Dice))) :+: (C1 (MetaCons "SetFlag" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Flag)) :+: C1 (MetaCons "ELabel" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text)))) :+: ((C1 (MetaCons "ToThrow" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 ThrowMod)) :+: C1 (MetaCons "HideAs" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (GroupName ItemKind)))) :+: (C1 (MetaCons "EqpSlot" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 EqpSlot)) :+: C1 (MetaCons "Odds" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Dice) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Aspect]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Aspect]))))))

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

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

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

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);

Composite [Effect]

only fire next effect if previous fully activated

VerbNoLonger Text

a sentence with the actor causing the effect as subject and the given text as verb is emitted when the activation causes item to expire; no spam is emitted if a projectile

VerbMsg Text

a sentence with the actor causing the effect as subject and the given text as verb is emitted whenever the item is activated; no spam is emitted if a projectile

Instances
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

Generic Effect Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Associated Types

type Rep Effect :: Type -> Type #

Methods

from :: Effect -> Rep Effect x #

to :: Rep Effect x -> Effect #

Binary Effect Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Methods

put :: Effect -> Put #

get :: Get Effect #

putList :: [Effect] -> Put #

type Rep Effect Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

type Rep Effect = D1 (MetaData "Effect" "Game.LambdaHack.Content.ItemKind" "LambdaHack-0.9.3.1-inplace" False) (((((C1 (MetaCons "Burn" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Dice)) :+: C1 (MetaCons "Explode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (GroupName ItemKind)))) :+: (C1 (MetaCons "RefillHP" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int)) :+: C1 (MetaCons "RefillCalm" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int)))) :+: ((C1 (MetaCons "Dominate" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Impress" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "PutToSleep" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Yell" PrefixI False) (U1 :: Type -> Type)))) :+: (((C1 (MetaCons "Summon" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (GroupName ItemKind)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Dice)) :+: C1 (MetaCons "Ascend" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Bool))) :+: (C1 (MetaCons "Escape" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Paralyze" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Dice)))) :+: ((C1 (MetaCons "ParalyzeInWater" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Dice)) :+: C1 (MetaCons "InsertMove" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Dice))) :+: (C1 (MetaCons "Teleport" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Dice)) :+: C1 (MetaCons "CreateItem" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 CStore) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (GroupName ItemKind)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 TimerDice))))))) :+: ((((C1 (MetaCons "DropItem" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 CStore) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (GroupName ItemKind)))) :+: C1 (MetaCons "PolyItem" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "RerollItem" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DupItem" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Identify" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Detect" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 DetectKind) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int))) :+: (C1 (MetaCons "SendFlying" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 ThrowMod)) :+: C1 (MetaCons "PushActor" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 ThrowMod))))) :+: (((C1 (MetaCons "PullActor" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 ThrowMod)) :+: C1 (MetaCons "DropBestWeapon" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "ActivateInv" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Char)) :+: C1 (MetaCons "ApplyPerfume" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "OneOf" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Effect])) :+: C1 (MetaCons "OnSmash" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Effect))) :+: (C1 (MetaCons "Composite" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Effect])) :+: (C1 (MetaCons "VerbNoLonger" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text)) :+: C1 (MetaCons "VerbMsg" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text))))))))

data DetectKind Source #

Instances
Eq DetectKind Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Show DetectKind Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Generic DetectKind Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Associated Types

type Rep DetectKind :: Type -> Type #

Binary DetectKind Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

type Rep DetectKind Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

type Rep DetectKind = D1 (MetaData "DetectKind" "Game.LambdaHack.Content.ItemKind" "LambdaHack-0.9.3.1-inplace" False) ((C1 (MetaCons "DetectAll" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "DetectActor" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DetectLoot" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "DetectExit" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "DetectHidden" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DetectEmbed" PrefixI False) (U1 :: Type -> Type))))

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 # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Show TimerDice Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Generic TimerDice Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Associated Types

type Rep TimerDice :: Type -> Type #

Binary TimerDice Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

type Rep TimerDice Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

type Rep TimerDice = D1 (MetaData "TimerDice" "Game.LambdaHack.Content.ItemKind" "LambdaHack-0.9.3.1-inplace" False) (C1 (MetaCons "TimerNone" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "TimerGameTurn" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Dice)) :+: C1 (MetaCons "TimerActorTurn" PrefixI False) (S1 (MetaSel (Nothing :: Maybe 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 # 
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.9.3.1-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. We assume at least one of OneOf effects must be noticeable.

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.