[Snapshot Bryan O'Sullivan **20080212231919] { addfile ./examples/ch16/VCard.hs hunk ./en/ch05-fp.xml 717 - We call the non-recursive case (when the list is empty) - the base case. We'll see people refer to the case where the - function calls itself as the recursive case (surprise!), or - they might give a nod to mathematical induction and call it - the inductive case. + We call the non-recursive case (when the list is + empty) the base case. We'll see people + refer to the case where the function calls itself as the + recursive case (surprise!), or they might give a nod to + mathematical induction and call it the inductive + case. hunk ./en/ch16-monad-case.xml 3 - - Some monad examples + + Programming with monads hunk ./en/ch16-monad-case.xml 128 + + Looking for alternatives + + Here's a simple representation of a person's phone + numbers. + + &VCard.hs:numbers; + + Suppose we want to get in touch with someone to make a + personal call. We don't want their business number, and we'd + prefer to use their home number (if they have one) instead of + their mobile number, because the call will be cheaper. + + &VCard.hs:personalPhone; + + Of course, if we use Maybe as the result type, + we can't accommodate the possibility that someone might have + more than one number that meet our criteria. For that, we + switch to a list. + + &VCard.hs:businessPhones; + + Notice that these two functions structure their &case; + expressions similarly: one alternative handles the case where + the first lookup returns an empty result, while the other + handles the non-empty case. + + &vcard.ghci:simple; + + Haskell's Control.Monad module defines a + typeclass, MonadPlus, that lets us abstract the + common pattern out of our &case; expressions. + + &VCard.hs:MonadPlus; + + The value mzero represents an empty result, + while mplus combines two results. Here are + the standard definitions of mzero and + mplus for Maybe and + lists. + + &VCard.hs:instances; + + We can now use mplus to get rid of our + &case; expressions entirely. + + &VCard.hs:caseless; + + In these functions, because we know that + lookup returns a value of type + Maybe, and filter returns a + list, it's obvious which version of mplus + is going to be used in each case. + + What's more interesting is that we can use + mzero and mplus to write + functions that will be useful for any + MonadPlus instance. As an example, here's the + standard lookup function, which returns a + value of type Maybe. + + &VCard.hs:lookup; + + We can easily generalise the result type to any instance of + MonadPlus as follows. + + &VCard.hs:lookupM; + + This lets us get either no result or one, if our result type + is Maybe; all results, if our result type is a + list; or something of appropriate for some other exotic instance + of MonadPlus. + hunk ./examples/ch16/VCard.hs 1 +import Prelude hiding (lookup) + +{-- snippet MonadPlus --} +class Monad m => MonadPlus m where + mzero :: m a + mplus :: m a -> m a -> m a +{-- /snippet MonadPlus --} + +{-- snippet instances --} +instance MonadPlus [] where + mzero = [] + mplus = (++) + +instance MonadPlus Maybe where + mzero = Nothing + + Nothing `mplus` ys = ys + xs `mplus` _ = xs +{-- /snippet instances --} + +{-- snippet numbers --} +data Context = Home | Mobile | Business + deriving (Eq, Show) + +type Phone = String + +albulena = [(Home, "+355-652-55512")] + +nils = [(Mobile, "+47-922-55-512"), (Business, "+47-922-12-121"), + (Home, "+47-925-55-121"), (Business, "+47-922-25-551")] + +twalumba = [(Business, "+260-02-55-5121")] +{-- /snippet numbers --} + +{-- snippet personalPhone --} +personalPhone :: [(Context, Phone)] -> Maybe Phone + +personalPhone ps = case lookup Home ps of + Nothing -> lookup Mobile ps + Just n -> Just n +{-- /snippet personalPhone --} + +{-- snippet businessPhones --} +businessPhones ps = map snd numbers + where numbers = case filter (contextIs Business) ps of + [] -> filter (contextIs Mobile) ps + ns -> ns + +contextIs a (b, _) = a == b +{-- /snippet businessPhones --} + +{-- snippet caseless --} +businessPhone :: [(Context, Phone)] -> Maybe Phone +businessPhone ps = lookup Business ps `mplus` lookup Mobile ps + +personalPhones :: [(Context, Phone)] -> [Phone] +personalPhones ps = map snd $ filter (contextIs Home) ps `mplus` + filter (contextIs Mobile) ps +{-- /snippet caseless --} + +{-- snippet lookup --} +lookup :: (Eq a) => a -> [(a, b)] -> Maybe b +lookup _ [] = Nothing +lookup k ((x,y):xys) | x == k = Just y + | otherwise = lookup k xys +{-- /snippet lookup --} + +{-- snippet lookupM --} +lookupM :: (MonadPlus m, Eq a) => a -> [(a, b)] -> m b +lookupM _ [] = mzero +lookupM k ((x,y):xys) + | x == k = return y `mplus` lookupM k xys + | otherwise = lookupM k xys +{-- /snippet lookupM --} }