module Game.Werewolf.Game (
Game,
stage, round, players, boots, allowedVoters, divine, fallenAngelLynched, healUsed,
hunterRetaliated, jesterRevealed, passed, poison, poisonUsed, priorProtect, protect, roleModel,
scapegoatBlamed, see, votes,
Stage(..),
_FerinasGrunt, _GameOver, _HuntersTurn1, _HuntersTurn2, _Lynching, _OraclesTurn, _OrphansTurn,
_ProtectorsTurn, _ScapegoatsTurn, _SeersTurn, _Sunrise, _Sunset, _VillageDrunksTurn,
_VillagesTurn, _WerewolvesTurn, _WitchsTurn,
allStages,
stageCycle, stageAvailable,
newGame,
votee,
firstRound, secondRound, thirdRound,
getAllowedVoters, getPendingVoters,
hasAnyoneWon, hasFallenAngelWon, hasVillagersWon, hasWerewolvesWon,
) where
import Control.Lens hiding (isn't)
import Control.Lens.Extra
import Data.List.Extra
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Maybe
import Data.String
import Data.String.Humanise
import Data.Text (Text)
import Game.Werewolf.Player
import Prelude hiding (round)
data Game = Game
{ _stage :: Stage
, _round :: Int
, _players :: [Player]
, _boots :: Map Text [Text]
, _allowedVoters :: [Text]
, _divine :: Maybe Text
, _fallenAngelLynched :: Bool
, _healUsed :: Bool
, _hunterRetaliated :: Bool
, _jesterRevealed :: Bool
, _passed :: Bool
, _poison :: Maybe Text
, _poisonUsed :: Bool
, _priorProtect :: Maybe Text
, _protect :: Maybe Text
, _roleModel :: Maybe Text
, _scapegoatBlamed :: Bool
, _see :: Maybe Text
, _votes :: Map Text Text
} deriving (Eq, Read, Show)
data Stage = FerinasGrunt | GameOver | HuntersTurn1 | HuntersTurn2 | Lynching | OraclesTurn
| OrphansTurn | ProtectorsTurn | ScapegoatsTurn | SeersTurn | Sunrise | Sunset
| VillageDrunksTurn | VillagesTurn | WerewolvesTurn | WitchsTurn
deriving (Eq, Read, Show)
instance Humanise Stage where
humanise FerinasGrunt = fromString "Ferina's Grunt"
humanise GameOver = fromString "Game over"
humanise HuntersTurn1 = fromString "Hunter's turn"
humanise HuntersTurn2 = fromString "Hunter's turn"
humanise Lynching = fromString "Lynching"
humanise OraclesTurn = fromString "Oracle's turn"
humanise OrphansTurn = fromString "Orphan's turn"
humanise ProtectorsTurn = fromString "Protector's turn"
humanise ScapegoatsTurn = fromString "Scapegoat's turn"
humanise SeersTurn = fromString "Seer's turn"
humanise Sunrise = fromString "Sunrise"
humanise Sunset = fromString "Sunset"
humanise VillageDrunksTurn = fromString "Village Drunk's turn"
humanise VillagesTurn = fromString "village's turn"
humanise WerewolvesTurn = fromString "Werewolves' turn"
humanise WitchsTurn = fromString "Witch's turn"
makeLenses ''Game
makePrisms ''Stage
allStages :: [Stage]
allStages =
[ Sunset
, OrphansTurn
, VillageDrunksTurn
, SeersTurn
, OraclesTurn
, ProtectorsTurn
, WerewolvesTurn
, WitchsTurn
, Sunrise
, HuntersTurn2
, FerinasGrunt
, VillagesTurn
, Lynching
, HuntersTurn1
, ScapegoatsTurn
, GameOver
]
stageCycle :: [Stage]
stageCycle = cycle allStages
stageAvailable :: Game -> Stage -> Bool
stageAvailable game FerinasGrunt = has (players . druids . alive) game
stageAvailable _ GameOver = False
stageAvailable game HuntersTurn1 =
has (players . hunters . dead) game
&& not (game ^. hunterRetaliated)
stageAvailable game HuntersTurn2 =
has (players . hunters . dead) game
&& not (game ^. hunterRetaliated)
stageAvailable game Lynching = Map.size (game ^. votes) > 0
stageAvailable game OraclesTurn = has (players . oracles . alive) game
stageAvailable game OrphansTurn =
has (players . orphans . alive) game
&& isNothing (game ^. roleModel)
stageAvailable game ProtectorsTurn = has (players . protectors . alive) game
stageAvailable game ScapegoatsTurn = game ^. scapegoatBlamed
stageAvailable game SeersTurn = has (players . seers . alive) game
stageAvailable _ Sunrise = True
stageAvailable _ Sunset = True
stageAvailable game VillageDrunksTurn =
has (players . villageDrunks . alive) game
&& is thirdRound game
stageAvailable game VillagesTurn = any (is alive) (getAllowedVoters game)
stageAvailable game WerewolvesTurn = has (players . werewolves . alive) game
stageAvailable game WitchsTurn =
has (players . witches . alive) game
&& (not (game ^. healUsed) || not (game ^. poisonUsed))
newGame :: [Player] -> Game
newGame players = Game
{ _stage = head stageCycle
, _round = 0
, _players = players
, _boots = Map.empty
, _passed = False
, _allowedVoters = players ^.. names
, _divine = Nothing
, _fallenAngelLynched = False
, _healUsed = False
, _hunterRetaliated = False
, _jesterRevealed = False
, _poison = Nothing
, _poisonUsed = False
, _priorProtect = Nothing
, _protect = Nothing
, _roleModel = Nothing
, _scapegoatBlamed = False
, _see = Nothing
, _votes = Map.empty
}
votee :: Fold Game Player
votee = folding $ (\players -> if length players == 1 then take 1 players else []) . getVoteResult
getVoteResult :: Game -> [Player]
getVoteResult game
| Map.null (game ^. votes) = []
| otherwise = game ^.. players . traverse . filtered ((`elem` result) . view name)
where
votees = Map.elems $ game ^. votes
result = last $ groupSortOn (length . (`elemIndices` votees)) (nub votees)
firstRound :: Prism' Game Game
firstRound = prism (set round 0) $ \game -> (if game ^. round == 0 then Right else Left) game
secondRound :: Prism' Game Game
secondRound = prism (set round 1) $ \game -> (if game ^. round == 1 then Right else Left) game
thirdRound :: Prism' Game Game
thirdRound = prism (set round 2) $ \game -> (if game ^. round == 2 then Right else Left) game
getAllowedVoters :: Game -> [Player]
getAllowedVoters game =
map (\name -> game ^?! players . traverse . named name) (game ^. allowedVoters)
getPendingVoters :: Game -> [Player]
getPendingVoters game =
game ^.. players . traverse . alive . filtered ((`Map.notMember` votes') . view name)
where
votes' = game ^. votes
hasAnyoneWon :: Game -> Bool
hasAnyoneWon game = any ($ game) [hasFallenAngelWon, hasVillagersWon, hasWerewolvesWon]
hasFallenAngelWon :: Game -> Bool
hasFallenAngelWon game = game ^. fallenAngelLynched
hasVillagersWon :: Game -> Bool
hasVillagersWon = allOf (players . traverse . alive) (\player -> is villager player || is fallenAngel player)
hasWerewolvesWon :: Game -> Bool
hasWerewolvesWon = allOf (players . traverse . alive) (is werewolf)