{-# LANGUAGE DeriveGeneric #-}
module Game.LambdaHack.Common.Faction
( FactionId, FactionDict, Faction(..), Diplomacy(..), Status(..)
, Target(..), TGoal(..), Challenge(..)
, gleader, tgtKindDescription, isHorrorFact
, noRunWithMulti, isAIFact, autoDungeonLevel, automatePlayer
, isFoe, isFriend
, difficultyBound, difficultyDefault, difficultyCoeff, difficultyInverse
, defaultChallenge
#ifdef EXPOSE_INTERNAL
, Dipl
#endif
) where
import Prelude ()
import Game.LambdaHack.Common.Prelude
import Data.Binary
import qualified Data.EnumMap.Strict as EM
import qualified Data.IntMap.Strict as IM
import GHC.Generics (Generic)
import qualified Game.LambdaHack.Common.Ability as Ability
import Game.LambdaHack.Common.Actor
import qualified Game.LambdaHack.Common.Color as Color
import Game.LambdaHack.Common.Item
import Game.LambdaHack.Common.Kind
import Game.LambdaHack.Common.Misc
import Game.LambdaHack.Common.Point
import Game.LambdaHack.Common.Vector
import Game.LambdaHack.Content.ItemKind (ItemKind)
import Game.LambdaHack.Content.ModeKind
type FactionDict = EM.EnumMap FactionId Faction
data Faction = Faction
{ gname :: Text
, gcolor :: Color.Color
, gplayer :: Player
, ginitial :: [(Int, Int, GroupName ItemKind)]
, gdipl :: Dipl
, gquit :: Maybe Status
, _gleader :: Maybe ActorId
, gsha :: ItemBag
, gvictims :: EM.EnumMap (ContentId ItemKind) Int
, gvictimsD :: EM.EnumMap (ContentId ModeKind)
(IM.IntMap (EM.EnumMap (ContentId ItemKind) Int))
}
deriving (Show, Eq, Generic)
instance Binary Faction
data Diplomacy =
Unknown
| Neutral
| Alliance
| War
deriving (Show, Eq, Ord, Enum, Generic)
instance Binary Diplomacy
type Dipl = EM.EnumMap FactionId Diplomacy
data Status = Status
{ stOutcome :: Outcome
, stDepth :: Int
, stNewGame :: Maybe (GroupName ModeKind)
}
deriving (Show, Eq, Ord, Generic)
instance Binary Status
data Target =
TEnemy ActorId Bool
| TPoint TGoal LevelId Point
| TVector Vector
deriving (Show, Eq, Ord, Generic)
instance Binary Target
data TGoal =
TEnemyPos ActorId Bool
| TEmbed ItemBag Point
| TItem ItemBag
| TSmell
| TUnknown
| TKnown
| TAny
deriving (Show, Eq, Ord, Generic)
instance Binary TGoal
data Challenge = Challenge
{ cdiff :: Int
, cwolf :: Bool
, cfish :: Bool
}
deriving (Show, Eq, Ord, Generic)
instance Binary Challenge
gleader :: Faction -> Maybe ActorId
gleader = _gleader
tgtKindDescription :: Target -> Text
tgtKindDescription tgt = case tgt of
TEnemy _ True -> "at actor"
TEnemy _ False -> "at enemy"
TPoint{} -> "at position"
TVector{} -> "with a vector"
isHorrorFact :: Faction -> Bool
isHorrorFact fact = nameOfHorrorFact `elem` fgroups (gplayer fact)
noRunWithMulti :: Faction -> Bool
noRunWithMulti fact =
let skillsOther = fskillsOther $ gplayer fact
in EM.findWithDefault 0 Ability.AbMove skillsOther >= 0
|| case fleaderMode (gplayer fact) of
LeaderNull -> True
LeaderAI AutoLeader{} -> True
LeaderUI AutoLeader{..} -> autoDungeon || autoLevel
isAIFact :: Faction -> Bool
isAIFact fact =
case fleaderMode (gplayer fact) of
LeaderNull -> True
LeaderAI _ -> True
LeaderUI _ -> False
autoDungeonLevel :: Faction -> (Bool, Bool)
autoDungeonLevel fact = case fleaderMode (gplayer fact) of
LeaderNull -> (False, False)
LeaderAI AutoLeader{..} -> (autoDungeon, autoLevel)
LeaderUI AutoLeader{..} -> (autoDungeon, autoLevel)
automatePlayer :: Bool -> Player -> Player
automatePlayer st pl =
let autoLeader False Player{fleaderMode=LeaderAI auto} = LeaderUI auto
autoLeader True Player{fleaderMode=LeaderUI auto} = LeaderAI auto
autoLeader _ Player{fleaderMode} = fleaderMode
in pl {fleaderMode = autoLeader st pl}
isFoe :: FactionId -> Faction -> FactionId -> Bool
isFoe fid1 fact1 fid2 =
fid1 /= fid2
&& War == EM.findWithDefault Unknown fid2 (gdipl fact1)
isAlly :: Faction -> FactionId -> Bool
{-# INLINE isAlly #-}
isAlly fact1 fid2 = Alliance == EM.findWithDefault Unknown fid2 (gdipl fact1)
isFriend :: FactionId -> Faction -> FactionId -> Bool
isFriend fid1 fact1 fid2 = fid1 == fid2 || isAlly fact1 fid2
difficultyBound :: Int
difficultyBound = 9
difficultyDefault :: Int
difficultyDefault = (1 + difficultyBound) `div` 2
difficultyCoeff :: Int -> Int
difficultyCoeff n = difficultyDefault - n
difficultyInverse :: Int -> Int
difficultyInverse n = difficultyBound + 1 - n
defaultChallenge :: Challenge
defaultChallenge = Challenge { cdiff = difficultyDefault
, cwolf = False
, cfish = False }