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

Safe HaskellNone
LanguageHaskell2010

Game.LambdaHack.Common.Faction

Contents

Description

Factions taking part in the game: e.g., two human players controlling the hero faction battling the monster and the animal factions.

Synopsis

Documentation

type FactionDict = EnumMap FactionId Faction Source #

All factions in the game, indexed by faction identifier.

data Faction Source #

Constructors

Faction 

Fields

Instances

Eq Faction Source # 

Methods

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

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

Ord Faction Source # 
Show Faction Source # 
Generic Faction Source # 

Associated Types

type Rep Faction :: * -> * #

Methods

from :: Faction -> Rep Faction x #

to :: Rep Faction x -> Faction #

Binary Faction Source # 

Methods

put :: Faction -> Put #

get :: Get Faction #

putList :: [Faction] -> Put #

type Rep Faction Source # 

data Diplomacy Source #

Diplomacy states. Higher overwrite lower in case of asymmetric content.

Constructors

Unknown 
Neutral 
Alliance 
War 

Instances

Enum Diplomacy Source # 
Eq Diplomacy Source # 
Ord Diplomacy Source # 
Show Diplomacy Source # 
Generic Diplomacy Source # 

Associated Types

type Rep Diplomacy :: * -> * #

Binary Diplomacy Source # 
type Rep Diplomacy Source # 
type Rep Diplomacy = D1 (MetaData "Diplomacy" "Game.LambdaHack.Common.Faction" "LambdaHack-0.6.0.0-KKqNxYnoEMa5Wo2qfudFog" False) ((:+:) ((:+:) (C1 (MetaCons "Unknown" PrefixI False) U1) (C1 (MetaCons "Neutral" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Alliance" PrefixI False) U1) (C1 (MetaCons "War" PrefixI False) U1)))

data Status Source #

Current game status.

Constructors

Status 

Fields

Instances

Eq Status Source # 

Methods

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

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

Ord Status Source # 
Show Status Source # 
Generic Status Source # 

Associated Types

type Rep Status :: * -> * #

Methods

from :: Status -> Rep Status x #

to :: Rep Status x -> Status #

Binary Status Source # 

Methods

put :: Status -> Put #

get :: Get Status #

putList :: [Status] -> Put #

type Rep Status Source # 
type Rep Status = D1 (MetaData "Status" "Game.LambdaHack.Common.Faction" "LambdaHack-0.6.0.0-KKqNxYnoEMa5Wo2qfudFog" False) (C1 (MetaCons "Status" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "stOutcome") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Outcome)) ((:*:) (S1 (MetaSel (Just Symbol "stDepth") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) (S1 (MetaSel (Just Symbol "stNewGame") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (GroupName ModeKind)))))))

data Target Source #

The type of na actor target.

Constructors

TEnemy !ActorId !Bool

target an actor; cycle only trough seen foes, unless the flag is set

TPoint !TGoal !LevelId !Point

target a concrete spot

TVector !Vector

target position relative to actor

Instances

Eq Target Source # 

Methods

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

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

Ord Target Source # 
Show Target Source # 
Generic Target Source # 

Associated Types

type Rep Target :: * -> * #

Methods

from :: Target -> Rep Target x #

to :: Rep Target x -> Target #

Binary Target Source # 

Methods

put :: Target -> Put #

get :: Get Target #

putList :: [Target] -> Put #

type Rep Target Source # 

data TGoal Source #

Constructors

TEnemyPos !ActorId !Bool

last seen position of the targeted actor

TEmbed !ItemBag !Point

in TPoint (TEmbed bag p) _ q usually bag is embbedded in p and q is an adjacent open tile

TItem !ItemBag 
TSmell 
TUnknown 
TKnown 
TAny 

Instances

Eq TGoal Source # 

Methods

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

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

Ord TGoal Source # 

Methods

compare :: TGoal -> TGoal -> Ordering #

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

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

(>) :: TGoal -> TGoal -> Bool #

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

max :: TGoal -> TGoal -> TGoal #

min :: TGoal -> TGoal -> TGoal #

Show TGoal Source # 

Methods

showsPrec :: Int -> TGoal -> ShowS #

show :: TGoal -> String #

showList :: [TGoal] -> ShowS #

Generic TGoal Source # 

Associated Types

type Rep TGoal :: * -> * #

Methods

from :: TGoal -> Rep TGoal x #

to :: Rep TGoal x -> TGoal #

Binary TGoal Source # 

Methods

put :: TGoal -> Put #

get :: Get TGoal #

putList :: [TGoal] -> Put #

type Rep TGoal Source # 

data Challenge Source #

Constructors

Challenge 

Fields

  • cdiff :: !Int

    game difficulty level (HP bonus or malus)

  • cwolf :: !Bool

    lone wolf challenge (only one starting character)

  • cfish :: !Bool

    cold fish challenge (no healing from enemies)

isHorrorFact :: Faction -> Bool Source #

Tell whether the faction consists of summoned horrors only.

Horror player is special, for summoned actors that don't belong to any of the main players of a given game. E.g., animals summoned during a skirmish game between two hero factions land in the horror faction. In every game, either all factions for which summoning items exist should be present or a horror player should be added to host them.

isAtWar :: Faction -> FactionId -> Bool Source #

Check if factions are at war. Assumes symmetry.

isAllied :: Faction -> FactionId -> Bool Source #

Check if factions are allied. Assumes symmetry.

Internal operations