summaryrefslogtreecommitdiff
path: root/src/Sequence
diff options
context:
space:
mode:
authorGregor Kleen <gkleen@yggdrasil.li>2016-06-03 22:09:01 +0200
committerGregor Kleen <gkleen@yggdrasil.li>2016-06-03 22:09:01 +0200
commitcfb7be14aebffd68ca357d7c6ef15e1c0974a156 (patch)
tree7448ef0ee0fa4049903efabf2fe7abf8eb7940b3 /src/Sequence
parenta98cd5d87a0c7959146a8ca35aa40f42fc146ad8 (diff)
download2017-01-16_17:13:37-cfb7be14aebffd68ca357d7c6ef15e1c0974a156.tar
2017-01-16_17:13:37-cfb7be14aebffd68ca357d7c6ef15e1c0974a156.tar.gz
2017-01-16_17:13:37-cfb7be14aebffd68ca357d7c6ef15e1c0974a156.tar.bz2
2017-01-16_17:13:37-cfb7be14aebffd68ca357d7c6ef15e1c0974a156.tar.xz
2017-01-16_17:13:37-cfb7be14aebffd68ca357d7c6ef15e1c0974a156.zip
cleanup & stumped on variadic val
Diffstat (limited to 'src/Sequence')
-rw-r--r--src/Sequence/Formula.hs59
-rw-r--r--src/Sequence/Utils.hs17
-rw-r--r--src/Sequence/Utils/Ask.hs27
3 files changed, 73 insertions, 30 deletions
diff --git a/src/Sequence/Formula.hs b/src/Sequence/Formula.hs
index 7a6e689..2a4541f 100644
--- a/src/Sequence/Formula.hs
+++ b/src/Sequence/Formula.hs
@@ -1,26 +1,37 @@
1{-# LANGUAGE RecordWildCards, RankNTypes, TypeSynonymInstances, FlexibleInstances #-} 1{-# LANGUAGE RecordWildCards, RankNTypes, TypeSynonymInstances, FlexibleInstances, MultiParamTypeClasses, ViewPatterns, TypeFamilies #-}
2 2
3module Sequence.Formula 3module Sequence.Formula
4 ( FormulaM 4 ( FormulaM
5 , evalFormula 5 , evalFormula
6 , val 6 , val
7 , d, z
7 ) where 8 ) where
8 9
9import Control.Lens 10import Control.Lens
11import Data.Data.Lens
12import Data.Data (Data)
13import Data.Typeable (Typeable)
10 14
11import Control.Monad.Trans.Either 15import Control.Monad.Except
12import Control.Monad.Reader 16import Control.Monad.Reader
13import Numeric.Probability.Game.Event 17import Numeric.Probability.Game.Event
18import qualified Numeric.Probability.Game.Dice as D
14 19
15import Sequence.Utils 20import Sequence.Utils.Ask
16 21
17import Text.Read (readMaybe) 22import Text.Read (readMaybe)
18 23
19type FormulaM input a = ReaderT input (EitherT (Question input) EventM) a 24import Data.Bool
25import Data.List
26import Data.Maybe
27
28
29type FormulaM input a = ReaderT input (ExceptT (Question input) EventM) a
20 30
21data Question input = Question 31data Question input = Question
22 { answer :: Lens' input (Maybe Int) 32 { answer :: Traversal' input (FormulaM input Int)
23 , prompt :: String 33 , prompt :: String
34 , keepResult :: Bool
24 } 35 }
25 36
26instance Integral a => Num (FormulaM input a) where 37instance Integral a => Num (FormulaM input a) where
@@ -29,18 +40,36 @@ instance Integral a => Num (FormulaM input a) where
29 negate = fmap negate 40 negate = fmap negate
30 abs = fmap abs 41 abs = fmap abs
31 signum = fmap signum 42 signum = fmap signum
32 (*) x y = sum <$> (flip replicateM y =<< fromIntegral <$> x) 43 (*) x y = do n <- x
44 sum <$> replicateM (fromIntegral n) y
33 fromInteger = return . fromInteger 45 fromInteger = return . fromInteger
34 46
47
35askQuestion :: MonadIO m => input -> (Question input) -> m input 48askQuestion :: MonadIO m => input -> (Question input) -> m input
36askQuestion input q@(Question{..}) = flip (set answer) input <$> askQ prompt (join . fmap readMaybe) 49askQuestion input q@(Question{..}) = flip (set answer) input . maybe (throwError q) return <$> askQ prompt (join . fmap readMaybe)
50
51evalFormula :: MonadIO m => input -> FormulaM input a -> m (input, a)
52evalFormula = evalFormula' []
53 where
54 evalFormula' finalChanges input formula = do
55 result <- liftIO . enact . runExceptT . (runReaderT ?? input) $ formula
56 case result of
57 Left q@(Question{..}) -> askQuestion input q >>= flip (evalFormula' $ bool (pure . set answer $ throwError q) mempty keepResult ++ finalChanges) formula
58 Right result -> return (foldr ($) input finalChanges, result)
59
60val :: Integral a => Traversal' input (FormulaM input Int) -> String -> Bool -> FormulaM input Int
61val answer prompt keepResult = preview answer >>= maybe (throwError Question{..}) id
62
63-- viewL :: Lens' lInput sInput -> Iso' (FormulaM sInput a) (FormulaM lInput a)
64-- viewL lTrav = iso asL asS
65-- where
66-- asL small = join $ lift . withExceptT (\Question{..} -> Question{ answer = lTrav . answer . viewL lTrav, .. }) . runReaderT small <$> view lTrav
67-- asS :: FormulaM lInput a -> FormulaM sInput a
68-- asS large = undefined
37 69
38evalFormula :: MonadIO m => input -> FormulaM input a -> m a 70-- val' :: Integral a => Lens' lInput sInput -> Traversal' sInput (FormulaM sInput Int) -> String -> Bool -> FormulaM lInput Int
39evalFormula input formula = do 71-- val' lTrav sTrav prompt keepResult = preview (lTrav . sTrav . viewL lTrav) >>= maybe (throwError Question{ answer = lTrav . sTrav . viewL lTrav, ..}) id
40 result <- liftIO . enact . runEitherT . (runReaderT ?? input) $ formula
41 case result of
42 Left q -> askQuestion input q >>= flip evalFormula formula
43 Right result -> return result
44 72
45val :: Integral a => Lens' input (Maybe Int) -> String -> FormulaM input Int 73d, z :: Integral a => Int -> FormulaM input a
46val answer prompt = view answer >>= maybe (lift . left $ Question{..}) return 74d n = lift . lift . fmap fromIntegral $ D.d n
75z n = lift . lift . fmap fromIntegral $ D.z n
diff --git a/src/Sequence/Utils.hs b/src/Sequence/Utils.hs
index f0a8849..274a69d 100644
--- a/src/Sequence/Utils.hs
+++ b/src/Sequence/Utils.hs
@@ -2,8 +2,8 @@
2 2
3module Sequence.Utils 3module Sequence.Utils
4 ( withArg, withFocus 4 ( withArg, withFocus
5 , askQ, askBool
6 , toName, fromName 5 , toName, fromName
6 , module Sequence.Utils.Ask
7 ) where 7 ) where
8 8
9import Sequence.Types 9import Sequence.Types
@@ -33,8 +33,7 @@ import System.Console.Shell
33import System.Console.Shell.ShellMonad 33import System.Console.Shell.ShellMonad
34import System.Console.Shell.Backend.Haskeline 34import System.Console.Shell.Backend.Haskeline
35 35
36import System.Console.Readline (readline) 36import Sequence.Utils.Ask
37
38 37
39class Argument a st | a -> st where 38class Argument a st | a -> st where
40 arg :: String -> Sh st (Maybe a) 39 arg :: String -> Sh st (Maybe a)
@@ -49,18 +48,6 @@ withFocus f = use gFocus >>= \focus -> case focus of
49 Nothing -> shellPutErrLn $ "Currently not focusing any entity" 48 Nothing -> shellPutErrLn $ "Currently not focusing any entity"
50 Just id -> f id 49 Just id -> f id
51 50
52askBool :: MonadIO m => String -> Bool -> m Bool
53askBool prompt initial = askQ prompt $ fromMaybe initial . join . fmap (eval . CI.mk)
54 where
55 eval "yes" = Just True
56 eval "y" = Just True
57 eval "no" = Just False
58 eval "n" = Just False
59 eval _ = Nothing
60
61askQ :: MonadIO m => String -> (Maybe String -> a) -> m a
62askQ prompt eval = eval <$> liftIO (readline $ prompt ++ " ")
63
64unaligned = view faction' def 51unaligned = view faction' def
65 52
66toName :: MonadState GameState m => EntityIdentifier -> m String 53toName :: MonadState GameState m => EntityIdentifier -> m String
diff --git a/src/Sequence/Utils/Ask.hs b/src/Sequence/Utils/Ask.hs
new file mode 100644
index 0000000..8020656
--- /dev/null
+++ b/src/Sequence/Utils/Ask.hs
@@ -0,0 +1,27 @@
1{-# LANGUAGE OverloadedStrings #-}
2
3module Sequence.Utils.Ask
4 ( askQ, askBool
5 ) where
6
7import System.Console.Readline (readline)
8
9import Control.Monad.IO.Class
10import Control.Monad
11
12import Data.CaseInsensitive (CI)
13import qualified Data.CaseInsensitive as CI
14
15import Data.Maybe
16
17askBool :: MonadIO m => String -> Bool -> m Bool
18askBool prompt initial = askQ prompt $ fromMaybe initial . join . fmap (eval . CI.mk)
19 where
20 eval "yes" = Just True
21 eval "y" = Just True
22 eval "no" = Just False
23 eval "n" = Just False
24 eval _ = Nothing
25
26askQ :: MonadIO m => String -> (Maybe String -> a) -> m a
27askQ prompt eval = eval <$> liftIO (readline $ prompt ++ " ")