Safe Haskell | None |
---|---|
Language | Haskell2010 |
The type of kinds of weapons, treasure, organs, blasts, etc.
Synopsis
- pattern CONDITION :: GroupName ItemKind
- pattern COMMON_ITEM :: GroupName ItemKind
- pattern S_BONUS_HP :: GroupName ItemKind
- pattern S_BRACED :: GroupName ItemKind
- pattern S_ASLEEP :: GroupName ItemKind
- pattern S_IMPRESSED :: GroupName ItemKind
- pattern S_CURRENCY :: GroupName ItemKind
- pattern MOBILE :: GroupName ItemKind
- pattern CRAWL_ITEM :: GroupName ItemKind
- pattern TREASURE :: GroupName ItemKind
- pattern ANY_SCROLL :: GroupName ItemKind
- pattern ANY_GLASS :: GroupName ItemKind
- pattern ANY_POTION :: GroupName ItemKind
- pattern ANY_FLASK :: GroupName ItemKind
- pattern EXPLOSIVE :: GroupName ItemKind
- pattern ANY_JEWELRY :: GroupName ItemKind
- pattern S_SINGLE_SPARK :: GroupName ItemKind
- pattern S_SPARK :: GroupName ItemKind
- pattern S_FRAGRANCE :: GroupName ItemKind
- pattern HORROR :: GroupName ItemKind
- pattern VALUABLE :: GroupName ItemKind
- pattern UNREPORTED_INVENTORY :: GroupName ItemKind
- pattern AQUATIC :: GroupName ItemKind
- data ItemKind = ItemKind {}
- makeData :: ItemSymbolsUsedInEngine -> [ItemKind] -> [GroupName ItemKind] -> [GroupName ItemKind] -> ContentData ItemKind
- data Aspect
- data Effect
- = Burn Dice
- | Explode (GroupName ItemKind)
- | RefillHP Int
- | RefillCalm Int
- | Dominate
- | Impress
- | PutToSleep
- | Yell
- | Summon (GroupName ItemKind) Dice
- | Ascend Bool
- | Escape
- | Paralyze Dice
- | ParalyzeInWater Dice
- | InsertMove Dice
- | Teleport Dice
- | CreateItem (Maybe Int) CStore (GroupName ItemKind) TimerDice
- | DestroyItem Int Int CStore (GroupName ItemKind)
- | ConsumeItems [(Int, GroupName ItemKind)] [(Int, GroupName ItemKind)]
- | DropItem Int Int CStore (GroupName ItemKind)
- | Recharge Int Dice
- | Discharge Int Dice
- | PolyItem
- | RerollItem
- | DupItem
- | Identify
- | Detect DetectKind Int
- | SendFlying ThrowMod
- | PushActor ThrowMod
- | PullActor ThrowMod
- | ApplyPerfume
- | AtMostOneOf [Effect]
- | OneOf [Effect]
- | OnSmash Effect
- | OnCombine Effect
- | OnUser Effect
- | NopEffect
- | AndEffect Effect Effect
- | OrEffect Effect Effect
- | SeqEffect [Effect]
- | When Condition Effect
- | Unless Condition Effect
- | IfThenElse Condition Effect Effect
- | VerbNoLonger Text Text
- | VerbMsg Text Text
- | VerbMsgFail Text Text
- data Condition
- data DetectKind
- data TimerDice
- data ThrowMod = ThrowMod {
- throwVelocity :: Int
- throwLinger :: Int
- throwHP :: Int
- data ItemSymbolsUsedInEngine = ItemSymbolsUsedInEngine {
- rsymbolProjectile :: ContentSymbol ItemKind
- rsymbolLight :: ContentSymbol ItemKind
- rsymbolTool :: ContentSymbol ItemKind
- rsymbolSpecial :: ContentSymbol ItemKind
- rsymbolGold :: ContentSymbol ItemKind
- rsymbolNecklace :: ContentSymbol ItemKind
- rsymbolRing :: ContentSymbol ItemKind
- rsymbolPotion :: ContentSymbol ItemKind
- rsymbolFlask :: ContentSymbol ItemKind
- rsymbolScroll :: ContentSymbol ItemKind
- rsymbolTorsoArmor :: ContentSymbol ItemKind
- rsymbolMiscArmor :: ContentSymbol ItemKind
- rsymbolClothes :: ContentSymbol ItemKind
- rsymbolShield :: ContentSymbol ItemKind
- rsymbolPolearm :: ContentSymbol ItemKind
- rsymbolEdged :: ContentSymbol ItemKind
- rsymbolHafted :: ContentSymbol ItemKind
- rsymbolWand :: ContentSymbol ItemKind
- rsymbolFood :: ContentSymbol ItemKind
- emptyItemSymbolsUsedInEngine :: ItemSymbolsUsedInEngine
- boostItemKindList :: SMGen -> [ItemKind] -> [ItemKind]
- forApplyEffect :: Effect -> Bool
- forDamageEffect :: Effect -> Bool
- isDamagingKind :: ItemKind -> Bool
- strengthOnCombine :: ItemKind -> [Effect]
- strengthOnSmash :: ItemKind -> [Effect]
- getDropOrgans :: ItemKind -> [GroupName ItemKind]
- getMandatoryPresentAsFromKind :: ItemKind -> Maybe (GroupName ItemKind)
- isEffEscape :: Effect -> Bool
- isEffEscapeOrAscend :: Effect -> Bool
- timeoutAspect :: Aspect -> Bool
- orEffect :: Effect -> Bool
- onSmashEffect :: Effect -> Bool
- onCombineEffect :: Effect -> Bool
- alwaysDudEffect :: Effect -> Bool
- damageUsefulness :: ItemKind -> Double
- verbMsgNoLonger :: Text -> Effect
- verbMsgLess :: Text -> Effect
- toVelocity :: Int -> Aspect
- toLinger :: Int -> Aspect
- timerNone :: TimerDice
- isTimerNone :: TimerDice -> Bool
- foldTimer :: a -> (Dice -> a) -> (Dice -> a) -> TimerDice -> a
- toOrganBad :: GroupName ItemKind -> Dice -> Effect
- toOrganGood :: GroupName ItemKind -> Dice -> Effect
- toOrganNoTimer :: GroupName ItemKind -> Effect
- validateSingle :: ItemSymbolsUsedInEngine -> ItemKind -> [Text]
- mandatoryGroups :: [GroupName ItemKind]
- mandatoryGroupsSingleton :: [GroupName ItemKind]
- boostItemKind :: ItemKind -> ItemKind
- onSmashOrCombineEffect :: Effect -> Bool
- validateAll :: [ItemKind] -> ContentData ItemKind -> [Text]
- validateDups :: ItemKind -> Aspect -> [Text]
- validateDamage :: Dice -> [Text]
Documentation
pattern COMMON_ITEM :: GroupName ItemKind Source #
pattern S_BONUS_HP :: GroupName ItemKind Source #
pattern S_IMPRESSED :: GroupName ItemKind Source #
pattern S_CURRENCY :: GroupName ItemKind Source #
pattern CRAWL_ITEM :: GroupName ItemKind Source #
pattern ANY_SCROLL :: GroupName ItemKind Source #
pattern ANY_POTION :: GroupName ItemKind Source #
pattern ANY_JEWELRY :: GroupName ItemKind Source #
pattern S_SINGLE_SPARK :: GroupName ItemKind Source #
pattern S_FRAGRANCE :: GroupName ItemKind Source #
pattern UNREPORTED_INVENTORY :: GroupName 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
.
ItemKind | |
|
makeData :: ItemSymbolsUsedInEngine -> [ItemKind] -> [GroupName ItemKind] -> [GroupName ItemKind] -> ContentData ItemKind 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.
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
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.
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)] |
|
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 |
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, |
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 |
VerbMsgFail Text Text | as |
Instances
data DetectKind Source #
Instances
Eq DetectKind Source # | |
Defined in Game.LambdaHack.Content.ItemKind (==) :: DetectKind -> DetectKind -> Bool # (/=) :: DetectKind -> DetectKind -> Bool # | |
Show DetectKind Source # | |
Defined in Game.LambdaHack.Content.ItemKind showsPrec :: Int -> DetectKind -> ShowS # show :: DetectKind -> String # showList :: [DetectKind] -> ShowS # |
Specification of how to randomly roll a timer at item creation to obtain a fixed timer for the item's lifetime.
Parameters modifying a throw of a projectile or flight of pushed actor. Not additive and don't start at 0.
ThrowMod | |
|
Instances
Eq ThrowMod Source # | |
Ord ThrowMod Source # | |
Defined in Game.LambdaHack.Content.ItemKind | |
Show ThrowMod Source # | |
Generic ThrowMod Source # | |
Binary ThrowMod Source # | |
Hashable ThrowMod Source # | |
Defined in Game.LambdaHack.Content.ItemKind | |
type Rep ThrowMod Source # | |
Defined in Game.LambdaHack.Content.ItemKind type Rep ThrowMod = D1 ('MetaData "ThrowMod" "Game.LambdaHack.Content.ItemKind" "LambdaHack-0.11.0.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)))) |
data ItemSymbolsUsedInEngine Source #
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.
strengthOnCombine :: ItemKind -> [Effect] Source #
strengthOnSmash :: ItemKind -> [Effect] Source #
isEffEscape :: Effect -> Bool Source #
isEffEscapeOrAscend :: Effect -> Bool Source #
timeoutAspect :: Aspect -> Bool Source #
onSmashEffect :: Effect -> Bool Source #
onCombineEffect :: Effect -> Bool Source #
alwaysDudEffect :: Effect -> Bool Source #
damageUsefulness :: ItemKind -> Double Source #
verbMsgNoLonger :: Text -> Effect Source #
verbMsgLess :: Text -> Effect Source #
toVelocity :: Int -> Aspect Source #
isTimerNone :: TimerDice -> Bool Source #
validateSingle :: ItemSymbolsUsedInEngine -> ItemKind -> [Text] Source #
Catch invalid item kind definitions.
Internal operations
boostItemKind :: ItemKind -> ItemKind Source #
onSmashOrCombineEffect :: Effect -> Bool Source #
validateAll :: [ItemKind] -> ContentData ItemKind -> [Text] Source #
Validate all item kinds.
validateDamage :: Dice -> [Text] Source #