Skip to content

Commit

Permalink
Update problem 79
Browse files Browse the repository at this point in the history
  • Loading branch information
Abhijit Sarkar committed Jan 3, 2024
1 parent f2d6bbc commit 071dc24
Show file tree
Hide file tree
Showing 4 changed files with 33 additions and 21 deletions.
1 change: 1 addition & 0 deletions ninety-nine-haskell.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -54,6 +54,7 @@ library
, psqueues
, random
, split
, transformers
, vector
default-language: Haskell2010

Expand Down
1 change: 1 addition & 0 deletions package.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -53,6 +53,7 @@ library:
- random
- array
- mtl
- transformers
- psqueues
- hashable
- vector
Expand Down
23 changes: 13 additions & 10 deletions src/Monads.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleContexts #-}

module Monads
( Operator (..),
Expand All @@ -13,9 +12,10 @@ where
import qualified Control.Monad as M
import Control.Monad.State (StateT)
import qualified Control.Monad.State as S
import Control.Monad.Trans.Maybe (MaybeT)
import qualified Control.Monad.Trans.Maybe as MbT
import Control.Monad.Writer (Writer)
import qualified Control.Monad.Writer as W
import qualified Data.Maybe as Mb
import Data.Monoid (Sum (..))
import qualified Data.Monoid as Md

Expand Down Expand Up @@ -151,22 +151,25 @@ data Element = Operator Operator | Operand Integer deriving stock (Show, Eq)

type Stack = [Integer]

type Logger = Writer [(Stack, Maybe Operator)]
type Logs = [(Stack, Maybe Operator)]

type Result = Maybe Integer

type Calculation = MaybeT (StateT Stack (Writer Logs)) Integer

calculatePostfix :: [Element] -> (Result, [(Stack, Maybe Operator)])
calculatePostfix xs = (res, logs)
where
((res, _), logs) = W.runWriter $ S.runStateT (calc xs) []
((res, _), logs) = W.runWriter $ S.runStateT (MbT.runMaybeT (calc xs)) []

calc :: [Element] -> StateT Stack Logger Result
calc [] = S.gets result
calc (Operand n : xs) = S.get >>= loop xs Nothing . (n :)
calc (Operator op : xs) =
S.get >>= Mb.maybe (return Nothing) (loop xs (Just op)) . runOp op
calc :: [Element] -> Calculation
calc elems =
S.get >>= case elems of
[] -> result
(Operand n : xs) -> loop xs Nothing . (n :)
(Operator op : xs) -> runOp op M.>=> loop xs (Just op)

loop :: [Element] -> Maybe Operator -> Stack -> StateT Stack Logger Result
loop :: [Element] -> Maybe Operator -> Stack -> Calculation
loop xs op s = W.tell [(s, op)] >> S.put s >> calc xs

result :: (MonadFail m) => Stack -> m Integer
Expand Down
29 changes: 18 additions & 11 deletions test/MonadsSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -43,9 +43,22 @@ spec = do

describe "calculatePostfix" $ do
it "evaluates an expression in postfix notation" $ do
let xs =
[ ("8 5 4 10 + - 3 * negate +", Just 35),
("8 5 -", Just 3),
("8 6", Nothing),
("8 negate", Just (-8)),
("8 +", Nothing)
]
M.forM_ xs $ \(ex, res) -> do
let expr = parsePostfix ex
let result = calculatePostfix expr
fst result `shouldBe` res

it "logs each step of a computation" $ do
let expr = parsePostfix "8 5 4 10 + - 3 * negate +"
let result = calculatePostfix expr
fst result `shouldBe` Just 35

snd result
`shouldBe` [ ([8], Nothing),
([5, 8], Nothing),
Expand All @@ -59,17 +72,11 @@ spec = do
([35], Just Add)
]

let xs = [("8 5 -", Just 3), ("8 6", Nothing), ("8 negate", Just (-8)), ("8 +", Nothing)]

M.forM_ xs $ \(ex, res) -> do
let expr' = parsePostfix ex
let result' = calculatePostfix expr'
fst result' `shouldBe` res
it "logs each step of a failed computation" $ do
let expr = parsePostfix "1 2 * +"
let result = calculatePostfix expr

let expr2 = parsePostfix "1 2 * +"
let result2 = calculatePostfix expr2
fst result2 `shouldBe` Nothing
snd result2
snd result
`shouldBe` [ ([1], Nothing),
([2, 1], Nothing),
([2], Just Multiply)
Expand Down

0 comments on commit 071dc24

Please sign in to comment.