[Haskell-cafe] What Does Graham Hutton Mean by Effect

Brandon Allbery allbery.b at gmail.com
Tue Oct 31 02:02:34 UTC 2017


In this specific case it is actually pure, because Maybe is pure, but in
the general case it behaves with respect to Applicative (and Monad, which
this appears to be leading up to) as effectful. In this context, an effect
is just whatever behavior is captured by the Applicative/Monad.

"purity" is a bit overloaded:

- purity with respect to an effect of some unspecified kind, as here;

- purity with respect to IO which encapsulates behavior not contained
specifically within your program, the most common meaning in Haskell;

- purity with respect to cross-thread effects in IO/STM;

- purity with respect to mutability in ST;

....


On Mon, Oct 30, 2017 at 9:49 PM, Steven Leiva <leiva.steven at gmail.com>
wrote:

> 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 where
> data Expr = Val Int | Div Expr Expr
> eval :: Expr -> Int
> eval (Val n) = n
> eval (Div el er) = eval el `div` eval er
>
>                 [image: Mixmax]
> <https://mixmax.com/r/59ec918e83319a2a077ff18c> Not using Mixmax yet?
> <https://mixmax.com/r/59ec918e83319a2a077ff18c>
>
>
> 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 where
> data Expr = Val Int | Div Expr Expr
> eval :: Expr -> Maybe Int
> eval (Val n) = Just n
> eval (Div el er) = case eval el of
>                     Nothing -> Nothing
>                     Just y -> case eval er of
>                                 Nothing -> Nothing
>                                 Just x -> y `safeDiv` x
> safeDiv :: Int -> Int -> Maybe Int
> safeDiv x y
>     | y == 0 = Nothing
>     | otherwise = Just (x `div` y)
>
>                 [image: Mixmax]
> <https://mixmax.com/r/59ec918e83319a2a077ff18c> Not using Mixmax yet?
> <https://mixmax.com/r/59ec918e83319a2a077ff18c>
>
>
> 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 <(305)%20528-6038>
> leiva.steven at gmail.com
> http://www.linkedin.com/in/stevenleiva
>
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.
>



-- 
brandon s allbery kf8nh                               sine nomine associates
allbery.b at gmail.com                                  ballbery at sinenomine.net
unix, openafs, kerberos, infrastructure, xmonad        http://sinenomine.net
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20171030/defe2229/attachment.html>


More information about the Haskell-Cafe mailing list