 
            Hi Everyone, I am reading the 2nd edition of Graham Hutton's Programming in Haskell. I'm not reading the entire book, just the parts of Haskell that I am still iffy on. Anyway, in Chapter 12, Section 3, Hutton introduces monads. He start off with the following code: first module Expr wheredata Expr = Val Int | Div Expr Expreval :: Expr -> Inteval (Val n) = neval (Div el er) = eval el `div` eval er Not using Mixmax yet? And then he points out that the second clause of eval will raise an error if eval er evaluates to 0. One solution is that, instead of using the div function, we use a safeDiv:: Int -> Int -> Maybe Int function, which evaluate to Nothing if the divisor is 0. This means that expr's type changes from eval :: Eval -> Int to eval :: Eval -> Maybe Int, and this means that implementing eval becomes very verbose: second module Expr wheredata Expr = Val Int | Div Expr Expreval :: Expr -> Maybe Inteval (Val n) = Just neval (Div el er) = case eval el of Nothing -> Nothing Just y -> case eval er of Nothing -> Nothing Just x -> y `safeDiv` xsafeDiv :: Int -> Int -> Maybe IntsafeDiv x y | y == 0 = Nothing | otherwise = Just (x `div` y) Not using Mixmax yet? In order to make eval more concise, we can try the applicative style, where the second clause of the eval function becomes pure safeDiv <*> eval el <*> eval er. Of course, that doesn't work because pure safeDiv has the type Int -> Int -> Maybe Int, and what we need is a function of type Int -> Int -> Int. Anyways, this is all setup / context to what Hutton says next: The conclusion is that the function eval does not fit the pattern of effectful programming that is capture by applicative functors. The applicative style restricts us to applying pure functions to effectful arguments: eval does not fit this pattern because the function safeDiv that is used to process the resulting values is not a pure function, but may itself fail. I am confused by Hutton's use of the word effectful and by his description of safeDiv as "not a pure function". I tried skimming the other sections of the book to see if he provided a definition of this somewhere, but if he did, I couldn't find it. So my question is, in what way does Hutton mean for the reader to understand the words effect / effectful, and why does he describe the function safeDiv as not a pure function? Thank you! Steven Leiva 305.528.6038 leiva.steven@gmail.com http://www.linkedin.com/in/stevenleiva