Haskell logo CIS 5520: Advanced Programming

Fall 2023

  • Home
  • Schedule
  • Homework
  • Resources
  • Software
  • Style guide
Note: this is the completed version of lecture MaybePractice.

In class exercise: Practice with Maybe Monad

The goal of this short in-class exercise is to get a bit more practice with using the Maybe Monad.

> module MaybePractice where
> import qualified Control.Monad as Monad
> import Data.Map (Map)
> import qualified Data.Map as Map
> import qualified Text.Read as Text

Part 1

Consider the Weather datatype from the Kata problem from HW #3.

> data Weather = Weather {
>     dayNumber :: Int, maxTemp :: Int, minTemp :: Int 
>     } deriving (Eq, Show)

Use Map.lookup and Text.readMaybe to write a function that takes a dictionary (i.e. a finite map from String keys to String values) and converts it into weather data. Your implementation should not use pattern matching; use do notation instead.

If the provided dictionary does not have the appropriate data, then the function should return Nothing. In other words, this function should behave according to the examples below.

> -- >>> parseWeather (Map.fromList [("day", "2"), ("maxTemp", "78"), ("minTemp", "62")])
> -- Just (Weather {dayNumber = 2, maxTemp = 78, minTemp = 62})
> -- >>> parseWeather (Map.fromList [("day", "2")])
> -- Nothing
> -- >>> parseWeather (Map.fromList [("day", "two"), ("maxTemp", "78"), ("minTemp", "62")])
> -- Nothing
> parseWeather :: Map String String -> Maybe Weather
> 
> parseWeather m = do
>     dayString <- Map.lookup "day" m
>     day <- Text.readMaybe dayString
>     maxString <- Map.lookup "maxTemp" m
>     maxT <- Text.readMaybe maxString
>     minString <- Map.lookup "minTemp" m
>     minT <- Text.readMaybe minString
>     return Weather {dayNumber=day, maxTemp=maxT, minTemp=minT}
> 
> -- now try to write a shorter version that uses the Applicative operators (and >=>)

Part 2

Consider the following operations that combine two Maybes. Implement them both. One can be defined using (>>=) from the Maybe monad, and one cannot. Which is which?

> -- | Left-biased choice on maybes
> --
> -- >>> firstJust (Just 1) (Just 2)
> -- Just 1
> -- >>> firstJust Nothing (Just 2)
> -- Just 2
> -- >>> firstJust (Just 1) Nothing
> -- Just 1
> -- >>> firstJust Nothing Nothing
> -- Nothing
> firstJust :: Maybe a -> Maybe a -> Maybe a
> 
> firstJust (Just x) _ = Just x
> firstJust Nothing  m = m
> -- note, this can be generalized to the `(<|>)` operator
> -- from the Alternative type class (defined in Control.Applicative).
> -- | Ensure that both Maybes are 'Just' and retain the first one
> -- 
> -- >>> sequenceFirst (Just 1) (Just 'a')
> -- Just 1
> -- >>> sequenceFirst Nothing (Just 'a')
> -- Nothing
> -- >>> sequenceFirst (Just 1) Nothing
> -- Nothing
> -- >>> sequenceFirst Nothing Nothing
> -- Nothing
> sequenceFirst :: Maybe a -> Maybe b -> Maybe a
> 
> sequenceFirst m1 m2 = do
>    x <- m1
>    _ <- m2
>    return x
> 
> -- Extra definitions for comparison with the above.
> 
> -- | Right-biased choice on maybes
> --
> -- >>> secondJust (Just 1) (Just 2)
> -- Just 2
> -- >>> secondJust Nothing (Just 2)
> -- Just 2
> -- >>> secondJust (Just 1) Nothing
> -- Just 1
> -- >>> secondJust Nothing Nothing
> -- Nothing
> secondJust :: Maybe a -> Maybe a -> Maybe a
> secondJust _ (Just x) = Just x
> secondJust m Nothing  = m
> 
> -- | Ensure that both Maybes are 'Just' and retain the second one
> -- 
> -- >>> sequenceSecond (Just 1) (Just 'a')
> -- Just 1
> -- >>> sequenceSecond Nothing (Just 'a')
> -- Nothing
> -- >>> sequenceSecond (Just 1) Nothing
> -- Nothing
> -- >>> sequenceSecond Nothing Nothing
> -- Nothing
> 
> sequenceSecond :: Maybe a -> Maybe b -> Maybe b
> sequenceSecond m1 m2 = do
>    _ <- m1
>    m2
> 
> -- | Ensure both Maybes are 'Just' and apply a function to combine 
> -- if so
> -- >>> sequenceBoth (+) (Just 1) (Just 2)
> -- Just 3
> -- >>> sequenceBoth (+) (Just 1) Nothing
> -- Nothing
> -- >>> sequenceBoth (+) Nothing (Just 2)
> -- Nothing
> 
> sequenceBoth :: (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c
> sequenceBoth = Monad.liftM2
Design adapted from Minimalistic Design | Powered by Pandoc and Hakyll