diff options
author | Gregor Kleen <gkleen@yggdrasil.li> | 2016-06-06 02:41:09 +0200 |
---|---|---|
committer | Gregor Kleen <gkleen@yggdrasil.li> | 2016-06-06 02:41:09 +0200 |
commit | 54624cecd73a0b1ae3b8c6de41808ca02b31179e (patch) | |
tree | adebeb88499749969e6f56e10ddf3347c219b3ed | |
parent | b0460c33fe676912b88de09f49956a4adf5c9752 (diff) | |
download | 2017-01-16_17:13:37-54624cecd73a0b1ae3b8c6de41808ca02b31179e.tar 2017-01-16_17:13:37-54624cecd73a0b1ae3b8c6de41808ca02b31179e.tar.gz 2017-01-16_17:13:37-54624cecd73a0b1ae3b8c6de41808ca02b31179e.tar.bz2 2017-01-16_17:13:37-54624cecd73a0b1ae3b8c6de41808ca02b31179e.tar.xz 2017-01-16_17:13:37-54624cecd73a0b1ae3b8c6de41808ca02b31179e.zip |
Evaluate formulas in arbitrarily large context
-rw-r--r-- | src/Main.hs | 6 | ||||
-rw-r--r-- | src/Sequence/Formula.hs | 38 | ||||
-rw-r--r-- | src/Sequence/Types.hs | 6 |
3 files changed, 37 insertions, 13 deletions
diff --git a/src/Main.hs b/src/Main.hs index 06cc6ed..f4a863f 100644 --- a/src/Main.hs +++ b/src/Main.hs | |||
@@ -2,7 +2,7 @@ | |||
2 | 2 | ||
3 | import Control.Monad | 3 | import Control.Monad |
4 | 4 | ||
5 | import Control.Lens | 5 | import Control.Lens hiding (Context(..)) |
6 | 6 | ||
7 | import System.Console.Shell | 7 | import System.Console.Shell |
8 | import System.Console.Shell.ShellMonad | 8 | import System.Console.Shell.ShellMonad |
@@ -146,7 +146,7 @@ rollTest = withArg $ enactTest' >=> maybe (return ()) (shellPutStrLn . ppResult) | |||
146 | 146 | ||
147 | enactTest' :: (FormulaM Stats Test) -> Sh GameState (Maybe TestResult) | 147 | enactTest' :: (FormulaM Stats Test) -> Sh GameState (Maybe TestResult) |
148 | enactTest' test = withFocus' $ \focus -> do | 148 | enactTest' test = withFocus' $ \focus -> do |
149 | (newStats, result) <- evalFormula (view eStats focus) (enactTest =<< test) | 149 | (newFocus, result) <- evalFormula focus (enactTest =<< test) |
150 | gFocus'.eStats .= newStats | 150 | gFocus' .= newFocus |
151 | return result | 151 | return result |
152 | 152 | ||
diff --git a/src/Sequence/Formula.hs b/src/Sequence/Formula.hs index 0d99fc0..9000c58 100644 --- a/src/Sequence/Formula.hs +++ b/src/Sequence/Formula.hs | |||
@@ -1,13 +1,14 @@ | |||
1 | {-# LANGUAGE RecordWildCards, RankNTypes, TypeSynonymInstances, FlexibleInstances, MultiParamTypeClasses, ViewPatterns, TypeFamilies #-} | 1 | {-# LANGUAGE RecordWildCards, RankNTypes, TypeSynonymInstances, FlexibleInstances, MultiParamTypeClasses, ViewPatterns, TypeFamilies, GADTs, TypeOperators, ExistentialQuantification, FlexibleContexts #-} |
2 | 2 | ||
3 | module Sequence.Formula | 3 | module Sequence.Formula |
4 | ( FormulaM, Formula, quot' | 4 | ( FormulaM, Formula, quot' |
5 | , (:<:)(..), Context(..) | ||
5 | , evalFormula | 6 | , evalFormula |
6 | , val | 7 | , val |
7 | , d, z | 8 | , d, z |
8 | ) where | 9 | ) where |
9 | 10 | ||
10 | import Control.Lens | 11 | import Control.Lens hiding (Context(..)) |
11 | import Data.Data.Lens | 12 | import Data.Data.Lens |
12 | 13 | ||
13 | import Control.Monad | 14 | import Control.Monad |
@@ -30,8 +31,27 @@ import Data.Either | |||
30 | import Data.Set (Set) | 31 | import Data.Set (Set) |
31 | import qualified Data.Set as Set | 32 | import qualified Data.Set as Set |
32 | 33 | ||
34 | class (:<:) small large where | ||
35 | ctx' :: Traversal' large small | ||
33 | 36 | ||
34 | type FormulaM input a = StateT (Set String) (ReaderT input (ExceptT (Question input) EventM)) a | 37 | instance a :<: a where |
38 | ctx' = simple | ||
39 | |||
40 | instance a :<: (a, a) where | ||
41 | ctx' = both | ||
42 | |||
43 | instance a :<: (a, b) where | ||
44 | ctx' = _1 | ||
45 | |||
46 | instance a :<: (b, a) where | ||
47 | ctx' = _2 | ||
48 | |||
49 | data Context small = forall large. (small :<: large) => Context large | ||
50 | |||
51 | ctx :: Traversal' (Context input) input | ||
52 | ctx modifySmall (Context large) = Context <$> ctx' modifySmall large | ||
53 | |||
54 | type FormulaM input a = StateT (Set String) (ReaderT (Context input) (ExceptT (Question input) EventM)) a | ||
35 | 55 | ||
36 | type Formula input = FormulaM input Int | 56 | type Formula input = FormulaM input Int |
37 | 57 | ||
@@ -66,22 +86,22 @@ instance Integral a => Num (FormulaM input a) where | |||
66 | quot' :: Integral a => FormulaM input a -> FormulaM input a -> FormulaM input a | 86 | quot' :: Integral a => FormulaM input a -> FormulaM input a -> FormulaM input a |
67 | quot' = liftM2 quot | 87 | quot' = liftM2 quot |
68 | 88 | ||
69 | askQuestion :: MonadIO m => input -> (Question input) -> m input | 89 | askQuestion :: (MonadIO m, sInput :<: lInput) => lInput -> Question sInput -> m lInput |
70 | askQuestion input q@(Question{..}) = flip (set answer) input . maybe (throwError q) return <$> askQ prompt (join . fmap readMaybe) | 90 | askQuestion input q@(Question{..}) = flip (set $ ctx' . answer) input . maybe (throwError q) return <$> askQ prompt (join . fmap readMaybe) |
71 | 91 | ||
72 | evalFormula :: (MonadIO m, Ord a, Show a) => input -> FormulaM input a -> m (input, a) | 92 | evalFormula :: (MonadIO m, sInput :<: lInput) => lInput -> FormulaM sInput a -> m (lInput, a) |
73 | evalFormula = evalFormula' [] | 93 | evalFormula = evalFormula' [] |
74 | where | 94 | where |
75 | evalFormula' finalChanges input formula = do | 95 | evalFormula' finalChanges input formula = do |
76 | result <- liftIO . enact . runExceptT . (runReaderT ?? input) . (evalStateT ?? Set.empty) $ formula | 96 | result <- liftIO . enact . runExceptT . (runReaderT ?? (Context input)) . (evalStateT ?? Set.empty) $ formula |
77 | case result of | 97 | case result of |
78 | Left q@(Question{..}) -> askQuestion input q >>= flip (evalFormula' $ bool (pure . set answer $ throwError q) mempty keepResult ++ finalChanges) formula | 98 | Left q@(Question{..}) -> askQuestion input q >>= flip (evalFormula' $ bool (pure . set (ctx' . answer) $ throwError q) mempty keepResult ++ finalChanges) formula |
79 | Right result -> return (foldr ($) input finalChanges, result) | 99 | Right result -> return (foldr ($) input finalChanges, result) |
80 | 100 | ||
81 | val :: Integral a => Traversal' input (Formula input) -> String -> Bool -> Formula input | 101 | val :: Integral a => Traversal' input (Formula input) -> String -> Bool -> Formula input |
82 | val answer prompt keepResult = do | 102 | val answer prompt keepResult = do |
83 | gets (Set.member prompt) >>= bool (modify $ Set.insert prompt) (modify (Set.delete prompt) >> throwError Question{..}) | 103 | gets (Set.member prompt) >>= bool (modify $ Set.insert prompt) (modify (Set.delete prompt) >> throwError Question{..}) |
84 | preview answer >>= maybe (throwError Question{..}) id | 104 | preview (ctx . answer) >>= maybe (throwError Question{..}) id |
85 | 105 | ||
86 | d, z :: Integral a => Int -> FormulaM input a | 106 | d, z :: Integral a => Int -> FormulaM input a |
87 | d n = liftBase . fmap fromIntegral $ D.d n | 107 | d n = liftBase . fmap fromIntegral $ D.d n |
diff --git a/src/Sequence/Types.hs b/src/Sequence/Types.hs index 541505c..480dfee 100644 --- a/src/Sequence/Types.hs +++ b/src/Sequence/Types.hs | |||
@@ -1,4 +1,4 @@ | |||
1 | {-# LANGUAGE FlexibleInstances, FlexibleContexts, MultiParamTypeClasses, TypeSynonymInstances, ViewPatterns, OverloadedStrings, TemplateHaskell, GeneralizedNewtypeDeriving #-} | 1 | {-# LANGUAGE FlexibleInstances, FlexibleContexts, MultiParamTypeClasses, TypeSynonymInstances, ViewPatterns, OverloadedStrings, TemplateHaskell, GeneralizedNewtypeDeriving, TypeOperators #-} |
2 | 2 | ||
3 | module Sequence.Types | 3 | module Sequence.Types |
4 | ( GameState, gEntities, gEntityNames, gFocus, gNextId' | 4 | ( GameState, gEntities, gEntityNames, gFocus, gNextId' |
@@ -33,6 +33,7 @@ import Data.Tuple | |||
33 | import Data.Ord | 33 | import Data.Ord |
34 | 34 | ||
35 | import Sequence.Contact.Types | 35 | import Sequence.Contact.Types |
36 | import Sequence.Formula ((:<:)(..)) | ||
36 | 37 | ||
37 | import Text.Read (readMaybe) | 38 | import Text.Read (readMaybe) |
38 | 39 | ||
@@ -77,6 +78,9 @@ instance Default Entity where | |||
77 | , _eStats = def | 78 | , _eStats = def |
78 | } | 79 | } |
79 | 80 | ||
81 | instance Stats :<: Entity where | ||
82 | ctx' = eStats | ||
83 | |||
80 | newtype EntityName = EntityName { _entityName :: CI String } | 84 | newtype EntityName = EntityName { _entityName :: CI String } |
81 | deriving (Show, Eq, Ord) | 85 | deriving (Show, Eq, Ord) |
82 | 86 | ||