All About Monads/Solutions

From HaskellWiki
< All About Monads
Revision as of 02:33, 7 January 2022 by Derifatives (talk | contribs) (→‎For exercise 4)
(diff) ← Older revision | Latest revision (diff) | Newer revision → (diff)
Jump to navigation Jump to search

For exercise 1

maternalGrandfather :: Sheep -> Maybe Sheep
maternalGrandfather s =
   return s    >>= \ms  ->
   mother ms   >>= \m   ->
   father m

fathersMaternalGrandmother :: Sheep -> Maybe Sheep
fathersMaternalGrandMother s =
   return s    >>= \ms  ->
   father ms   >>= \f   ->
   mother s    >>= \gm  ->
   mother gm

mothersPaternalGrandfather :: Sheep -> Maybe Sheep
mothersPaternalGrandfather s = 
   return s    >>= \ms  ->
   mother ms   >>= \m   ->
   father m    >>= \gf  ->
   father gf

Note: the returns are not not necessary; they are only used for the sake of the exercise.

An alternative solution without use of return:

maternalGrandfather :: Sheep -> Maybe Sheep
maternalGrandfather s =
   mother s    >>= \m   ->
   father m

fathersMaternalGrandmother :: Sheep -> Maybe Sheep
fathersMaternalGrandMother s =
   father s    >>= \f   ->
   mother s    >>= \gm  ->
   mother gm

mothersPaternalGrandfather :: Sheep -> Maybe Sheep
mothersPaternalGrandfather s = 
   mother s    >>= \m   ->
   father m    >>= \gf  ->
   father gf


For exercise 2

parent :: Sheep -> Maybe Sheep
parent s = father s `mplus` mother s

grandparent :: Sheep -> Maybe Sheep
grandparent s = paternalGrandfather s `mplus` 
                paternalGrandmother s `mplus` 
                maternalGrandfather s `mplus` 
                maternalGrandmother s


This next solution will not work. If the sheep has a father and only a maternal grandparent, this function will return Nothing:

grandparent :: Sheep -> Maybe Sheep
grandparent s = parent s >>= parent


For exercise 3

parent :: Sheep -> [Sheep]
parent s = (maybeToList (mother s)) ++ (maybeToList (father s))

grandparent :: Sheep -> [Sheep]
grandparent s = (maybeToList (paternalGrandfather s)) ++
                (maybeToList (paternalGrandmother s)) ++
                (maybeToList (maternalGrandfather s)) ++
                (maybeToList (maternalGrandmother s))

Alternate solution:

parent :: Sheep -> [Sheep]
parent s = (maybeToList $ mother s) `mplus` (maybeToList $ father s)

grandparent :: Sheep -> [Sheep]
grandparent s = parent s >>= parent


For exercise 4

parent :: MonadPlus m => Sheep -> m Sheep
parent s = (toMonad (father s)) `mplus` (toMonad (mother s))

grandparent :: MonadPlus m => Sheep -> m Sheep
grandparent s = (toMonad (paternalGrandfather s)) `mplus`
                (toMonad (paternalGrandmother s)) `mplus`
                (toMonad (maternalGrandfather s)) `mplus`
                (toMonad (maternalGrandmother s))

toMonad :: MonadPlus m => Maybe a -> m a
toMonad Nothing = mzero
toMonad (Just s) = return s

If the compiler cannot guess which MonadPlus to use you will need to specify it when the function is called. So, parent someSheep :: Maybe Sheep will use the Maybe monad and either parent someSheep :: [] Sheep or parent someSheep :: [Sheep] will use the list monad.


This next alternative grandparent function only works in the case of the list monad (see exercise 5.2 for why the Maybe monad does not work):

grandparent :: (MonadPlus m) => Sheep -> m Sheep
grandparent s = parent s >>= parent