Safe Haskell | None |
---|---|
Language | Haskell2010 |
Factions taking part in the game, e.g., a hero faction, a monster faction and an animal faction.
Synopsis
- data FactionId
- type FactionDict = EnumMap FactionId Faction
- data Faction = Faction {}
- data Diplomacy
- data Status = Status {}
- data Target
- data TGoal
- data Challenge = Challenge {}
- gleader :: Faction -> Maybe ActorId
- tgtKindDescription :: Target -> Text
- isHorrorFact :: Faction -> Bool
- noRunWithMulti :: Faction -> Bool
- isAIFact :: Faction -> Bool
- autoDungeonLevel :: Faction -> (Bool, Bool)
- automatePlayer :: Bool -> Player -> Player
- isFoe :: FactionId -> Faction -> FactionId -> Bool
- isFriend :: FactionId -> Faction -> FactionId -> Bool
- difficultyBound :: Int
- difficultyDefault :: Int
- difficultyCoeff :: Int -> Int
- difficultyInverse :: Int -> Int
- defaultChallenge :: Challenge
- type Dipl = EnumMap FactionId Diplomacy
Documentation
A unique identifier of a faction in a game.
Instances
Enum FactionId Source # | |
Defined in Game.LambdaHack.Common.Misc succ :: FactionId -> FactionId # pred :: FactionId -> FactionId # fromEnum :: FactionId -> Int # enumFrom :: FactionId -> [FactionId] # enumFromThen :: FactionId -> FactionId -> [FactionId] # enumFromTo :: FactionId -> FactionId -> [FactionId] # enumFromThenTo :: FactionId -> FactionId -> FactionId -> [FactionId] # | |
Eq FactionId Source # | |
Ord FactionId Source # | |
Defined in Game.LambdaHack.Common.Misc | |
Show FactionId Source # | |
Binary FactionId Source # | |
Hashable FactionId Source # | |
Defined in Game.LambdaHack.Common.Misc |
type FactionDict = EnumMap FactionId Faction Source #
All factions in the game, indexed by faction identifier.
The faction datatype.
Faction | |
|
Instances
Diplomacy states. Higher overwrite lower in case of asymmetric content.
Instances
Enum Diplomacy Source # | |
Defined in Game.LambdaHack.Common.Faction succ :: Diplomacy -> Diplomacy # pred :: Diplomacy -> Diplomacy # fromEnum :: Diplomacy -> Int # enumFrom :: Diplomacy -> [Diplomacy] # enumFromThen :: Diplomacy -> Diplomacy -> [Diplomacy] # enumFromTo :: Diplomacy -> Diplomacy -> [Diplomacy] # enumFromThenTo :: Diplomacy -> Diplomacy -> Diplomacy -> [Diplomacy] # | |
Eq Diplomacy Source # | |
Ord Diplomacy Source # | |
Defined in Game.LambdaHack.Common.Faction | |
Show Diplomacy Source # | |
Generic Diplomacy Source # | |
Binary Diplomacy Source # | |
type Rep Diplomacy Source # | |
Defined in Game.LambdaHack.Common.Faction type Rep Diplomacy = D1 (MetaData "Diplomacy" "Game.LambdaHack.Common.Faction" "LambdaHack-0.8.3.0-5WMRdylEY9jFLqYScFUab7" 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 :: * -> *))) |
Current game status.
Instances
Eq Status Source # | |
Ord Status Source # | |
Show Status Source # | |
Generic Status Source # | |
Binary Status Source # | |
type Rep Status Source # | |
Defined in Game.LambdaHack.Common.Faction type Rep Status = D1 (MetaData "Status" "Game.LambdaHack.Common.Faction" "LambdaHack-0.8.3.0-5WMRdylEY9jFLqYScFUab7" False) (C1 (MetaCons "Status" PrefixI True) (S1 (MetaSel (Just "stOutcome") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Outcome) :*: (S1 (MetaSel (Just "stDepth") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "stNewGame") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe (GroupName ModeKind)))))) |
The type of na actor target.
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
The goal of an actor.
TEnemyPos ActorId Bool | last seen position of the targeted actor |
TEmbed ItemBag Point | embedded item that can be triggered;
in |
TItem ItemBag | item lying on the ground |
TSmell | smell potentially left by enemies |
TUnknown | an unknown tile to be explored |
TKnown | a known tile to be patrolled |
TAny | an unspecified goal |
Instances
Instances
Eq Challenge Source # | |
Ord Challenge Source # | |
Defined in Game.LambdaHack.Common.Faction | |
Show Challenge Source # | |
Generic Challenge Source # | |
Binary Challenge Source # | |
type Rep Challenge Source # | |
Defined in Game.LambdaHack.Common.Faction type Rep Challenge = D1 (MetaData "Challenge" "Game.LambdaHack.Common.Faction" "LambdaHack-0.8.3.0-5WMRdylEY9jFLqYScFUab7" False) (C1 (MetaCons "Challenge" PrefixI True) (S1 (MetaSel (Just "cdiff") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int) :*: (S1 (MetaSel (Just "cwolf") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Bool) :*: S1 (MetaSel (Just "cfish") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Bool)))) |
tgtKindDescription :: Target -> Text Source #
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.
noRunWithMulti :: Faction -> Bool Source #
isFoe :: FactionId -> Faction -> FactionId -> Bool Source #
Check if factions are at war. Assumes symmetry.
isFriend :: FactionId -> Faction -> FactionId -> Bool Source #
Check if factions are allied or are the same faction. Assumes symmetry.
difficultyCoeff :: Int -> Int Source #
difficultyInverse :: Int -> Int Source #