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

Game.LambdaHack.Content.FactionKind

Description

The type of kinds of factions present in a game, both human and computer-controlled.

Synopsis

Documentation

data FactionKind Source #

Properties of a particular faction.

Constructors

FactionKind 

Fields

  • fname :: Text

    name of the faction

  • ffreq :: Freqs FactionKind

    frequency within groups

  • fteam :: TeamContinuity

    the team the faction identifies with across games and modes

  • fgroups :: Freqs ItemKind

    names of actor groups that may naturally fall under faction's control, e.g., upon spawning; make sure all groups that may ever continuousely generate actors, e.g., through spawning or summoning, are mentioned in at least one faction kind; groups of initial faction actors don't need to be included

  • fskillsOther :: Skills

    fixed skill modifiers to the non-leader actors; also summed with skills implied by fdoctrine (which is not fixed)

  • fcanEscape :: Bool

    the faction can escape the dungeon

  • fneverEmpty :: Bool

    the faction declared killed if no actors

  • fhiCondPoly :: HiCondPoly

    score formula (conditional polynomial)

  • fhasGender :: Bool

    whether actors have gender

  • finitDoctrine :: Doctrine

    initial faction's non-leaders doctrine

  • fspawnsFast :: Bool

    spawns fast enough that switching pointman to another level to optimize spawning is a winning tactics, which would spoil the fun, so switching is disabled in UI and AI clients

  • fhasPointman :: Bool

    whether the faction can have a pointman

  • fhasUI :: Bool

    does the faction have a UI client (for control or passive observation)

  • finitUnderAI :: Bool

    is the faction initially under AI control

  • fenemyTeams :: [TeamContinuity]

    teams starting at war with the faction

  • falliedTeams :: [TeamContinuity]

    teams starting allied with the faction

Instances

Instances details
Eq FactionKind Source # 
Instance details

Defined in Game.LambdaHack.Content.FactionKind

Show FactionKind Source # 
Instance details

Defined in Game.LambdaHack.Content.FactionKind

Generic FactionKind Source # 
Instance details

Defined in Game.LambdaHack.Content.FactionKind

Associated Types

type Rep FactionKind :: Type -> Type #

Binary FactionKind Source # 
Instance details

Defined in Game.LambdaHack.Content.FactionKind

type Rep FactionKind Source # 
Instance details

Defined in Game.LambdaHack.Content.FactionKind

type Rep FactionKind = D1 ('MetaData "FactionKind" "Game.LambdaHack.Content.FactionKind" "LambdaHack-0.11.0.0-inplace" 'False) (C1 ('MetaCons "FactionKind" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "fname") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "ffreq") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Freqs FactionKind))) :*: (S1 ('MetaSel ('Just "fteam") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TeamContinuity) :*: S1 ('MetaSel ('Just "fgroups") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Freqs ItemKind)))) :*: ((S1 ('MetaSel ('Just "fskillsOther") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Skills) :*: S1 ('MetaSel ('Just "fcanEscape") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "fneverEmpty") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "fhiCondPoly") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 HiCondPoly)))) :*: (((S1 ('MetaSel ('Just "fhasGender") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "finitDoctrine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Doctrine)) :*: (S1 ('MetaSel ('Just "fspawnsFast") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "fhasPointman") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool))) :*: ((S1 ('MetaSel ('Just "fhasUI") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "finitUnderAI") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "fenemyTeams") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [TeamContinuity]) :*: S1 ('MetaSel ('Just "falliedTeams") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [TeamContinuity]))))))

type HiCondPoly = [HiSummand] Source #

Conditional polynomial representing score calculation for this faction.

data HiIndeterminant Source #

Instances

Instances details
Eq HiIndeterminant Source # 
Instance details

Defined in Game.LambdaHack.Content.FactionKind

Show HiIndeterminant Source # 
Instance details

Defined in Game.LambdaHack.Content.FactionKind

Generic HiIndeterminant Source # 
Instance details

Defined in Game.LambdaHack.Content.FactionKind

Associated Types

type Rep HiIndeterminant :: Type -> Type #

Binary HiIndeterminant Source # 
Instance details

Defined in Game.LambdaHack.Content.FactionKind

type Rep HiIndeterminant Source # 
Instance details

Defined in Game.LambdaHack.Content.FactionKind

type Rep HiIndeterminant = D1 ('MetaData "HiIndeterminant" "Game.LambdaHack.Content.FactionKind" "LambdaHack-0.11.0.0-inplace" 'False) ((C1 ('MetaCons "HiConst" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HiLoot" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HiSprint" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "HiBlitz" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HiSurvival" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HiKill" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HiLoss" 'PrefixI 'False) (U1 :: Type -> Type))))

newtype TeamContinuity Source #

Team continuity index. Starting with 1. See the comment for FactionId.

Constructors

TeamContinuity Int 

Instances

Instances details
Enum TeamContinuity Source # 
Instance details

Defined in Game.LambdaHack.Content.FactionKind

Eq TeamContinuity Source # 
Instance details

Defined in Game.LambdaHack.Content.FactionKind

Ord TeamContinuity Source # 
Instance details

Defined in Game.LambdaHack.Content.FactionKind

Show TeamContinuity Source # 
Instance details

Defined in Game.LambdaHack.Content.FactionKind

Generic TeamContinuity Source # 
Instance details

Defined in Game.LambdaHack.Content.FactionKind

Associated Types

type Rep TeamContinuity :: Type -> Type #

Binary TeamContinuity Source # 
Instance details

Defined in Game.LambdaHack.Content.FactionKind

type Rep TeamContinuity Source # 
Instance details

Defined in Game.LambdaHack.Content.FactionKind

type Rep TeamContinuity = D1 ('MetaData "TeamContinuity" "Game.LambdaHack.Content.FactionKind" "LambdaHack-0.11.0.0-inplace" 'True) (C1 ('MetaCons "TeamContinuity" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

data Outcome Source #

Outcome of a game.

Constructors

Escape

the faction escaped the dungeon alive

Conquer

the faction won by eliminating all rivals

Defeated

the faction lost the game in another way

Killed

the faction was eliminated

Restart

game is restarted; the quitter quit

Camping

game is supended

Instances

Instances details
Bounded Outcome Source # 
Instance details

Defined in Game.LambdaHack.Content.FactionKind

Enum Outcome Source # 
Instance details

Defined in Game.LambdaHack.Content.FactionKind

Eq Outcome Source # 
Instance details

Defined in Game.LambdaHack.Content.FactionKind

Methods

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

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

Ord Outcome Source # 
Instance details

Defined in Game.LambdaHack.Content.FactionKind

Show Outcome Source # 
Instance details

Defined in Game.LambdaHack.Content.FactionKind

Generic Outcome Source # 
Instance details

Defined in Game.LambdaHack.Content.FactionKind

Associated Types

type Rep Outcome :: Type -> Type #

Methods

from :: Outcome -> Rep Outcome x #

to :: Rep Outcome x -> Outcome #

Binary Outcome Source # 
Instance details

Defined in Game.LambdaHack.Content.FactionKind

Methods

put :: Outcome -> Put #

get :: Get Outcome #

putList :: [Outcome] -> Put #

type Rep Outcome Source # 
Instance details

Defined in Game.LambdaHack.Content.FactionKind

type Rep Outcome = D1 ('MetaData "Outcome" "Game.LambdaHack.Content.FactionKind" "LambdaHack-0.11.0.0-inplace" 'False) ((C1 ('MetaCons "Escape" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Conquer" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Defeated" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Killed" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Restart" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Camping" 'PrefixI 'False) (U1 :: Type -> Type))))

Internal operations

validateAll :: [FactionKind] -> ContentData FactionKind -> [Text] Source #

Validate game faction kinds together.