summaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/Main.hs19
-rw-r--r--src/Sequence/Contact/Archetypes.hs2
-rw-r--r--src/Sequence/Contact/Tests.hs14
3 files changed, 27 insertions, 8 deletions
diff --git a/src/Main.hs b/src/Main.hs
index c6eee62..06cc6ed 100644
--- a/src/Main.hs
+++ b/src/Main.hs
@@ -1,4 +1,4 @@
1{-# LANGUAGE ViewPatterns #-} 1{-# LANGUAGE ViewPatterns, RecordWildCards #-}
2 2
3import Control.Monad 3import Control.Monad
4 4
@@ -7,6 +7,7 @@ import Control.Lens
7import System.Console.Shell 7import System.Console.Shell
8import System.Console.Shell.ShellMonad 8import System.Console.Shell.ShellMonad
9import System.Console.Shell.Backend.Haskeline 9import System.Console.Shell.Backend.Haskeline
10import System.Console.ANSI (setSGRCode, SGR(..), ConsoleLayer(..), ConsoleIntensity(..), ColorIntensity(..), Color(..))
10 11
11import System.Environment.XDG.BaseDir 12import System.Environment.XDG.BaseDir
12import System.FilePath 13import System.FilePath
@@ -126,8 +127,22 @@ nameEntity :: String -> Sh GameState ()
126nameEntity ('#':_) = shellPutErrLn "We do not allow names that might shadow explicit access to entities via their number (‘#<n>’)" 127nameEntity ('#':_) = shellPutErrLn "We do not allow names that might shadow explicit access to entities via their number (‘#<n>’)"
127nameEntity name = withFocus $ \ident -> modifying gEntityNames $ Bimap.insert ident (name ^. entityName) 128nameEntity name = withFocus $ \ident -> modifying gEntityNames $ Bimap.insert ident (name ^. entityName)
128 129
130-- Dice rolls
129rollTest :: Completable (FormulaM Stats Test) -> Sh GameState () 131rollTest :: Completable (FormulaM Stats Test) -> Sh GameState ()
130rollTest = withArg $ enactTest' >=> maybe (return ()) (shellPutStrLn . show) 132rollTest = withArg $ enactTest' >=> maybe (return ()) (shellPutStrLn . ppResult)
133 where
134 ppResult result = pad 3 (show $ result^.rWith) ++ ": " ++ setSGRCode (colour result) ++ name result ++ setSGRCode [] ++ " by " ++ pad 2 (show $ result^.rBy) ++ "pp"
135 colour CritSuccess{..} = [SetColor Foreground Vivid Green, SetConsoleIntensity BoldIntensity]
136 colour Success{..} = [SetColor Foreground Dull Green]
137 colour Failure{..} = [SetColor Foreground Dull Red]
138 colour CritFailure{..} = [SetColor Foreground Vivid Red, SetConsoleIntensity BoldIntensity]
139 name CritSuccess{..} = "Critical Success"
140 name Success{..} = "Success"
141 name Failure{..} = "Failure"
142 name CritFailure{..} = "Critical Failure"
143 pad n str
144 | length str >= n = str
145 | otherwise = ' ' : pad (n - 1) str
131 146
132enactTest' :: (FormulaM Stats Test) -> Sh GameState (Maybe TestResult) 147enactTest' :: (FormulaM Stats Test) -> Sh GameState (Maybe TestResult)
133enactTest' test = withFocus' $ \focus -> do 148enactTest' test = withFocus' $ \focus -> do
diff --git a/src/Sequence/Contact/Archetypes.hs b/src/Sequence/Contact/Archetypes.hs
index 3b014e4..8eb9dd7 100644
--- a/src/Sequence/Contact/Archetypes.hs
+++ b/src/Sequence/Contact/Archetypes.hs
@@ -23,7 +23,7 @@ import qualified Data.CaseInsensitive as CI
23 23
24instance Completion Entity GameState where 24instance Completion Entity GameState where
25 completableLabel _ = "<archetype>" 25 completableLabel _ = "<archetype>"
26 complete _ _ (CI.foldCase -> prefix) = return . filter (prefix `isPrefixOf`) . map CI.foldedCase $ Map.keys archetypes 26 complete _ _ (CI.foldCase -> prefix) = return . map CI.original . filter ((prefix `isPrefixOf`) . CI.foldedCase) $ Map.keys archetypes
27 27
28instance Argument Entity GameState where 28instance Argument Entity GameState where
29 arg = return . fmap (flip (set eStats) def) . flip Map.lookup archetypes . CI.mk 29 arg = return . fmap (flip (set eStats) def) . flip Map.lookup archetypes . CI.mk
diff --git a/src/Sequence/Contact/Tests.hs b/src/Sequence/Contact/Tests.hs
index 86f72b5..8aa072a 100644
--- a/src/Sequence/Contact/Tests.hs
+++ b/src/Sequence/Contact/Tests.hs
@@ -1,8 +1,8 @@
1{-# LANGUAGE TemplateHaskell, OverloadedStrings, OverloadedLists, ViewPatterns, MultiParamTypeClasses, FlexibleContexts, RankNTypes, TypeSynonymInstances, FlexibleInstances, ImpredicativeTypes #-} 1{-# LANGUAGE TemplateHaskell, OverloadedStrings, OverloadedLists, ViewPatterns, MultiParamTypeClasses, FlexibleContexts, RankNTypes, TypeSynonymInstances, FlexibleInstances, ImpredicativeTypes #-}
2 2
3module Sequence.Contact.Tests 3module Sequence.Contact.Tests
4 ( TestResult(..) 4 ( TestResult(..), rWith, rBy
5 , Test 5 , Test, tCritSuccessMod, tCritFailureMod, tBaseDifficulty, tMod
6 , enactTest 6 , enactTest
7 ) where 7 ) where
8 8
@@ -55,12 +55,16 @@ instance Default Test where
55 } 55 }
56 56
57tests :: MonadReader Stats m => m (Map (CI String) (FormulaM Stats Test)) 57tests :: MonadReader Stats m => m (Map (CI String) (FormulaM Stats Test))
58tests = mconcat <$> sequence [ test "Stärke" (sAStrength . attributeTest) 58tests = mconcat <$> sequence [ test "Stärke" $ sAStrength . attributeTest
59
60 , test "Archaische Distanzwaffen" $ sSArchaicRanged . skillTest
61
62 , test "Beißen" $ sSBiting . skillTest
59 ] 63 ]
60 where 64 where
61 test k v = maybe mempty (Map.singleton k) <$> preview v 65 test k v = maybe mempty (Map.singleton k) <$> preview v
62 66
63 -- skillTest = to (\x -> flip (set tBaseDifficulty) def <$> x) 67 skillTest = to (\x -> flip (set tBaseDifficulty) def <$> x)
64 attributeTest = to (\x -> flip (set tBaseDifficulty) def . (* 10) <$> x) 68 attributeTest = to (\x -> flip (set tBaseDifficulty) def . (* 10) <$> x)
65 69
66 70
@@ -71,7 +75,7 @@ getTest (CI.mk -> str) = folding tests'
71 75
72instance Completion (FormulaM Stats Test) GameState where 76instance Completion (FormulaM Stats Test) GameState where
73 completableLabel _ = "<test>" 77 completableLabel _ = "<test>"
74 complete _ st (CI.foldCase -> prefix) = return . fromMaybe [] . fmap (filter (prefix `isPrefixOf`) . map CI.foldedCase . Map.keys) $ previews (gFocus' . eStats) tests st 78 complete _ st (CI.foldCase -> prefix) = return . fromMaybe [] . fmap (map CI.original . filter ((prefix `isPrefixOf`) . CI.foldedCase) . Map.keys) $ previews (gFocus' . eStats) tests st
75 79
76instance Argument (FormulaM Stats Test) GameState where 80instance Argument (FormulaM Stats Test) GameState where
77 arg str = join <$> preuses (gFocus' . eStats) (preview (getTest str)) 81 arg str = join <$> preuses (gFocus' . eStats) (preview (getTest str))