LambdaHack-0.8.1.2: 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. Note that this type is mutually recursive with Effect and Feature.

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 :: * -> * #

Methods

from :: ItemKind -> Rep ItemKind x #

to :: Rep ItemKind x -> ItemKind #

NFData ItemKind Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Methods

rnf :: 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.8.1.2-9Fmfvbfsr9xEInnejydwaW" 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 Part)))) :*: ((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 "ifeature") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Feature])) :*: (S1 (MetaSel (Just "idesc") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "ikit") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [(GroupName ItemKind, CStore)]))))))

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

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

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

Recharging Effect

this effect inactive until timeout passes

Composite [Effect]

only fire next effect if previous fully activated

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

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 :: * -> * #

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 #

NFData Effect Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Methods

rnf :: Effect -> () #

type Rep Effect Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

type Rep Effect = D1 (MetaData "Effect" "Game.LambdaHack.Content.ItemKind" "LambdaHack-0.8.1.2-9Fmfvbfsr9xEInnejydwaW" 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 :: * -> *)) :+: (C1 (MetaCons "Impress" PrefixI False) (U1 :: * -> *) :+: 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 :: * -> *) :+: C1 (MetaCons "Paralyze" 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 :: * -> *) :+: (C1 (MetaCons "Identify" PrefixI False) (U1 :: * -> *) :+: 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 :: * -> *)))) :+: ((C1 (MetaCons "ActivateInv" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Char)) :+: (C1 (MetaCons "ApplyPerfume" PrefixI False) (U1 :: * -> *) :+: 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 "Recharging" 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 "Temporary" 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 :: * -> * #

Binary DetectKind Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

NFData DetectKind Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Methods

rnf :: DetectKind -> () #

type Rep DetectKind Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

type Rep DetectKind = D1 (MetaData "DetectKind" "Game.LambdaHack.Content.ItemKind" "LambdaHack-0.8.1.2-9Fmfvbfsr9xEInnejydwaW" False) ((C1 (MetaCons "DetectAll" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "DetectActor" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "DetectItem" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "DetectExit" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "DetectHidden" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "DetectEmbed" PrefixI False) (U1 :: * -> *))))

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 :: * -> * #

Binary TimerDice Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

NFData TimerDice Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Methods

rnf :: TimerDice -> () #

type Rep TimerDice Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

type Rep TimerDice = D1 (MetaData "TimerDice" "Game.LambdaHack.Content.ItemKind" "LambdaHack-0.8.1.2-9Fmfvbfsr9xEInnejydwaW" False) (C1 (MetaCons "TimerNone" PrefixI False) (U1 :: * -> *) :+: (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 :: * -> * #

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 #

NFData ThrowMod Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Methods

rnf :: ThrowMod -> () #

type Rep ThrowMod Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

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

data Feature Source #

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

Constructors

ELabel Text

extra label of the item; it's not pluralized

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

HideAs (GroupName ItemKind)

until identified, presents as this unique kind

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; WIP; move?

Blast

the item is an explosion blast particle

EqpSlot EqpSlot

AI and UI flag that leaks item intended use

Unique

at most one copy can ever be generated

Periodic

in eqp, triggered as often as Timeout permits

MinorEffects

override: the effects on this item are considered minor and so not causing identification on use, and so this item will identify on pick-up

Instances
Eq Feature Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Methods

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

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

Ord Feature Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Show Feature Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Generic Feature Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Associated Types

type Rep Feature :: * -> * #

Methods

from :: Feature -> Rep Feature x #

to :: Rep Feature x -> Feature #

NFData Feature Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Methods

rnf :: Feature -> () #

type Rep Feature Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

type Rep Feature = D1 (MetaData "Feature" "Game.LambdaHack.Content.ItemKind" "LambdaHack-0.8.1.2-9Fmfvbfsr9xEInnejydwaW" False) (((C1 (MetaCons "ELabel" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text)) :+: (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 :: 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 "Equipable" PrefixI False) (U1 :: * -> *)))) :+: (((C1 (MetaCons "Meleeable" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Precious" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Tactic" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Tactic)) :+: C1 (MetaCons "Blast" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "EqpSlot" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 EqpSlot)) :+: C1 (MetaCons "Unique" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Periodic" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "MinorEffects" PrefixI False) (U1 :: * -> *)))))

data ItemSpeedup Source #

Map from an item kind identifier to the mean aspect value for the kind.

Significant portions of this map are unused and so intentially kept unevaluated.

Instances
Eq ItemSpeedup Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Show ItemSpeedup Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Generic ItemSpeedup Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

Associated Types

type Rep ItemSpeedup :: * -> * #

type Rep ItemSpeedup Source # 
Instance details

Defined in Game.LambdaHack.Content.ItemKind

type Rep ItemSpeedup = D1 (MetaData "ItemSpeedup" "Game.LambdaHack.Content.ItemKind" "LambdaHack-0.8.1.2-9Fmfvbfsr9xEInnejydwaW" True) (C1 (MetaCons "ItemSpeedup" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector KindMean))))

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.