LambdaHack-0.8.1.1: A game engine library for tactical squad ASCII roguelike dungeon crawlers

Safe HaskellNone
LanguageHaskell2010

Game.LambdaHack.Common.ItemAspect

Contents

Description

The type of item aspects and its operations.

Synopsis

Documentation

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

Defined in Game.LambdaHack.Common.ItemAspect

Methods

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

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

Ord Aspect Source # 
Instance details

Defined in Game.LambdaHack.Common.ItemAspect

Show Aspect Source # 
Instance details

Defined in Game.LambdaHack.Common.ItemAspect

Generic Aspect Source # 
Instance details

Defined in Game.LambdaHack.Common.ItemAspect

Associated Types

type Rep Aspect :: * -> * #

Methods

from :: Aspect -> Rep Aspect x #

to :: Rep Aspect x -> Aspect #

NFData Aspect Source # 
Instance details

Defined in Game.LambdaHack.Common.ItemAspect

Methods

rnf :: Aspect -> () #

type Rep Aspect Source # 
Instance details

Defined in Game.LambdaHack.Common.ItemAspect

type Rep Aspect = D1 (MetaData "Aspect" "Game.LambdaHack.Common.ItemAspect" "LambdaHack-0.8.1.1-B7gvMzZweCFaQcfmLNwOP" False) (((C1 (MetaCons "Timeout" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Dice)) :+: (C1 (MetaCons "AddHurtMelee" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Dice)) :+: C1 (MetaCons "AddArmorMelee" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Dice)))) :+: (C1 (MetaCons "AddArmorRanged" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Dice)) :+: (C1 (MetaCons "AddMaxHP" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Dice)) :+: C1 (MetaCons "AddMaxCalm" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Dice))))) :+: ((C1 (MetaCons "AddSpeed" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Dice)) :+: (C1 (MetaCons "AddSight" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Dice)) :+: C1 (MetaCons "AddSmell" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Dice)))) :+: ((C1 (MetaCons "AddShine" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Dice)) :+: C1 (MetaCons "AddNocto" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Dice))) :+: (C1 (MetaCons "AddAggression" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Dice)) :+: C1 (MetaCons "AddAbility" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Ability) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Dice))))))

data AspectRecord Source #

Record of sums of aspect values of an item, container, actor, etc.

Instances
Eq AspectRecord Source # 
Instance details

Defined in Game.LambdaHack.Common.ItemAspect

Ord AspectRecord Source # 
Instance details

Defined in Game.LambdaHack.Common.ItemAspect

Show AspectRecord Source # 
Instance details

Defined in Game.LambdaHack.Common.ItemAspect

Generic AspectRecord Source # 
Instance details

Defined in Game.LambdaHack.Common.ItemAspect

Associated Types

type Rep AspectRecord :: * -> * #

Binary AspectRecord Source # 
Instance details

Defined in Game.LambdaHack.Common.ItemAspect

Hashable AspectRecord Source # 
Instance details

Defined in Game.LambdaHack.Common.ItemAspect

type Rep AspectRecord Source # 
Instance details

Defined in Game.LambdaHack.Common.ItemAspect

type Rep AspectRecord = D1 (MetaData "AspectRecord" "Game.LambdaHack.Common.ItemAspect" "LambdaHack-0.8.1.1-B7gvMzZweCFaQcfmLNwOP" False) (C1 (MetaCons "AspectRecord" PrefixI True) (((S1 (MetaSel (Just "aTimeout") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int) :*: (S1 (MetaSel (Just "aHurtMelee") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "aArmorMelee") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int))) :*: (S1 (MetaSel (Just "aArmorRanged") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int) :*: (S1 (MetaSel (Just "aMaxHP") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "aMaxCalm") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int)))) :*: ((S1 (MetaSel (Just "aSpeed") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int) :*: (S1 (MetaSel (Just "aSight") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "aSmell") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int))) :*: ((S1 (MetaSel (Just "aShine") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "aNocto") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int)) :*: (S1 (MetaSel (Just "aAggression") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "aSkills") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Skills))))))

data KindMean Source #

Partial information about an item, deduced from its item kind. These are assigned to each ItemKind. The kmConst flag says whether the item's aspects are constant rather than random or dependent on item creation dungeon level.

Constructors

KindMean 

Fields

Instances
Eq KindMean Source # 
Instance details

Defined in Game.LambdaHack.Common.ItemAspect

Ord KindMean Source # 
Instance details

Defined in Game.LambdaHack.Common.ItemAspect

Show KindMean Source # 
Instance details

Defined in Game.LambdaHack.Common.ItemAspect

Generic KindMean Source # 
Instance details

Defined in Game.LambdaHack.Common.ItemAspect

Associated Types

type Rep KindMean :: * -> * #

Methods

from :: KindMean -> Rep KindMean x #

to :: Rep KindMean x -> KindMean #

type Rep KindMean Source # 
Instance details

Defined in Game.LambdaHack.Common.ItemAspect

type Rep KindMean = D1 (MetaData "KindMean" "Game.LambdaHack.Common.ItemAspect" "LambdaHack-0.8.1.1-B7gvMzZweCFaQcfmLNwOP" False) (C1 (MetaCons "KindMean" PrefixI True) (S1 (MetaSel (Just "kmConst") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Bool) :*: S1 (MetaSel (Just "kmMean") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 AspectRecord)))

data ItemSeed Source #

A seed for rolling aspects of an item Clients have partial knowledge of how item ids map to the seeds. They gain knowledge by identifying items.

data EqpSlot Source #

AI and UI hints about the role of the item.

Instances
Bounded EqpSlot Source # 
Instance details

Defined in Game.LambdaHack.Common.ItemAspect

Enum EqpSlot Source # 
Instance details

Defined in Game.LambdaHack.Common.ItemAspect

Eq EqpSlot Source # 
Instance details

Defined in Game.LambdaHack.Common.ItemAspect

Methods

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

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

Ord EqpSlot Source # 
Instance details

Defined in Game.LambdaHack.Common.ItemAspect

Show EqpSlot Source # 
Instance details

Defined in Game.LambdaHack.Common.ItemAspect

Generic EqpSlot Source # 
Instance details

Defined in Game.LambdaHack.Common.ItemAspect

Associated Types

type Rep EqpSlot :: * -> * #

Methods

from :: EqpSlot -> Rep EqpSlot x #

to :: Rep EqpSlot x -> EqpSlot #

NFData EqpSlot Source # 
Instance details

Defined in Game.LambdaHack.Common.ItemAspect

Methods

rnf :: EqpSlot -> () #

type Rep EqpSlot Source # 
Instance details

Defined in Game.LambdaHack.Common.ItemAspect

type Rep EqpSlot = D1 (MetaData "EqpSlot" "Game.LambdaHack.Common.ItemAspect" "LambdaHack-0.8.1.1-B7gvMzZweCFaQcfmLNwOP" 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 :: * -> *))))))

Internal operations