summaryrefslogtreecommitdiff
path: root/src/Sequence/Formula.hs
blob: fc61efb5b297e94779acc19719dba60ea1403de8 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
{-# LANGUAGE RecordWildCards, RankNTypes, TypeSynonymInstances, FlexibleInstances, MultiParamTypeClasses, ViewPatterns, TypeFamilies #-}

module Sequence.Formula
  ( FormulaM, Formula
  , evalFormula
  , val
  , d, z
  ) where

import Control.Lens
import Data.Data.Lens
import Data.Data (Data)
import Data.Typeable (Typeable)

import Control.Monad.Except
import Control.Monad.Reader
import Numeric.Probability.Game.Event
import qualified Numeric.Probability.Game.Dice as D

import Sequence.Utils.Ask

import Text.Read (readMaybe)

import Data.Bool
import Data.List
import Data.Maybe


type FormulaM input a = ReaderT input (ExceptT (Question input) EventM) a

type Formula input = Formulam input Int

data Question input = Question
                      { answer :: Traversal' input (Formula input)
                      , prompt :: String
                      , keepResult :: Bool
                      }

instance Integral a => Num (FormulaM input a) where
  (+) x y = (+) <$> x <*> y
  (-) x y = (-) <$> x <*> y
  negate = fmap negate
  abs = fmap abs
  signum = fmap signum
  (*) x y = do n <- x
               sum <$> replicateM (fromIntegral n) y
  fromInteger = return . fromInteger


askQuestion :: MonadIO m => input -> (Question input) -> m input
askQuestion input q@(Question{..}) = flip (set answer) input . maybe (throwError q) return <$> askQ prompt (join . fmap readMaybe)

evalFormula :: MonadIO m => input -> FormulaM input a -> m (input, a)
evalFormula = evalFormula' []
  where
    evalFormula' finalChanges input formula = do
      result <- liftIO . enact . runExceptT . (runReaderT ?? input) $ formula
      case result of
        Left q@(Question{..}) -> askQuestion input q >>= flip (evalFormula' $ bool (pure . set answer $ throwError q) mempty keepResult ++ finalChanges) formula
        Right result -> return (foldr ($) input finalChanges, result)

val :: Integral a => Traversal' input (Formula input) -> String -> Bool -> Formula input
val answer prompt keepResult = preview answer >>= maybe (throwError Question{..}) id

-- viewL :: Lens' lInput sInput -> Prism' (FormulaM sInput a) (FormulaM lInput a)
-- viewL lTrav = iso asL asS
--   where
--     asL small = join $ lift . withExceptT (\Question{..} -> Question{ answer = lTrav . answer . viewL lTrav, .. }) . runReaderT small <$> view lTrav
--     asS :: FormulaM lInput a -> FormulaM sInput a
--     asS large = undefined

-- val' :: Integral a => Lens' lInput sInput -> Traversal' sInput (FormulaM sInput Int) -> String -> Bool -> FormulaM lInput Int
-- val' lTrav sTrav prompt keepResult = preview (lTrav . sTrav . viewL lTrav) >>= maybe (throwError Question{ answer = lTrav . sTrav . viewL lTrav, ..}) id

d, z :: Integral a => Int -> FormulaM input a
d n = lift . lift . fmap fromIntegral $ D.d n
z n = lift . lift . fmap fromIntegral $ D.z n