| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Game.LambdaHack.Content.ModeKind
Contents
Description
The type of kinds of game modes.
Synopsis
- pattern CAMPAIGN_SCENARIO :: GroupName ModeKind
- pattern INSERT_COIN :: GroupName ModeKind
- pattern NO_CONFIRMS :: GroupName ModeKind
- data ModeKind = ModeKind {}
- makeData :: [ModeKind] -> [GroupName ModeKind] -> [GroupName ModeKind] -> ContentData ModeKind
- type Caves = [([Int], [GroupName CaveKind])]
- data Roster = Roster {
- rosterList :: [(Player, Maybe TeamContinuity, [(Int, Dice, GroupName ItemKind)])]
- rosterEnemy :: [(Text, Text)]
- rosterAlly :: [(Text, Text)]
- newtype TeamContinuity = TeamContinuity Int
- data Outcome
- type HiCondPoly = [HiSummand]
- type HiSummand = (HiPolynomial, [Outcome])
- type HiPolynomial = [(HiIndeterminant, Double)]
- data HiIndeterminant
- data Player = Player {
- fname :: Text
- fgroups :: [GroupName ItemKind]
- fskillsOther :: Skills
- fcanEscape :: Bool
- fneverEmpty :: Bool
- fhiCondPoly :: HiCondPoly
- fhasGender :: Bool
- fdoctrine :: Doctrine
- fleaderMode :: LeaderMode
- fhasUI :: Bool
- data LeaderMode
- data AutoLeader = AutoLeader {
- autoDungeon :: Bool
- autoLevel :: Bool
- teamExplorer :: TeamContinuity
- victoryOutcomes :: [Outcome]
- deafeatOutcomes :: [Outcome]
- nameOutcomePast :: Outcome -> Text
- nameOutcomeVerb :: Outcome -> Text
- endMessageOutcome :: Outcome -> Text
- screensave :: AutoLeader -> ModeKind -> ModeKind
- validateSingle :: ModeKind -> [Text]
- validateAll :: [ModeKind] -> ContentData ModeKind -> [Text]
- validateSingleRoster :: Caves -> Roster -> [Text]
- validateSinglePlayer :: Player -> [Text]
- mandatoryGroups :: [GroupName ModeKind]
Documentation
pattern CAMPAIGN_SCENARIO :: GroupName ModeKind Source #
pattern INSERT_COIN :: GroupName ModeKind Source #
pattern NO_CONFIRMS :: GroupName ModeKind Source #
Game mode specification.
Constructors
| ModeKind | |
Fields
| |
makeData :: [ModeKind] -> [GroupName ModeKind] -> [GroupName ModeKind] -> ContentData ModeKind Source #
type Caves = [([Int], [GroupName CaveKind])] Source #
Requested cave groups for particular level intervals.
The specification of players for the game mode.
Constructors
| Roster | |
Fields
| |
newtype TeamContinuity Source #
Team continuity index. Starting with 1, lower than 100.
Constructors
| TeamContinuity Int |
Instances
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
| Bounded Outcome Source # | |
| Enum Outcome Source # | |
| Eq Outcome Source # | |
| Ord Outcome Source # | |
Defined in Game.LambdaHack.Content.ModeKind | |
| Show Outcome Source # | |
| Generic Outcome Source # | |
| Binary Outcome Source # | |
| type Rep Outcome Source # | |
Defined in Game.LambdaHack.Content.ModeKind type Rep Outcome = D1 ('MetaData "Outcome" "Game.LambdaHack.Content.ModeKind" "LambdaHack-0.10.2.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.
type HiSummand = (HiPolynomial, [Outcome]) Source #
type HiPolynomial = [(HiIndeterminant, Double)] Source #
data HiIndeterminant Source #
Instances
Properties of a particular player.
Constructors
| Player | |
Fields
| |
Instances
data LeaderMode Source #
If a faction with LeaderUI and LeaderAI has any actor, it has a leader.
Constructors
| LeaderNull | faction can have no leader, is whole under AI control |
| LeaderAI AutoLeader | leader under AI control |
| LeaderUI AutoLeader | leader under UI control, assumes |
Instances
data AutoLeader Source #
Constructors
| AutoLeader | |
Fields
| |
Instances
| Eq AutoLeader Source # | |
Defined in Game.LambdaHack.Content.ModeKind | |
| Show AutoLeader Source # | |
Defined in Game.LambdaHack.Content.ModeKind Methods showsPrec :: Int -> AutoLeader -> ShowS # show :: AutoLeader -> String # showList :: [AutoLeader] -> ShowS # | |
| Generic AutoLeader Source # | |
Defined in Game.LambdaHack.Content.ModeKind Associated Types type Rep AutoLeader :: Type -> Type # | |
| Binary AutoLeader Source # | |
Defined in Game.LambdaHack.Content.ModeKind | |
| type Rep AutoLeader Source # | |
Defined in Game.LambdaHack.Content.ModeKind type Rep AutoLeader = D1 ('MetaData "AutoLeader" "Game.LambdaHack.Content.ModeKind" "LambdaHack-0.10.2.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))) | |
victoryOutcomes :: [Outcome] Source #
deafeatOutcomes :: [Outcome] Source #
nameOutcomePast :: Outcome -> Text Source #
nameOutcomeVerb :: Outcome -> Text Source #
endMessageOutcome :: Outcome -> Text Source #
screensave :: AutoLeader -> ModeKind -> ModeKind Source #
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.
validateSinglePlayer :: Player -> [Text] Source #