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

Safe HaskellNone
LanguageHaskell2010

Game.LambdaHack.Definition.Ability

Contents

Description

Abilities of items, actors and factions.

Synopsis

Documentation

data Skill Source #

Actor and faction skills. They are a subset of actor aspects. See skillDesc for documentation.

Instances
Bounded Skill Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Enum Skill Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Eq Skill Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Methods

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

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

Ord Skill Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Methods

compare :: Skill -> Skill -> Ordering #

(<) :: Skill -> Skill -> Bool #

(<=) :: Skill -> Skill -> Bool #

(>) :: Skill -> Skill -> Bool #

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

max :: Skill -> Skill -> Skill #

min :: Skill -> Skill -> Skill #

Show Skill Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Methods

showsPrec :: Int -> Skill -> ShowS #

show :: Skill -> String #

showList :: [Skill] -> ShowS #

Generic Skill Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Associated Types

type Rep Skill :: Type -> Type #

Methods

from :: Skill -> Rep Skill x #

to :: Rep Skill x -> Skill #

Binary Skill Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Methods

put :: Skill -> Put #

get :: Get Skill #

putList :: [Skill] -> Put #

Hashable Skill Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Methods

hashWithSalt :: Int -> Skill -> Int #

hash :: Skill -> Int #

type Rep Skill Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

type Rep Skill = D1 (MetaData "Skill" "Game.LambdaHack.Definition.Ability" "LambdaHack-0.9.5.0-inplace" False) ((((C1 (MetaCons "SkMove" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SkMelee" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "SkDisplace" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "SkAlter" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SkWait" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "SkMoveItem" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "SkProject" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SkApply" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "SkSwimming" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "SkFlying" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SkHurtMelee" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "SkArmorMelee" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "SkArmorRanged" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SkMaxHP" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "SkMaxCalm" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "SkSpeed" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SkSight" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "SkSmell" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "SkShine" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SkNocto" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "SkHearing" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "SkAggression" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SkOdor" PrefixI False) (U1 :: Type -> Type))))))

data Skills Source #

Strength of particular skills. This is cumulative from actor organs and equipment and so pertain to an actor as well as to items.

This representation is sparse, so better than a record when there are more item kinds (with few skills) than actors (with many skills), especially if the number of skills grows as the engine is developed. It's also easier to code and maintain.

The tree is by construction sparse, so the derived equality is semantical.

Instances
Eq Skills Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Methods

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

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

Ord Skills Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Show Skills Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Generic Skills Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Associated Types

type Rep Skills :: Type -> Type #

Methods

from :: Skills -> Rep Skills x #

to :: Rep Skills x -> Skills #

Binary Skills Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Methods

put :: Skills -> Put #

get :: Get Skills #

putList :: [Skills] -> Put #

Hashable Skills Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Methods

hashWithSalt :: Int -> Skills -> Int #

hash :: Skills -> Int #

type Rep Skills Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

type Rep Skills = D1 (MetaData "Skills" "Game.LambdaHack.Definition.Ability" "LambdaHack-0.9.5.0-inplace" True) (C1 (MetaCons "Skills" PrefixI True) (S1 (MetaSel (Just "skills") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (EnumMap Skill Int))))

data Flag Source #

Item flag aspects.

Constructors

Fragile

as a projectile, break at target tile, even if no hit; also, at each periodic activation a copy is destroyed and all other copies require full cooldown (timeout)

Lobable

drop at target tile, even if no hit

Durable

don't break even when hitting or applying

Equipable

AI and UI flag: consider equipping (may or may not have EqpSlot, e.g., if the benefit is periodic)

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; also may be used for UI flavour or AI hints

Blast

the item is an explosion blast particle

Condition

item is a condition (buff or de-buff) of an actor and is displayed as such; this differs from belonging to the condition group, which doesn't guarantee display as a condition, but governs removal by items that drop condition

Unique

at most one copy can ever be generated

Periodic

at most one of any copies without cooldown (timeout) activates each turn; the cooldown required after activation is specified in Timeout (or is zero); the initial cooldown can also be specified as TimerDice in CreateItem effect; uniquely, this activation never destroys a copy, unless item is fragile; all this happens only for items in equipment or organs

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
Bounded Flag Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Enum Flag Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Methods

succ :: Flag -> Flag #

pred :: Flag -> Flag #

toEnum :: Int -> Flag #

fromEnum :: Flag -> Int #

enumFrom :: Flag -> [Flag] #

enumFromThen :: Flag -> Flag -> [Flag] #

enumFromTo :: Flag -> Flag -> [Flag] #

enumFromThenTo :: Flag -> Flag -> Flag -> [Flag] #

Eq Flag Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Methods

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

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

Ord Flag Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Methods

compare :: Flag -> Flag -> Ordering #

(<) :: Flag -> Flag -> Bool #

(<=) :: Flag -> Flag -> Bool #

(>) :: Flag -> Flag -> Bool #

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

max :: Flag -> Flag -> Flag #

min :: Flag -> Flag -> Flag #

Show Flag Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Methods

showsPrec :: Int -> Flag -> ShowS #

show :: Flag -> String #

showList :: [Flag] -> ShowS #

Generic Flag Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Associated Types

type Rep Flag :: Type -> Type #

Methods

from :: Flag -> Rep Flag x #

to :: Rep Flag x -> Flag #

Binary Flag Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Methods

put :: Flag -> Put #

get :: Get Flag #

putList :: [Flag] -> Put #

Hashable Flag Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Methods

hashWithSalt :: Int -> Flag -> Int #

hash :: Flag -> Int #

type Rep Flag Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

type Rep Flag = D1 (MetaData "Flag" "Game.LambdaHack.Definition.Ability" "LambdaHack-0.9.5.0-inplace" False) (((C1 (MetaCons "Fragile" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Lobable" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Durable" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Equipable" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Meleeable" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "Precious" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Blast" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Condition" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "Unique" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Periodic" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MinorEffects" PrefixI False) (U1 :: Type -> Type)))))

newtype Flags Source #

Constructors

Flags 

Fields

Instances
Eq Flags Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Methods

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

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

Ord Flags Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Methods

compare :: Flags -> Flags -> Ordering #

(<) :: Flags -> Flags -> Bool #

(<=) :: Flags -> Flags -> Bool #

(>) :: Flags -> Flags -> Bool #

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

max :: Flags -> Flags -> Flags #

min :: Flags -> Flags -> Flags #

Show Flags Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Methods

showsPrec :: Int -> Flags -> ShowS #

show :: Flags -> String #

showList :: [Flags] -> ShowS #

Generic Flags Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Associated Types

type Rep Flags :: Type -> Type #

Methods

from :: Flags -> Rep Flags x #

to :: Rep Flags x -> Flags #

Binary Flags Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Methods

put :: Flags -> Put #

get :: Get Flags #

putList :: [Flags] -> Put #

Hashable Flags Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Methods

hashWithSalt :: Int -> Flags -> Int #

hash :: Flags -> Int #

type Rep Flags Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

type Rep Flags = D1 (MetaData "Flags" "Game.LambdaHack.Definition.Ability" "LambdaHack-0.9.5.0-inplace" True) (C1 (MetaCons "Flags" PrefixI True) (S1 (MetaSel (Just "flags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (EnumSet Flag))))

data Tactic Source #

Tactic of non-leader actors. Apart of determining AI operation, each tactic implies a skill modifier, that is added to the non-leader skills defined in fskillsOther field of Player.

Constructors

TExplore

if enemy nearby, attack, if no items, etc., explore unknown

TFollow

always follow leader's target or his position if no target

TFollowNoItems

follow but don't do any item management nor use

TMeleeAndRanged

only melee and do ranged combat

TMeleeAdjacent

only melee (or wait)

TBlock

always only wait, even if enemy in melee range

TRoam

if enemy nearby, attack, if no items, etc., roam randomly

TPatrol

find an open and uncrowded area, patrol it according to sight radius and fallback temporarily to TRoam when enemy is seen by the faction and is within the actor's sight radius

Instances
Bounded Tactic Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Enum Tactic Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Eq Tactic Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Methods

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

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

Ord Tactic Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Show Tactic Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Generic Tactic Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Associated Types

type Rep Tactic :: Type -> Type #

Methods

from :: Tactic -> Rep Tactic x #

to :: Rep Tactic x -> Tactic #

Binary Tactic Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Methods

put :: Tactic -> Put #

get :: Get Tactic #

putList :: [Tactic] -> Put #

Hashable Tactic Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Methods

hashWithSalt :: Int -> Tactic -> Int #

hash :: Tactic -> Int #

type Rep Tactic Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

type Rep Tactic = D1 (MetaData "Tactic" "Game.LambdaHack.Definition.Ability" "LambdaHack-0.9.5.0-inplace" False) (((C1 (MetaCons "TExplore" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TFollow" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "TFollowNoItems" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TMeleeAndRanged" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "TMeleeAdjacent" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TBlock" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "TRoam" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TPatrol" PrefixI False) (U1 :: Type -> Type))))

data EqpSlot Source #

AI and UI hints about the role of the item.

Instances
Bounded EqpSlot Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Enum EqpSlot Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Eq EqpSlot Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Methods

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

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

Ord EqpSlot Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Show EqpSlot Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Generic EqpSlot Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Associated Types

type Rep EqpSlot :: Type -> Type #

Methods

from :: EqpSlot -> Rep EqpSlot x #

to :: Rep EqpSlot x -> EqpSlot #

Binary EqpSlot Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Methods

put :: EqpSlot -> Put #

get :: Get EqpSlot #

putList :: [EqpSlot] -> Put #

Hashable EqpSlot Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

Methods

hashWithSalt :: Int -> EqpSlot -> Int #

hash :: EqpSlot -> Int #

type Rep EqpSlot Source # 
Instance details

Defined in Game.LambdaHack.Definition.Ability

type Rep EqpSlot = D1 (MetaData "EqpSlot" "Game.LambdaHack.Definition.Ability" "LambdaHack-0.9.5.0-inplace" False) ((((C1 (MetaCons "EqpSlotMove" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "EqpSlotMelee" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "EqpSlotDisplace" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "EqpSlotAlter" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "EqpSlotWait" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "EqpSlotMoveItem" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "EqpSlotProject" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "EqpSlotApply" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "EqpSlotSwimming" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "EqpSlotFlying" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "EqpSlotHurtMelee" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "EqpSlotArmorMelee" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "EqpSlotArmorRanged" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "EqpSlotMaxHP" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "EqpSlotSpeed" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "EqpSlotSight" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "EqpSlotShine" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "EqpSlotMiscBonus" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "EqpSlotWeaponFast" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "EqpSlotWeaponBig" PrefixI False) (U1 :: Type -> Type))))))

Internal operations