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

Game.LambdaHack.Content.ModeKind

Description

The type of kinds of game modes.

Synopsis

Documentation

data ModeKind Source #

Game mode specification.

Constructors

ModeKind 

Fields

Instances

Instances details
Show ModeKind Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

type Caves = [([Int], [GroupName CaveKind])] Source #

Requested cave groups for particular level intervals.

data Roster Source #

The specification of players for the game mode.

Constructors

Roster 

Fields

Instances

Instances details
Show Roster Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

newtype TeamContinuity Source #

Team continuity index. Starting with 1, lower than 100.

Constructors

TeamContinuity Int 

Instances

Instances details
Enum TeamContinuity Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

Eq TeamContinuity Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

Ord TeamContinuity Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

Show TeamContinuity Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

Generic TeamContinuity Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

Associated Types

type Rep TeamContinuity :: Type -> Type #

Binary TeamContinuity Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

type Rep TeamContinuity Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

type Rep TeamContinuity = D1 ('MetaData "TeamContinuity" "Game.LambdaHack.Content.ModeKind" "LambdaHack-0.10.3.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 player escaped the dungeon alive

Conquer

the player 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.ModeKind

Enum Outcome Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

Eq Outcome Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

Methods

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

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

Ord Outcome Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

Show Outcome Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

Generic Outcome Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

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.ModeKind

Methods

put :: Outcome -> Put #

get :: Get Outcome #

putList :: [Outcome] -> Put #

type Rep Outcome Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

type Rep Outcome = D1 ('MetaData "Outcome" "Game.LambdaHack.Content.ModeKind" "LambdaHack-0.10.3.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))))

type HiCondPoly = [HiSummand] Source #

Conditional polynomial representing score calculation for this player.

data HiIndeterminant Source #

Instances

Instances details
Eq HiIndeterminant Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

Show HiIndeterminant Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

Generic HiIndeterminant Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

Associated Types

type Rep HiIndeterminant :: Type -> Type #

Binary HiIndeterminant Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

type Rep HiIndeterminant Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

type Rep HiIndeterminant = D1 ('MetaData "HiIndeterminant" "Game.LambdaHack.Content.ModeKind" "LambdaHack-0.10.3.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))))

data Player Source #

Properties of a particular player.

Constructors

Player 

Fields

Instances

Instances details
Eq Player Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

Methods

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

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

Show Player Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

Generic Player Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

Associated Types

type Rep Player :: Type -> Type #

Methods

from :: Player -> Rep Player x #

to :: Rep Player x -> Player #

Binary Player Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

Methods

put :: Player -> Put #

get :: Get Player #

putList :: [Player] -> Put #

type Rep Player Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

data AutoLeader Source #

Constructors

AutoLeader 

Fields

  • autoDungeon :: Bool

    leader switching between levels is automatically done by the server and client is not permitted to change to leaders from other levels (the frequency of leader level switching done by the server is controlled by RuleKind.rleadLevelClips); if the flag is False, server still does a subset of the automatic switching, e.g., when the old leader dies and no other actor of the faction resides on his level, but the client (particularly UI) is expected to do changes as well

  • autoLevel :: Bool

    client is discouraged from leader switching (e.g., because non-leader actors have the same skills as leader); server is guaranteed to switch leader within a level very rarely, e.g., when the old leader dies; if the flag is False, server still does a subset of the automatic switching, but the client is expected to do more, because it's advantageous for that kind of a faction

Instances

Instances details
Eq AutoLeader Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

Show AutoLeader Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

Generic AutoLeader Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

Associated Types

type Rep AutoLeader :: Type -> Type #

Binary AutoLeader Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

type Rep AutoLeader Source # 
Instance details

Defined in Game.LambdaHack.Content.ModeKind

type Rep AutoLeader = D1 ('MetaData "AutoLeader" "Game.LambdaHack.Content.ModeKind" "LambdaHack-0.10.3.0-inplace" 'False) (C1 ('MetaCons "AutoLeader" 'PrefixI 'True) (S1 ('MetaSel ('Just "autoDungeon") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "autoLevel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool)))

Internal operations

validateSingle :: ModeKind -> [Text] Source #

Catch invalid game mode kind definitions.

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

Validate game mode kinds together.

validateSingleRoster :: Caves -> Roster -> [Text] Source #

Checks, in particular, that there is at least one faction with fneverEmpty or the game would get stuck as soon as the dungeon is devoid of actors.