summaryrefslogtreecommitdiff
path: root/src/Main.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Main.hs')
-rw-r--r--src/Main.hs57
1 files changed, 49 insertions, 8 deletions
diff --git a/src/Main.hs b/src/Main.hs
index 236e779..a0799e0 100644
--- a/src/Main.hs
+++ b/src/Main.hs
@@ -19,6 +19,9 @@ import qualified Data.CaseInsensitive as CI
19 19
20import Data.Map.Strict (Map) 20import Data.Map.Strict (Map)
21import qualified Data.Map.Strict as Map 21import qualified Data.Map.Strict as Map
22
23import Data.Map as Lazy (Map)
24import qualified Data.Map as Lazy.Map
22 25
23import Data.Set (Set) 26import Data.Set (Set)
24import qualified Data.Set as Set 27import qualified Data.Set as Set
@@ -34,7 +37,7 @@ import Data.List
34import Data.List 37import Data.List
35import Data.Maybe 38import Data.Maybe
36import Data.Bool 39import Data.Bool
37import Data.Monoid (All(..)) 40import Data.Monoid (Monoid(..), (<>), All(..))
38import Data.Ord 41import Data.Ord
39import Data.Ratio 42import Data.Ratio
40 43
@@ -67,6 +70,8 @@ import qualified Data.Text.Lazy as Lazy (Text)
67import qualified Data.Text.Lazy as Lazy.Text 70import qualified Data.Text.Lazy as Lazy.Text
68import Data.Text.Template 71import Data.Text.Template
69 72
73import Debug.Trace
74
70main :: IO () 75main :: IO ()
71main = do 76main = do
72 historyFile <- getUserCacheFile "sequence" "history" 77 historyFile <- getUserCacheFile "sequence" "history"
@@ -115,6 +120,7 @@ main = do
115 , cmd "log" dumpLog "Print the combat log" 120 , cmd "log" dumpLog "Print the combat log"
116 , cmd "val" printVal "Find the distribution of a specific value of the current entities" 121 , cmd "val" printVal "Find the distribution of a specific value of the current entities"
117 , cmd "summary" printVals "Find the averages of applicable all values" 122 , cmd "summary" printVals "Find the averages of applicable all values"
123 , cmd "burstfire" burstfire "Roll an automatic burst of <n> shots against given skill compensating for recoil with the given attribute"
118 ] 124 ]
119 , wordBreakChars = wordBreakChars initialShellDescription \\ [',', '\''] 125 , wordBreakChars = wordBreakChars initialShellDescription \\ [',', '\'']
120 } 126 }
@@ -385,7 +391,13 @@ spawnFaction cFaction num cEntity nameTemplate
385 391
386-- Dice rolls 392-- Dice rolls
387rollTest :: Completable (FormulaM Stats Test) -> Sh GameState () 393rollTest :: Completable (FormulaM Stats Test) -> Sh GameState ()
388rollTest = withArg $ maybe (return ()) ((>>) <$> outputResult <*> applyEffect) <=< enactTest' 394rollTest = withArg rollTest'
395
396rollTest' :: FormulaM Stats Test -> Sh GameState ()
397rollTest' = rollTest'' Nothing
398
399rollTest'' :: Maybe (Formula Stats) -> FormulaM Stats Test -> Sh GameState ()
400rollTest'' testMod = maybe (return ()) ((>>) <$> outputResult <*> applyEffect) <=< enactTest' testMod
389 where 401 where
390 outputResult :: (String, TestResult) -> Sh GameState () 402 outputResult :: (String, TestResult) -> Sh GameState ()
391 outputResult (test, view (rRoll . to ppResult) -> result) = do 403 outputResult (test, view (rRoll . to ppResult) -> result) = do
@@ -408,7 +420,8 @@ rollTest = withArg $ maybe (return ()) ((>>) <$> outputResult <*> applyEffect) <
408 420
409 421
410 applyEffect :: (String, TestResult) -> Sh GameState () 422 applyEffect :: (String, TestResult) -> Sh GameState ()
411 applyEffect (test, view rResult -> (Effect (CI.original -> effectDesc) effect)) = void . runMaybeT $ do 423 applyEffect (_, view rResult -> Nothing) = return ()
424 applyEffect (test, view rResult -> Just (Effect (CI.original -> effectDesc) effect)) = void . runMaybeT $ do
412 focusId <- MaybeT $ use gFocus 425 focusId <- MaybeT $ use gFocus
413 name <- toName focusId 426 name <- toName focusId
414 let 427 let
@@ -416,15 +429,15 @@ rollTest = withArg $ maybe (return ()) ((>>) <$> outputResult <*> applyEffect) <
416 lStats = gEntities . ix focusId . eStats 429 lStats = gEntities . ix focusId . eStats
417 evalF = MaybeT . focusState lStats . evalFormula' [name] 430 evalF = MaybeT . focusState lStats . evalFormula' [name]
418 guard =<< askBool ("Apply effects (" ++ effectDesc ++ ")?") True 431 guard =<< askBool ("Apply effects (" ++ effectDesc ++ ")?") True
419 lStats <~ (MaybeT . fmap join . runMaybeT $ evalF effect) 432 lStats <~ (MaybeT . fmap join . runMaybeT . evalF $ runMaybeT effect)
420 lift . outputLogged focusId $ test ++ " effects: " ++ effectDesc 433 lift . outputLogged focusId $ test ++ " effects: " ++ effectDesc
421 434
422enactTest' :: FormulaM Stats Test -> Sh GameState (Maybe (String, TestResult)) 435enactTest' :: Maybe (Formula Stats) -> FormulaM Stats Test -> Sh GameState (Maybe (String, TestResult))
423enactTest' test = runMaybeT $ do 436enactTest' testMod test = runMaybeT $ do
424 focusName <- MaybeT (use gFocus) >>= lift . toName 437 focusName <- MaybeT (use gFocus) >>= lift . toName
425 let evalF = MaybeT . focusState (gFocus' . eStats) . evalFormula' [focusName] 438 let evalF = MaybeT . focusState (gFocus' . eStats) . evalFormula' [focusName]
426 test' <- evalF test 439 test' <- evalF test
427 result <- evalF $ enactTest test' 440 result <- evalF $ (maybe enactTest (flip enactTestMod) testMod) test'
428 return (view (tName . to CI.original) test', result) 441 return (view (tName . to CI.original) test', result)
429 442
430entitySeqVal :: Sh GameState () 443entitySeqVal :: Sh GameState ()
@@ -502,7 +515,7 @@ doShock dmg efLens = withFocus $ \focusId -> do
502 else guard $ val >= bar 515 else guard $ val >= bar
503 lStats . efLens . seApplied .= True 516 lStats . efLens . seApplied .= True
504 Effect (CI.original -> effectName) effect <- evalF . table $ cripple ^. seEffect 517 Effect (CI.original -> effectName) effect <- evalF . table $ cripple ^. seEffect
505 lStats <~ (MaybeT . fmap join . runMaybeT $ evalF effect) 518 lStats <~ (MaybeT . fmap join . runMaybeT . evalF $ runMaybeT effect)
506 lift . outputLogged focusId $ "Effect: " ++ effectName 519 lift . outputLogged focusId $ "Effect: " ++ effectName
507 lift . addNote $ "Effect: " ++ effectName 520 lift . addNote $ "Effect: " ++ effectName
508 521
@@ -586,3 +599,31 @@ printVals = withFocus $ \focusId -> do
586 Just avg -> shellPutStrLn $ printf "%*s: %5.1f" maxLength (CI.original str) (fromRational avg :: Double) 599 Just avg -> shellPutStrLn $ printf "%*s: %5.1f" maxLength (CI.original str) (fromRational avg :: Double)
587 Nothing -> return () 600 Nothing -> return ()
588 mapM_ printAvg $ Map.toList sheet 601 mapM_ printAvg $ Map.toList sheet
602
603burstfire :: Int -> Completable (Formula Stats) -> Completable (Formula Stats) -> Sh GameState ()
604burstfire nShots skill' attr' = skill' <~> \skill -> attr' <~> \attr -> withFocus (burstfire' skill attr)
605 where
606 burstfire' skill attr focusId = void . runMaybeT $ do
607 name <- lift $ toName focusId
608 let
609 lStats :: Traversal' GameState Stats
610 lStats = gEntities . ix focusId . eStats
611 evalF formula = do
612 stats <- MaybeT $ preuse lStats
613 (nStats, x) <- (evalFormula [name] :: Stats -> FormulaM Stats a -> MaybeT (Sh GameState) (Stats, a)) stats formula
614 lStats .= nStats
615 return x
616 skillVal <- evalF skill
617 attrVal <- evalF attr
618 minStrRaw <- evalF $ val ignored ["Mindeststärke der Waffe"] False
619 minStrMod <- evalF $ val ignored ["Mindeststärke der Waffe", "Modifikator"] False
620 mod <- evalF $ val ignored ["Modifikator"] False
621 let
622 recoilMod = max 0 $ 10 + (minStr - attrVal)
623 minStr = minStrRaw + minStrMod
624 lift . forM_ [1..nShots] $ \n -> do
625 rollTest'' (Just $ fromIntegral mod) . return $ def
626 & tName . iso CI.original CI.mk .~ printf "Schuss %2d" n
627 & tBaseDifficulty .~ skillVal
628 & tMod .~ (n - 1) * (-recoilMod)
629 & tEffect .~ MaybeT . table . critTables "Fernkampfangriffe"