LambdaHack-0.6.1.0: A game engine library for roguelike dungeon crawlers

Safe HaskellNone
LanguageHaskell2010

Game.LambdaHack.Common.Actor

Contents

Description

Actors in the game: heroes, monsters, etc. No operation in this module involves the State or Action type.

Synopsis

Actor identifiers and related operations

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

Chance that a new monster is generated. Currently depends on the number of monsters already present, and on the level. In the future, the strength of the character and the strength of the monsters present could further influence the chance, and the chance could also affect which monster is generated. How many and which monsters are generated will also depend on the cave kind used to build the level.

The Actor type

data Actor Source #

Actor properties that are changing throughout the game. If they are dublets of properties from ActorKind, they are usually modified temporarily, but tend to return to the original value from ActorKind over time. E.g., HP.

Constructors

Actor 

Fields

Instances

Eq Actor Source # 

Methods

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

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

Show Actor Source # 

Methods

showsPrec :: Int -> Actor -> ShowS #

show :: Actor -> String #

showList :: [Actor] -> ShowS #

Generic Actor Source # 

Associated Types

type Rep Actor :: * -> * #

Methods

from :: Actor -> Rep Actor x #

to :: Rep Actor x -> Actor #

Binary Actor Source # 

Methods

put :: Actor -> Put #

get :: Get Actor #

putList :: [Actor] -> Put #

type Rep Actor Source # 
type Rep Actor = D1 * (MetaData "Actor" "Game.LambdaHack.Common.Actor" "LambdaHack-0.6.1.0-HURqEs4cFyW7LJywblRLqn" False) (C1 * (MetaCons "Actor" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "btrunk") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ItemId)) (S1 * (MetaSel (Just Symbol "bhp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int64))) ((:*:) * (S1 * (MetaSel (Just Symbol "bhpDelta") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ResDelta)) (S1 * (MetaSel (Just Symbol "bcalm") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int64)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "bcalmDelta") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ResDelta)) (S1 * (MetaSel (Just Symbol "bpos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Point))) ((:*:) * (S1 * (MetaSel (Just Symbol "boldpos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Point))) (S1 * (MetaSel (Just Symbol "blid") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * LevelId))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "bfid") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * FactionId)) (S1 * (MetaSel (Just Symbol "btrajectory") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ([Vector], Speed))))) ((:*:) * (S1 * (MetaSel (Just Symbol "borgan") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ItemBag)) (S1 * (MetaSel (Just Symbol "beqp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ItemBag)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "binv") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ItemBag)) (S1 * (MetaSel (Just Symbol "bweapon") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "bwait") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "bproj") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Bool)))))))

data ResDelta Source #

Constructors

ResDelta 

Fields

Instances

Eq ResDelta Source # 
Show ResDelta Source # 
Generic ResDelta Source # 

Associated Types

type Rep ResDelta :: * -> * #

Methods

from :: ResDelta -> Rep ResDelta x #

to :: Rep ResDelta x -> ResDelta #

Binary ResDelta Source # 

Methods

put :: ResDelta -> Put #

get :: Get ResDelta #

putList :: [ResDelta] -> Put #

type Rep ResDelta Source # 
type Rep ResDelta = D1 * (MetaData "ResDelta" "Game.LambdaHack.Common.Actor" "LambdaHack-0.6.1.0-HURqEs4cFyW7LJywblRLqn" False) (C1 * (MetaCons "ResDelta" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "resCurrentTurn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Int64, Int64))) (S1 * (MetaSel (Just Symbol "resPreviousTurn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Int64, Int64)))))

actorTemplate :: ItemId -> Int64 -> Int64 -> Point -> LevelId -> FactionId -> Actor Source #

A template for a new actor.

braced :: Actor -> Bool Source #

Whether an actor is braced for combat this clip.

waitedLastTurn :: Actor -> Bool Source #

The actor waited last turn.

Assorted

type ActorDict = EnumMap ActorId Actor Source #

All actors on the level, indexed by actor identifier.

smellTimeout :: Delta Time Source #

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