{-# LANGUAGE TemplateHaskell, OverloadedStrings, OverloadedLists, ViewPatterns, MultiParamTypeClasses, FlexibleContexts, RankNTypes, TypeSynonymInstances, FlexibleInstances #-} module Sequence.Contact.Tests ( enactTest ) where import Sequence.Formula import Sequence.Types import Sequence.Utils import Sequence.Contact.Types import Control.Monad import Control.Monad.Reader import Control.Monad.Base import Control.Lens import Data.Default import Data.List import Data.Maybe import Data.CaseInsensitive (CI) import qualified Data.CaseInsensitive as CI import Data.Map.Strict (Map) import qualified Data.Map.Strict as Map import Data.Traversable (mapM) import Prelude hiding (mapM) tests :: MonadReader Stats m => m (Map (CI String) (FormulaM Stats Test)) tests = mconcat <$> sequence [ test "Stärke" $ sAStrength . attributeTest , test "Archaische Distanzwaffen" $ sSArchaicRanged . skillTest , test "Beißen" $ sSBiting . skillTest ] where test k v = maybe mempty (Map.singleton k) <$> preview v skillTest = to (\x -> flip (set tBaseDifficulty) def <$> x) attributeTest = to (\x -> flip (set tBaseDifficulty) def . (* 10) <$> x) getTest :: String -> Fold Stats (FormulaM Stats Test) getTest (CI.mk -> str) = folding tests' where tests' state = Map.lookup str (tests state) -- >>= (\get -> preview get state) instance Completion (FormulaM Stats Test) GameState where completableLabel _ = "" complete _ st (CI.foldCase -> prefix) = return . fromMaybe [] . fmap (map CI.original . filter ((prefix `isPrefixOf`) . CI.foldedCase) . Map.keys) $ previews (gFocus' . eStats) tests st instance Argument (FormulaM Stats Test) GameState where arg str = join <$> preuses (gFocus' . eStats) (preview (getTest str)) enactTest :: Test -> FormulaM Stats TestResult enactTest rawTest = do test <- foldM (&) rawTest =<< toListOf (ctx . sModifiers . folded . _Modifier . _2) <$> ask let critFailureBar = 95 - test^.tCritFailureMod critSuccessBar = 5 + test^.tCritSuccessMod bar = test^.tBaseDifficulty + test^.tMod toResult pw = (toResult' pw) pw (abs $ bar - pw) toResult' pw | bar > critSuccessBar , pw <= critSuccessBar = CritSuccess | pw <= bar = Success | pw >= critFailureBar = CritFailure | otherwise = Failure toResult <$> d 100 -- hasTest :: Stats -> String -> Bool -- hasTest stats str = has (getTest str) stats -- rollTest :: String -> FormulaM Stats (Maybe TestResult) -- rollTest str = preview (getTest str) >>= enactTest' -- where -- enactTest' Nothing = return Nothing -- enactTest' (Just t) = Just <$> (enactTest =<< t)