Re: [Haskell-cafe] Martin Odersky on "What's wrong with Monads"

Hi Rico, Rico Moorman wrote:
data Tree = Leaf Integer | Branch (Tree Integer) (Tree Integer)
amount:: Tree -> Integer amount (Leaf x) = x amount (Branch t1 t2) = amountt1 + amountt2
[...] additional requirement: "If the command-line flag --multiply is set, the function amount computes the product instead of the sum."
How would you implement this requirement in Haskell without changing the line "amount (Leaf x) = x"?
The (for me at least) most obvious way to do this would be, to make the operation to be applied to determine the amount (+ or *) an explicit parameter in the function's definition.
data Tree a = Leaf a | Branch (Tree a) (Tree a) amount :: (a -> a -> a) -> Tree a -> a amount fun (Leaf x) = x amount fun (Branch t1 t2) = amount fun t1 `fun` amount fun t2
I agree: This is the most obvious way, and also a very good way. I would probably do it like this.
Which drawbacks do you see besides increased verbosity?
Well, you did change the equation "amount (Leaf x) = x" to "amount fun (Leaf x) = x". In a larger example, this means that you need to change many lines of many functions, just to get the the value of fun from the point where it is known to the point where you need it.
[...] I am wondering which ways of doing this in Haskell you mean.
I thought of the following three options, but see also Nathan Howells email for another alternative (that is related to my option (1) below): (1) Implicit parameters: {-# LANGUAGE ImplicitParams #-} data Tree = Leaf Integer | Branch Tree Tree amount :: (?fun :: Integer -> Integer -> Integer) => Tree -> Integer amount (Leaf x) = x amount (Branch t1 t2) = ?fun (amount t1) (amount t2) (2) Lexical Scoping: data Tree = Leaf Integer | Branch Tree Tree amount :: (Integer -> Integer -> Integer) -> Tree -> Integer amount fun = amount where { amount (Leaf x) = x ; amount (Branch t1 t2) = fun (amount t1) (amount t2) } (3) UnsafePerformIO: import System.IO.Unsafe (unsafePerformIO) data Tree = Leaf Integer | Branch Tree Tree amount :: Tree -> Integer amount (Leaf x) = x amount (Branch t1 t2) = fun (amount t1) (amount t2) where fun = unsafePerformIO ... I'm not happy with any of these options. Personally, I would probably go ahead and transform the whole program just to get the value of fun to where it is needed. Nevertheless, having actually done this before, I understand why Martin Odersky doesn't like doing it :) Tillmann

I'm not happy with any of these options.
Why are you unhappy with the ImplicitParams option?
It's pretty much like resorting to a newtype, as it's been suggested before.
2012/6/27 Tillmann Rendel
Hi Rico,
Rico Moorman wrote:
data Tree = Leaf Integer | Branch (Tree Integer) (Tree Integer)
amount:: Tree -> Integer amount (Leaf x) = x amount (Branch t1 t2) = amountt1 + amountt2
[...] additional requirement: "If the command-line flag --multiply is set,
the function amount computes the product instead of the sum."
How would you implement this requirement in Haskell without changing the line "amount (Leaf x) = x"?
The (for me at least) most obvious way to do this would be, to make the
operation to be applied to determine the amount (+ or *) an explicit parameter in the function's definition.
data Tree a = Leaf a | Branch (Tree a) (Tree a) amount :: (a -> a -> a) -> Tree a -> a amount fun (Leaf x) = x amount fun (Branch t1 t2) = amount fun t1 `fun` amount fun t2
I agree: This is the most obvious way, and also a very good way. I would probably do it like this.
Which drawbacks do you see besides increased verbosity?
Well, you did change the equation "amount (Leaf x) = x" to "amount fun (Leaf x) = x". In a larger example, this means that you need to change many lines of many functions, just to get the the value of fun from the point where it is known to the point where you need it.
[...] I am wondering which ways of doing this in Haskell you mean.
I thought of the following three options, but see also Nathan Howells email for another alternative (that is related to my option (1) below):
(1) Implicit parameters:
{-# LANGUAGE ImplicitParams #-} data Tree = Leaf Integer | Branch Tree Tree
amount :: (?fun :: Integer -> Integer -> Integer) => Tree -> Integer
amount (Leaf x) = x amount (Branch t1 t2) = ?fun (amount t1) (amount t2)
(2) Lexical Scoping:
data Tree = Leaf Integer | Branch Tree Tree
amount :: (Integer -> Integer -> Integer) -> Tree -> Integer amount fun = amount where {
amount (Leaf x) = x ; amount (Branch t1 t2) = fun (amount t1) (amount t2) }
(3) UnsafePerformIO:
import System.IO.Unsafe (unsafePerformIO)
data Tree = Leaf Integer | Branch Tree Tree
amount :: Tree -> Integer amount (Leaf x) = x amount (Branch t1 t2) = fun (amount t1) (amount t2) where fun = unsafePerformIO ...
I'm not happy with any of these options. Personally, I would probably go ahead and transform the whole program just to get the value of fun to where it is needed. Nevertheless, having actually done this before, I understand why Martin Odersky doesn't like doing it :)
Tillmann
______________________________**_________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe

The "problem" of monads is that it defines different execution models,
besides the funcional,/lazy/declarative mode. There is no such problem in
imperative languages, which work ever in an hardwired IO monad. But this
means that the programmer has to code the extra behaviour needed in each
application to do the same.
I summarized this here:
http://haskell-web.blogspot.com.es/2012/06/intuitive-explanation-of-algorith...
It pretend to be intuitive, not accurate. (See disclaimer ;) . Comments
welcome
2012/6/27 Yves Parès
I'm not happy with any of these options.
Why are you unhappy with the ImplicitParams option?
It's pretty much like resorting to a newtype, as it's been suggested before.
2012/6/27 Tillmann Rendel
Hi Rico,
Rico Moorman wrote:
data Tree = Leaf Integer | Branch (Tree Integer) (Tree Integer)
amount:: Tree -> Integer amount (Leaf x) = x amount (Branch t1 t2) = amountt1 + amountt2
[...] additional requirement: "If the command-line flag --multiply is set,
the function amount computes the product instead of the sum."
How would you implement this requirement in Haskell without changing the line "amount (Leaf x) = x"?
The (for me at least) most obvious way to do this would be, to make the
operation to be applied to determine the amount (+ or *) an explicit parameter in the function's definition.
data Tree a = Leaf a | Branch (Tree a) (Tree a) amount :: (a -> a -> a) -> Tree a -> a amount fun (Leaf x) = x amount fun (Branch t1 t2) = amount fun t1 `fun` amount fun t2
I agree: This is the most obvious way, and also a very good way. I would probably do it like this.
Which drawbacks do you see besides increased verbosity?
Well, you did change the equation "amount (Leaf x) = x" to "amount fun (Leaf x) = x". In a larger example, this means that you need to change many lines of many functions, just to get the the value of fun from the point where it is known to the point where you need it.
[...] I am wondering which ways of doing this in Haskell you mean.
I thought of the following three options, but see also Nathan Howells email for another alternative (that is related to my option (1) below):
(1) Implicit parameters:
{-# LANGUAGE ImplicitParams #-} data Tree = Leaf Integer | Branch Tree Tree
amount :: (?fun :: Integer -> Integer -> Integer) => Tree -> Integer
amount (Leaf x) = x amount (Branch t1 t2) = ?fun (amount t1) (amount t2)
(2) Lexical Scoping:
data Tree = Leaf Integer | Branch Tree Tree
amount :: (Integer -> Integer -> Integer) -> Tree -> Integer amount fun = amount where {
amount (Leaf x) = x ; amount (Branch t1 t2) = fun (amount t1) (amount t2) }
(3) UnsafePerformIO:
import System.IO.Unsafe (unsafePerformIO)
data Tree = Leaf Integer | Branch Tree Tree
amount :: Tree -> Integer amount (Leaf x) = x amount (Branch t1 t2) = fun (amount t1) (amount t2) where fun = unsafePerformIO ...
I'm not happy with any of these options. Personally, I would probably go ahead and transform the whole program just to get the value of fun to where it is needed. Nevertheless, having actually done this before, I understand why Martin Odersky doesn't like doing it :)
Tillmann
______________________________**_________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Tillmann Rendel
Which drawbacks do you see besides increased verbosity?
Well, you did change the equation "amount (Leaf x) = x" to "amount fun (Leaf x) = x". In a larger example, this means that you need to change many lines of many functions, just to get the the value of fun from the point where it is known to the point where you need it.
I would argue that no matter how good one's language is, there will always exist realistic refactorings that require you to make sweeping changes to a large portion of your code base.
[...] I am wondering which ways of doing this in Haskell you mean.
I thought of the following three options, but see also Nathan Howells email for another alternative (that is related to my option (1) below):
(1) Implicit parameters: <snip> (2) Lexical Scoping: <snip> (3) UnsafePerformIO: <snip> I'm not happy with any of these options. Personally, I would probably go ahead and transform the whole program just to get the value of fun to where it is needed. Nevertheless, having actually done this before, I understand why Martin Odersky doesn't like doing it :)
I think that Martin's statement is an unavoidable fact of life that follows directly from the definition of purity and the mechanics of data dependencies. Of course nobody likes making sweeping changes to their app because they didn't anticipate the way the future would evolve. But lets not blame monads for what is really a much more fundamental phenomenon.
participants (4)
-
Alberto G. Corona
-
MightyByte
-
Tillmann Rendel
-
Yves Parès