diff options
Diffstat (limited to 'src/Sequence')
-rw-r--r-- | src/Sequence/Contact/Tests.hs | 100 | ||||
-rw-r--r-- | src/Sequence/Contact/Types.hs | 3 | ||||
-rw-r--r-- | src/Sequence/Formula.hs | 21 | ||||
-rw-r--r-- | src/Sequence/Types.hs | 30 | ||||
-rw-r--r-- | src/Sequence/Utils.hs | 9 |
5 files changed, 151 insertions, 12 deletions
diff --git a/src/Sequence/Contact/Tests.hs b/src/Sequence/Contact/Tests.hs new file mode 100644 index 0000000..86f72b5 --- /dev/null +++ b/src/Sequence/Contact/Tests.hs | |||
@@ -0,0 +1,100 @@ | |||
1 | {-# LANGUAGE TemplateHaskell, OverloadedStrings, OverloadedLists, ViewPatterns, MultiParamTypeClasses, FlexibleContexts, RankNTypes, TypeSynonymInstances, FlexibleInstances, ImpredicativeTypes #-} | ||
2 | |||
3 | module Sequence.Contact.Tests | ||
4 | ( TestResult(..) | ||
5 | , Test | ||
6 | , enactTest | ||
7 | ) where | ||
8 | |||
9 | import Sequence.Formula | ||
10 | import Sequence.Types | ||
11 | import Sequence.Utils | ||
12 | import Sequence.Contact.Types | ||
13 | |||
14 | import Control.Monad | ||
15 | import Control.Monad.Reader | ||
16 | import Control.Lens | ||
17 | |||
18 | import Data.Default | ||
19 | import Data.List | ||
20 | import Data.Maybe | ||
21 | |||
22 | import Data.CaseInsensitive (CI) | ||
23 | import qualified Data.CaseInsensitive as CI | ||
24 | |||
25 | import Data.Map.Strict (Map) | ||
26 | import qualified Data.Map.Strict as Map | ||
27 | |||
28 | import Data.Traversable (mapM) | ||
29 | |||
30 | import Prelude hiding (mapM) | ||
31 | |||
32 | |||
33 | data TestResult = CritSuccess { _rWith, _rBy :: Int } | ||
34 | | Success { _rWith, _rBy :: Int } | ||
35 | | Failure { _rWith, _rBy :: Int } | ||
36 | | CritFailure { _rWith, _rBy :: Int } | ||
37 | deriving (Eq, Ord, Show) | ||
38 | makeLenses ''TestResult | ||
39 | |||
40 | data Test = Test | ||
41 | { _tCritSuccessMod | ||
42 | , _tCritFailureMod | ||
43 | , _tBaseDifficulty | ||
44 | , _tMod :: Int | ||
45 | } | ||
46 | deriving (Eq, Ord) | ||
47 | makeLenses ''Test | ||
48 | |||
49 | instance Default Test where | ||
50 | def = Test | ||
51 | { _tCritSuccessMod = 0 | ||
52 | , _tCritFailureMod = 0 | ||
53 | , _tBaseDifficulty = 50 | ||
54 | , _tMod = 0 | ||
55 | } | ||
56 | |||
57 | tests :: MonadReader Stats m => m (Map (CI String) (FormulaM Stats Test)) | ||
58 | tests = mconcat <$> sequence [ test "Stärke" (sAStrength . attributeTest) | ||
59 | ] | ||
60 | where | ||
61 | test k v = maybe mempty (Map.singleton k) <$> preview v | ||
62 | |||
63 | -- skillTest = to (\x -> flip (set tBaseDifficulty) def <$> x) | ||
64 | attributeTest = to (\x -> flip (set tBaseDifficulty) def . (* 10) <$> x) | ||
65 | |||
66 | |||
67 | getTest :: String -> Fold Stats (FormulaM Stats Test) | ||
68 | getTest (CI.mk -> str) = folding tests' | ||
69 | where | ||
70 | tests' state = Map.lookup str (tests state) -- >>= (\get -> preview get state) | ||
71 | |||
72 | instance Completion (FormulaM Stats Test) GameState where | ||
73 | completableLabel _ = "<test>" | ||
74 | complete _ st (CI.foldCase -> prefix) = return . fromMaybe [] . fmap (filter (prefix `isPrefixOf`) . map CI.foldedCase . Map.keys) $ previews (gFocus' . eStats) tests st | ||
75 | |||
76 | instance Argument (FormulaM Stats Test) GameState where | ||
77 | arg str = join <$> preuses (gFocus' . eStats) (preview (getTest str)) | ||
78 | |||
79 | enactTest :: Test -> FormulaM input TestResult | ||
80 | enactTest test = toResult <$> d 100 | ||
81 | where | ||
82 | critFailureBar = 95 - test^.tCritFailureMod | ||
83 | critSuccessBar = 5 + test^.tCritSuccessMod | ||
84 | bar = test^.tBaseDifficulty + test^.tMod | ||
85 | toResult pw = (toResult' pw) pw (abs $ bar - pw) | ||
86 | toResult' pw | ||
87 | | bar > critSuccessBar | ||
88 | , pw <= critSuccessBar = CritSuccess | ||
89 | | pw <= bar = Success | ||
90 | | pw >= critFailureBar = CritFailure | ||
91 | | otherwise = Failure | ||
92 | |||
93 | -- hasTest :: Stats -> String -> Bool | ||
94 | -- hasTest stats str = has (getTest str) stats | ||
95 | |||
96 | -- rollTest :: String -> FormulaM Stats (Maybe TestResult) | ||
97 | -- rollTest str = preview (getTest str) >>= enactTest' | ||
98 | -- where | ||
99 | -- enactTest' Nothing = return Nothing | ||
100 | -- enactTest' (Just t) = Just <$> (enactTest =<< t) | ||
diff --git a/src/Sequence/Contact/Types.hs b/src/Sequence/Contact/Types.hs index 4166812..c00a60d 100644 --- a/src/Sequence/Contact/Types.hs +++ b/src/Sequence/Contact/Types.hs | |||
@@ -1,9 +1,10 @@ | |||
1 | {-# LANGUAGE TemplateHaskell #-} | 1 | {-# LANGUAGE TemplateHaskell, RecordWildCards, OverloadedStrings, OverloadedLists, ViewPatterns, RankNTypes #-} |
2 | 2 | ||
3 | module Sequence.Contact.Types where | 3 | module Sequence.Contact.Types where |
4 | 4 | ||
5 | import Sequence.Formula | 5 | import Sequence.Formula |
6 | 6 | ||
7 | import Control.Monad | ||
7 | import Control.Lens | 8 | import Control.Lens |
8 | 9 | ||
9 | import Data.Default | 10 | import Data.Default |
diff --git a/src/Sequence/Formula.hs b/src/Sequence/Formula.hs index 66672a2..c3e9e33 100644 --- a/src/Sequence/Formula.hs +++ b/src/Sequence/Formula.hs | |||
@@ -23,6 +23,9 @@ import Text.Read (readMaybe) | |||
23 | import Data.Bool | 23 | import Data.Bool |
24 | import Data.List | 24 | import Data.List |
25 | import Data.Maybe | 25 | import Data.Maybe |
26 | import Data.Either | ||
27 | |||
28 | import Debug.Trace | ||
26 | 29 | ||
27 | 30 | ||
28 | type FormulaM input a = ReaderT input (ExceptT (Question input) EventM) a | 31 | type FormulaM input a = ReaderT input (ExceptT (Question input) EventM) a |
@@ -35,6 +38,15 @@ data Question input = Question | |||
35 | , keepResult :: Bool | 38 | , keepResult :: Bool |
36 | } | 39 | } |
37 | 40 | ||
41 | instance Eq (Question a) where | ||
42 | (==) _ _ = True | ||
43 | |||
44 | instance Ord (Question a) where | ||
45 | (<=) _ _ = True | ||
46 | |||
47 | instance Show (Question a) where | ||
48 | show Question{..} = show prompt | ||
49 | |||
38 | instance Integral a => Num (FormulaM input a) where | 50 | instance Integral a => Num (FormulaM input a) where |
39 | (+) x y = (+) <$> x <*> y | 51 | (+) x y = (+) <$> x <*> y |
40 | (-) x y = (-) <$> x <*> y | 52 | (-) x y = (-) <$> x <*> y |
@@ -51,17 +63,18 @@ quot' = liftM2 quot | |||
51 | askQuestion :: MonadIO m => input -> (Question input) -> m input | 63 | askQuestion :: MonadIO m => input -> (Question input) -> m input |
52 | askQuestion input q@(Question{..}) = flip (set answer) input . maybe (throwError q) return <$> askQ prompt (join . fmap readMaybe) | 64 | askQuestion input q@(Question{..}) = flip (set answer) input . maybe (throwError q) return <$> askQ prompt (join . fmap readMaybe) |
53 | 65 | ||
54 | evalFormula :: MonadIO m => input -> FormulaM input a -> m (input, a) | 66 | evalFormula :: (MonadIO m, Ord a, Show a) => input -> FormulaM input a -> m (input, a) |
55 | evalFormula = evalFormula' [] | 67 | evalFormula = evalFormula' [] |
56 | where | 68 | where |
57 | evalFormula' finalChanges input formula = do | 69 | evalFormula' finalChanges input formula = trace "evalFormula'" $ do |
58 | result <- liftIO . enact . runExceptT . (runReaderT ?? input) $ formula | 70 | result <- liftIO . enact . traceShowId . runExceptT . (runReaderT ?? input) $ formula |
71 | liftIO . traceIO $ show (isLeft result, isRight result) | ||
59 | case result of | 72 | case result of |
60 | Left q@(Question{..}) -> askQuestion input q >>= flip (evalFormula' $ bool (pure . set answer $ throwError q) mempty keepResult ++ finalChanges) formula | 73 | Left q@(Question{..}) -> askQuestion input q >>= flip (evalFormula' $ bool (pure . set answer $ throwError q) mempty keepResult ++ finalChanges) formula |
61 | Right result -> return (foldr ($) input finalChanges, result) | 74 | Right result -> return (foldr ($) input finalChanges, result) |
62 | 75 | ||
63 | val :: Integral a => Traversal' input (Formula input) -> String -> Bool -> Formula input | 76 | val :: Integral a => Traversal' input (Formula input) -> String -> Bool -> Formula input |
64 | val answer prompt keepResult = preview answer >>= maybe (throwError Question{..}) id | 77 | val answer prompt keepResult = preview answer >>= maybe (throwError Question{..}) id . trace "val" |
65 | 78 | ||
66 | -- viewL :: Lens' lInput sInput -> Prism' (FormulaM sInput a) (FormulaM lInput a) | 79 | -- viewL :: Lens' lInput sInput -> Prism' (FormulaM sInput a) (FormulaM lInput a) |
67 | -- viewL lTrav = iso asL asS | 80 | -- viewL lTrav = iso asL asS |
diff --git a/src/Sequence/Types.hs b/src/Sequence/Types.hs index c47136c..541505c 100644 --- a/src/Sequence/Types.hs +++ b/src/Sequence/Types.hs | |||
@@ -7,7 +7,7 @@ module Sequence.Types | |||
7 | , Entity(..), eFaction, eSeqVal, eStats | 7 | , Entity(..), eFaction, eSeqVal, eStats |
8 | , EntityName(..), entityName | 8 | , EntityName(..), entityName |
9 | , EntityIdentifier(..), entityId, entityId' | 9 | , EntityIdentifier(..), entityId, entityId' |
10 | , inhabitedFactions, priorityQueue, tip, insertEntity | 10 | , inhabitedFactions, priorityQueue, tip, insertEntity, gFocus' |
11 | ) where | 11 | ) where |
12 | 12 | ||
13 | import Control.Lens | 13 | import Control.Lens |
@@ -24,6 +24,7 @@ import qualified Data.Map.Strict as Map | |||
24 | import Data.Bimap (Bimap) | 24 | import Data.Bimap (Bimap) |
25 | import qualified Data.Bimap as Bimap | 25 | import qualified Data.Bimap as Bimap |
26 | 26 | ||
27 | import Control.Monad.Reader | ||
27 | import Control.Monad.State | 28 | import Control.Monad.State |
28 | 29 | ||
29 | import Data.List | 30 | import Data.List |
@@ -117,8 +118,31 @@ priorityQueue = to priorityQueue' | |||
117 | filter (Nothing, _) = mempty | 118 | filter (Nothing, _) = mempty |
118 | filter (Just val, id) = pure (val, id) | 119 | filter (Just val, id) = pure (val, id) |
119 | 120 | ||
120 | tip :: Getter GameState (Maybe EntityIdentifier) | 121 | tip :: Fold GameState EntityIdentifier |
121 | tip = priorityQueue . to (fmap snd . listToMaybe) | 122 | tip = priorityQueue . folding (fmap snd . listToMaybe) |
123 | |||
124 | gFocus' :: Traversal' GameState Entity | ||
125 | gFocus' modifyFocus = do | ||
126 | focusIdent <- view gFocus | ||
127 | case focusIdent of | ||
128 | Nothing -> pure <$> ask | ||
129 | Just focusIdent -> do | ||
130 | focus <- view (gEntities . at focusIdent) | ||
131 | case focus of | ||
132 | Nothing -> pure <$> ask | ||
133 | Just focus -> do | ||
134 | st <- ask | ||
135 | return $ flip (set $ gEntities . at focusIdent) st . Just <$> modifyFocus focus | ||
136 | |||
137 | -- gFocus' = prism' getFocus setFocus | ||
138 | -- where | ||
139 | -- getFocus = do | ||
140 | -- ident <- preview tip | ||
141 | -- case ident of | ||
142 | -- Nothing -> return Nothing | ||
143 | -- Just ident' -> do | ||
144 | -- views gEntities $ Map.lookup ident' | ||
145 | -- setFocus | ||
122 | 146 | ||
123 | gNextId' :: Getter GameState EntityIdentifier | 147 | gNextId' :: Getter GameState EntityIdentifier |
124 | gNextId' = gNextId | 148 | gNextId' = gNextId |
diff --git a/src/Sequence/Utils.hs b/src/Sequence/Utils.hs index 9fc0ab2..517c3c2 100644 --- a/src/Sequence/Utils.hs +++ b/src/Sequence/Utils.hs | |||
@@ -1,7 +1,7 @@ | |||
1 | {-# LANGUAGE ViewPatterns, FlexibleContexts, MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, UndecidableInstances, OverloadedStrings #-} | 1 | {-# LANGUAGE ViewPatterns, FlexibleContexts, MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, UndecidableInstances, OverloadedStrings #-} |
2 | 2 | ||
3 | module Sequence.Utils | 3 | module Sequence.Utils |
4 | ( withArg, withFocus | 4 | ( withArg, withFocus, withFocus' |
5 | , toName | 5 | , toName |
6 | , Argument(..) | 6 | , Argument(..) |
7 | , Completion(..) | 7 | , Completion(..) |
@@ -48,9 +48,10 @@ withArg f (Completable str) = arg str >>= \a -> case a of | |||
48 | Just a -> f a | 48 | Just a -> f a |
49 | 49 | ||
50 | withFocus :: (EntityIdentifier -> Sh GameState ()) -> Sh GameState () | 50 | withFocus :: (EntityIdentifier -> Sh GameState ()) -> Sh GameState () |
51 | withFocus f = use gFocus >>= \focus -> case focus of | 51 | withFocus f = use gFocus >>= maybe (shellPutErrLn $ "Currently not focusing any entity") f |
52 | Nothing -> shellPutErrLn $ "Currently not focusing any entity" | 52 | |
53 | Just id -> f id | 53 | withFocus' :: (Entity -> Sh GameState a) -> Sh GameState (Maybe a) |
54 | withFocus' f = preuse gFocus' >>= maybe (Nothing <$ shellPutErrLn "Currently not focusing any entity") (fmap Just . f) | ||
54 | 55 | ||
55 | unaligned = view faction' def | 56 | unaligned = view faction' def |
56 | 57 | ||