diff --git a/exercises/chapter11/src/Data/GameState.purs b/exercises/chapter11/src/Data/GameState.purs index 0f53c1b86..6d05764e8 100644 --- a/exercises/chapter11/src/Data/GameState.purs +++ b/exercises/chapter11/src/Data/GameState.purs @@ -22,6 +22,8 @@ instance showGameState :: Show GameState where ", inventory: " <> show o.inventory <> " }" +derive instance eqGameState :: Eq GameState + initialGameState :: GameState initialGameState = GameState { items : M.fromFoldable [ Tuple (coords 0 1) (S.singleton Candle) diff --git a/exercises/chapter11/test/Main.purs b/exercises/chapter11/test/Main.purs index 2f266a8eb..7643f4e84 100644 --- a/exercises/chapter11/test/Main.purs +++ b/exercises/chapter11/test/Main.purs @@ -1,18 +1,26 @@ module Test.Main where -import Prelude (Unit, discard, ($), (<>)) - +import Prelude (Unit, discard, negate, ($), (*>), (<>), (==)) import Test.MySolutions +import Game import Test.NoPeeking.Solutions -- This line should have been automatically deleted by resetSolutions.sh. See Chapter 2 for instructions. -import Effect (Effect) -import Control.Monad.Writer (runWriterT, execWriter) import Control.Monad.Except (runExceptT) +import Control.Monad.RWS (RWSResult(..), runRWS) import Control.Monad.State (runStateT) +import Control.Monad.Writer (runWriterT, execWriter) import Data.Either (Either(..)) +import Data.GameEnvironment (GameEnvironment(..)) +import Data.GameItem (GameItem(..)) +import Data.GameState (GameState(..), initialGameState) +import Data.List (List, (:)) +import Data.List as L +import Data.Map as M import Data.Monoid.Additive (Additive(..)) import Data.Newtype (unwrap) +import Data.Set as S import Data.Tuple (Tuple(..)) +import Effect (Effect) import Test.Unit (TestSuite, success, suite, test) import Test.Unit.Assert as Assert import Test.Unit.Main (runTest) @@ -76,6 +84,12 @@ This line should have been automatically deleted by resetSolutions.sh. See Chapt Assert.equal expected_15 $ collatz 15 suite "Exercises Group - Monad Transformers" do + suite "safeDivide" do + test "should fail when dividing by zero" do + Assert.equal (Left "Divide by zero!") + $ unwrap $ runExceptT $ safeDivide 5 0 + test "should successfully divide for any other input" do + Assert.equal (Right 2) $ unwrap $ runExceptT $ safeDivide 6 3 suite "parser" do let runParser p s = unwrap $ runExceptT $ runWriterT $ runStateT p s @@ -129,5 +143,30 @@ This line should have been automatically deleted by resetSolutions.sh. See Chapt test "should fail if first is not a or b" do Assert.equal (Left ["Could not parse","Could not parse"]) $ runParser asOrBs "foobar" + + suite "Exercises Group - The RWS Monad" do + let + runGame :: Game Unit -> RWSResult GameState Unit (List String) + runGame testGame = runRWS testGame env initialGameState + env = GameEnvironment { debugMode: false, playerName: "Phil" } + + playerHasAllItems (GameState {inventory}) = inventory == S.fromFoldable [Candle, Matches] + mapIsEmpty (GameState {items}) = M.isEmpty items + expectedLogs = ("You now have the Candle" : "You now have the Matches" : L.Nil) + + suite "adds all items to your inventory when cheating" do + let + runCheatTest label testGame = + test label do + let (RWSResult actualState _ log) = runGame testGame + Assert.assert "Expected player to have both Candle and Matches" $ playerHasAllItems actualState + Assert.assert "Expected map to no longer have any items" $ mapIsEmpty actualState + Assert.equal expectedLogs $ L.sort log + + runCheatTest "only cheat" cheat + runCheatTest "move and cheat" $ move 0 (-1) *> move 0 1 *> cheat + runCheatTest "pickup matches and cheat" $ pickUp Matches *> cheat + runCheatTest "pickup all, move, and cheat" $ pickUp Matches *> move 0 1 *> pickUp Candle *> cheat + {- This line should have been automatically deleted by resetSolutions.sh. See Chapter 2 for instructions. -} \ No newline at end of file diff --git a/exercises/chapter11/test/no-peeking/Solutions.purs b/exercises/chapter11/test/no-peeking/Solutions.purs index 49aa50db6..a5099d4dc 100644 --- a/exercises/chapter11/test/no-peeking/Solutions.purs +++ b/exercises/chapter11/test/no-peeking/Solutions.purs @@ -8,17 +8,23 @@ import Control.Monad.Reader (Reader, ReaderT, ask, lift, local, runReader, runRe import Control.Monad.State (State, StateT, get, put, execState, modify_) import Control.Monad.Writer (Writer, WriterT, tell, runWriter, execWriterT) import Data.Array (some) -import Data.Foldable (fold) +import Data.Foldable (fold, foldl) +import Data.GameState (GameState(..)) import Data.Identity (Identity) +import Data.List ((:)) +import Data.List as L +import Data.Map as M import Data.Maybe (Maybe(..)) import Data.Monoid (power) import Data.Monoid.Additive (Additive(..)) import Data.Newtype (unwrap) +import Data.Set as S import Data.String (joinWith) import Data.String.CodeUnits (stripPrefix, toCharArray) import Data.String.Pattern (Pattern(..)) import Data.Traversable (sequence, traverse_) import Data.Tuple (Tuple) +import Game (Game) -- @@ -84,6 +90,12 @@ collatz c = runWriter $ cltz 0 c -- +safeDivide :: Int -> Int -> ExceptT String Identity Int +safeDivide _ 0 = throwError "Divide by zero!" +safeDivide a b = pure $ a / b + +-- + type Errors = Array String type Log = Array String type Parser = StateT String (WriterT Log (ExceptT Errors Identity)) @@ -123,4 +135,12 @@ asFollowedByBs = do pure $ fold $ as <> bs asOrBs :: Parser String -asOrBs = fold <$> some (string "a" <|> string "b") \ No newline at end of file +asOrBs = fold <$> some (string "a" <|> string "b") + +-- Note, that this function should be defined in Game.purs to avoid creating a circular dependency. +cheat :: Game Unit +cheat = do + GameState state <- get + let newInventory = foldl S.union state.inventory state.items + tell $ foldl (\acc x -> ("You now have the " <> show x) : acc) L.Nil $ S.unions state.items + put $ GameState state { items = M.empty, inventory = newInventory } diff --git a/text/chapter11.md b/text/chapter11.md index fc204978f..b9015cd11 100644 --- a/text/chapter11.md +++ b/text/chapter11.md @@ -545,7 +545,7 @@ Fortunately, as we will see, we can use the automatic code generation provided b ## Exercises - 1. (Easy) Use the `ExceptT` monad transformer over the `Identity` functor to write a function `safeDivide` which divides two numbers, throwing an error if the denominator is zero. + 1. (Easy) Use the `ExceptT` monad transformer over the `Identity` functor to write a function `safeDivide` which divides two numbers, throwing an error (as the String "Divide by zero!") if the denominator is zero. 1. (Medium) Write a parser ```haskell @@ -564,7 +564,7 @@ Fortunately, as we will see, we can use the automatic code generation provided b _Hint_: you can use the implementation of `split` as a starting point. You might find the `stripPrefix` function useful. 1. (Difficult) Use the `ReaderT` and `WriterT` monad transformers to reimplement the document printing library which we wrote earlier using the `Reader` monad. - Instead of using `line` to emit strings and `cat` to concatenate strings, use the `Array String` monoid with the `WriterT` monad transformer, and `tell` to append a line to the result. + Instead of using `line` to emit strings and `cat` to concatenate strings, use the `Array String` monoid with the `WriterT` monad transformer, and `tell` to append a line to the result. Use the same names as in the original implementation but ending with an apostrophe (`'`). ## Type Classes to the Rescue! @@ -731,7 +731,7 @@ Again, this illustrates the power of reusability that monad transformers bring - ## Exercises 1. (Easy) Remove the calls to the `lift` function from your implementation of the `string` parser. Verify that the new implementation type checks, and convince yourself that it should. - 1. (Medium) Use your `string` parser with the `many` combinator to write a parser `asFollowedByBs` which recognizes strings consisting of several copies of the string `"a"` followed by several copies of the string `"b"`. + 1. (Medium) Use your `string` parser with the `some` combinator to write a parser `asFollowedByBs` which recognizes strings consisting of several copies of the string `"a"` followed by several copies of the string `"b"`. 1. (Medium) Use the `<|>` operator to write a parser `asOrBs` which recognizes strings of the letters `a` or `b` in any order. 1. (Difficult) The `Parser` monad might also be defined as follows: @@ -965,10 +965,10 @@ The `runGame` function finally attaches the initial line handler to the console ## Exercises - 1. (Medium) Implement a new command `cheat`, which moves all game items from the game grid into the user's inventory. + 1. (Medium) Implement a new command `cheat`, which moves all game items from the game grid into the user's inventory. Create a function `cheat :: Game Unit` in the `Game` module, and use this function from `game`. 1. (Difficult) The `Writer` component of the `RWS` monad is currently used for two types of messages: error messages and informational messages. Because of this, several parts of the code use case statements to handle error cases. - Refactor the code to use the `ExceptT` monad transformer to handle the error messages, and `RWS` to handle informational messages. + Refactor the code to use the `ExceptT` monad transformer to handle the error messages, and `RWS` to handle informational messages. _Note:_ There are no tests for this exercise. ## Handling Command Line Options