LambdaHack-0.10.2.0: A game engine library for tactical squad ASCII roguelike dungeon crawlers
Safe HaskellNone
LanguageHaskell2010

Game.LambdaHack.Common.Actor

Description

Actors in the game: heroes, monsters, etc.

Synopsis

The Actor type, its components and operations on them

data Actor Source #

Actor attributes that are changing throughout the game. If they appear to be dublets of aspects from actor kinds, e.g. HP, they may be results of casting the dice specified in their respective actor kind and/or may be modified temporarily, but return to the original value from their respective kind over time.

Other properties of an actor, in particular its current aspects, are derived from the actor's trunk, organs and equipment. A class of the aspects, the boolean ones, are called flags. Another class are skills. Stats are a subclass that determines if particular actions are permitted for the actor (or faction).

Constructors

Actor 

Fields

Instances

Instances details
Eq Actor Source # 
Instance details

Defined in Game.LambdaHack.Common.Actor

Methods

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

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

Show Actor Source # 
Instance details

Defined in Game.LambdaHack.Common.Actor

Methods

showsPrec :: Int -> Actor -> ShowS #

show :: Actor -> String #

showList :: [Actor] -> ShowS #

Generic Actor Source # 
Instance details

Defined in Game.LambdaHack.Common.Actor

Associated Types

type Rep Actor :: Type -> Type #

Methods

from :: Actor -> Rep Actor x #

to :: Rep Actor x -> Actor #

Binary Actor Source # 
Instance details

Defined in Game.LambdaHack.Common.Actor

Methods

put :: Actor -> Put #

get :: Get Actor #

putList :: [Actor] -> Put #

type Rep Actor Source # 
Instance details

Defined in Game.LambdaHack.Common.Actor

type Rep Actor = D1 ('MetaData "Actor" "Game.LambdaHack.Common.Actor" "LambdaHack-0.10.2.0-inplace" 'False) (C1 ('MetaCons "Actor" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "btrunk") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ItemId) :*: S1 ('MetaSel ('Just "bnumber") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Int))) :*: (S1 ('MetaSel ('Just "bhp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int64) :*: S1 ('MetaSel ('Just "bhpDelta") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ResDelta))) :*: ((S1 ('MetaSel ('Just "bcalm") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int64) :*: S1 ('MetaSel ('Just "bcalmDelta") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ResDelta)) :*: (S1 ('MetaSel ('Just "bpos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Point) :*: S1 ('MetaSel ('Just "boldpos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Point))))) :*: (((S1 ('MetaSel ('Just "blid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 LevelId) :*: S1 ('MetaSel ('Just "bfid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 FactionId)) :*: (S1 ('MetaSel ('Just "btrajectory") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe ([Vector], Speed))) :*: S1 ('MetaSel ('Just "borgan") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ItemBag))) :*: ((S1 ('MetaSel ('Just "beqp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ItemBag) :*: S1 ('MetaSel ('Just "bweapon") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "bweapBenign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Just "bwatch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Watchfulness) :*: S1 ('MetaSel ('Just "bproj") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool)))))))

data ResDelta Source #

Representation of recent changes to HP of Calm of an actor. This is reset every time the actor perfoms an action, so this is aggregated over actor turn (move), not time turn. The resource changes recorded in the tuple are, respectively, negative and positive.

Constructors

ResDelta 

Fields

Instances

Instances details
Eq ResDelta Source # 
Instance details

Defined in Game.LambdaHack.Common.Actor

Show ResDelta Source # 
Instance details

Defined in Game.LambdaHack.Common.Actor

Generic ResDelta Source # 
Instance details

Defined in Game.LambdaHack.Common.Actor

Associated Types

type Rep ResDelta :: Type -> Type #

Methods

from :: ResDelta -> Rep ResDelta x #

to :: Rep ResDelta x -> ResDelta #

Binary ResDelta Source # 
Instance details

Defined in Game.LambdaHack.Common.Actor

Methods

put :: ResDelta -> Put #

get :: Get ResDelta #

putList :: [ResDelta] -> Put #

type Rep ResDelta Source # 
Instance details

Defined in Game.LambdaHack.Common.Actor

type Rep ResDelta = D1 ('MetaData "ResDelta" "Game.LambdaHack.Common.Actor" "LambdaHack-0.10.2.0-inplace" 'False) (C1 ('MetaCons "ResDelta" 'PrefixI 'True) (S1 ('MetaSel ('Just "resCurrentTurn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Int64, Int64)) :*: S1 ('MetaSel ('Just "resPreviousTurn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Int64, Int64))))

data Watchfulness Source #

Constructors

WWatch 
WWait Int 
WSleep 
WWake 

Instances

Instances details
Eq Watchfulness Source # 
Instance details

Defined in Game.LambdaHack.Common.Actor

Show Watchfulness Source # 
Instance details

Defined in Game.LambdaHack.Common.Actor

Generic Watchfulness Source # 
Instance details

Defined in Game.LambdaHack.Common.Actor

Associated Types

type Rep Watchfulness :: Type -> Type #

Binary Watchfulness Source # 
Instance details

Defined in Game.LambdaHack.Common.Actor

type Rep Watchfulness Source # 
Instance details

Defined in Game.LambdaHack.Common.Actor

type Rep Watchfulness = D1 ('MetaData "Watchfulness" "Game.LambdaHack.Common.Actor" "LambdaHack-0.10.2.0-inplace" 'False) ((C1 ('MetaCons "WWatch" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WWait" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int))) :+: (C1 ('MetaCons "WSleep" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WWake" 'PrefixI 'False) (U1 :: Type -> Type)))

gearSpeed :: Skills -> Speed Source #

The speed from organs and gear; being pushed is ignored.

actorDying :: Actor -> Bool Source #

Projectile that ran out of steam or collided with obstacle, dies. Even if it pierced through an obstacle, but lost its payload while altering the obstacle during piercing, it dies, too.

calmEnough :: Actor -> Skills -> Bool Source #

Check if actor calm enough to perform some actions.

If max Calm is zero, always holds, to permit removing disastrous equipped items, which would otherwise be stuck forever.

canSleep :: Skills -> Bool Source #

Has the skill and can wake up easily, so can sleep safely.

prefersSleep :: Skills -> Bool Source #

Can't loot, not too aggresive, so sometimes prefers to sleep instead of exploring.

Assorted

type ActorDict = EnumMap ActorId Actor Source #

All actors on the level, indexed by actor identifier.

monsterGenChance :: AbsDepth -> AbsDepth -> Int -> Int -> Rnd Bool Source #

Chance that a new monster is generated. Depends on the number of monsters already present, and on the level depth and its cave kind.

smellTimeout :: Delta Time Source #

How long until an actor's smell vanishes from a tile.