RE: [Haskell-cafe] Monadic vs "pure" style (was: pros and cons of sta tic typing and side effects)

From: Duncan Coutts [mailto:duncan.coutts@worcester.oxford.ac.uk]
This is often a misconception, that just because you find you need to 'do' something in the middle of your algorithm, that you need to convert it wholly to monadic style.
Yes. However, Wadler makes a convincing (at least to me) case that the monadic style is easier to extend. The code changes for the monadic style appear to be more localised. Something else I noticed about my non-monadic code was the way I was threading state through functions. I was tempted to introduce a State monad to make this easier to manage, but then I decided to try mutable arrays instead, so that experiment was not attempted. So it might well have been better in monadic style anyway, even with immutable arrays. I'm conscious that for most (?) monads, monadic code can be invoked from non-monadic code. I'm only aware of the IO monad as a one-way trap. So changing code from pure to monadic doesn't necessarily involve program-wide changes, unless the monad you're introducing happens to be IO. In my array example, I introduced STArrays, but the main interface remained pure (non-monadic), which was my goal. I was also wondering what the disadvantages of monadic style are? Are there compiler optimisations which are not possible with monadic code? Alistair. ----------------------------------------- ***************************************************************** Confidentiality Note: The information contained in this message, and any attachments, may contain confidential and/or privileged material. It is intended solely for the person(s) or entity to which it is addressed. Any review, retransmission, dissemination, or taking of any action in reliance upon this information by persons or entities other than the intended recipient(s) is prohibited. If you received this in error, please contact the sender and delete the material from any computer. *****************************************************************

On Aug 30, 2005, at 12:13 PM, Bayley, Alistair wrote:
From: Duncan Coutts [mailto:duncan.coutts@worcester.oxford.ac.uk]
This is often a misconception, that just because you find you need to 'do' something in the middle of your algorithm, that you need to convert it wholly to monadic style.
Yes. However, Wadler makes a convincing (at least to me) case that the monadic style is easier to extend. The code changes for the monadic style appear to be more localised.
Something else I noticed about my non-monadic code was the way I was threading state through functions. I was tempted to introduce a State monad to make this easier to manage, but then I decided to try mutable arrays instead, so that experiment was not attempted. So it might well have been better in monadic style anyway, even with immutable arrays.
I'm conscious that for most (?) monads, monadic code can be invoked from non-monadic code. I'm only aware of the IO monad as a one-way trap. So changing code from pure to monadic doesn't necessarily involve program-wide changes, unless the monad you're introducing happens to be IO. In my array example, I introduced STArrays, but the main interface remained pure (non-monadic), which was my goal.
I was also wondering what the disadvantages of monadic style are? Are there compiler optimisations which are not possible with monadic code?
Both the advantage and the disadvantage is that you break lazy evaluation. 90% of the time lazyness is your friend and monadifying your code can break some nice features, but there is an occasional 10% of the time when it's useful to break lazyness. On a side note, whenever I find myself tempted to pass state around, I consider whether using CPS is better... It provides some method of ordering code, but doesn't break lazyness. Just 2¢ from a relative newbie. Bob

There seems to be a misconception in this thread that there is something "non-functional" or "imperative" about using monads. That is simply not true. When what you are trying to write is most naturally and clearly expressed as a series of steps - there is no reason not to use a monad. Even when a function is most naturally written as purely recursive, in real-life code you often add "Monad m =>" to the type signature and wrap the function in a "return". This is primarily so that you can propagate exceptions. (I personally am not so impressed by the refactoring fears in the referenced paper, but yes, that is another reason.) True, there are a few rare monads that have non-lazy semantics; IO and ST come to mind. So I avoid those unless absolutely necessary. On Tue, Aug 30, 2005 at 12:40:27PM +0100, Thomas Davie wrote:
On Aug 30, 2005, at 12:13 PM, Bayley, Alistair wrote:
Something else I noticed about my non-monadic code was the way I was threading state through functions.
That was the classical way of doing state in functional languages, but in my opinion it is very bad style in modern Haskell.
I was tempted to introduce a State monad...
Right!
I was also wondering what the disadvantages of monadic style are?
Both the advantage and the disadvantage is that you break lazy evaluation.
Not true. Only if you use a non-lazy monad, like IO or ST. There is no inherent advantage or disadvantage to monads. If the idea is most clearly expressed as a monad, use a monad. If the idea is most clearly expressed recursively, write it recursively (but perhaps wrap it in "return"). Using that philosophy, I find that quite a bit of my code is monadic - most commonly State and StateT - and still perfectly functional and lazy.
90% of the time lazyness is your friend... but there is an occasional 10% of the time when it's useful to break lazyness.
I find the percentage much higher than 90%.
...monadifying your code can break some nice features,...
I do not know of any features it breaks.
On a side note, whenever I find myself tempted to pass state around, I consider whether using CPS is better...
I do not know how it could ever make sense to use CPS, except for a research project that explicitly requires it. (Yes, I know about callCC. I use a much simpler and clearer Exit monad instead.) -Yitz

There is no inherent advantage or disadvantage to monads. If the idea is most clearly expressed as a monad, use a monad. If the idea is most clearly expressed recursively, write it recursively (but perhaps wrap it in "return").
Perhaps the "inherent disadvantage" is that functions written in the monadic style must have different types compared with their conceptually similar non-monadic functions.. mapM :: Monad m => (a -> m b) -> [a] -> m [b] map :: (a -> b) -> [a] -> [b] filter :: (a -> Bool) -> [a] -> [a] filterM :: (Monad m) => (a -> m Bool) -> [a] -> m [a] foldl :: (a -> b -> a) -> a -> [b] -> a foldM :: (Monad m) => (a -> b -> m a) -> a -> [b] -> m a Some would say "but they're different functions!", others would say "close enough". I imagine this would be an absolute pain for library writers. Notice that we get Data.Map.map but no Data.Map.mapM - or perhaps there's some magical lifting combinator that I am not aware of? Ben.

On Wed, 31 Aug 2005, Ben Lippmeier wrote:
I imagine this would be an absolute pain for library writers. Notice that we get Data.Map.map but no Data.Map.mapM - or perhaps there's some magical lifting combinator that I am not aware of?
sequence (Data.Map.map (\x -> someAction x) someMap) -- flippa@flippac.org The task of the academic is not to scale great intellectual mountains, but to flatten them.

On Wed, 31 Aug 2005, Philippa Cowderoy wrote:
On Wed, 31 Aug 2005, Ben Lippmeier wrote:
I imagine this would be an absolute pain for library writers. Notice that we get Data.Map.map but no Data.Map.mapM - or perhaps there's some magical lifting combinator that I am not aware of?
sequence (Data.Map.map (\x -> someAction x) someMap)
Or not - I really should've at least typechecked that before sending. Wonder how fast toList and fromList are? -- flippa@flippac.org There is no magic bullet. There are, however, plenty of bullets that magically home in on feet when not used in exactly the right circumstances.

Philippa Cowderoy wrote:
On Wed, 31 Aug 2005, Philippa Cowderoy wrote:
On Wed, 31 Aug 2005, Ben Lippmeier wrote:
I imagine this would be an absolute pain for library writers. Notice that we get Data.Map.map but no Data.Map.mapM - or perhaps there's some magical lifting combinator that I am not aware of?
sequence (Data.Map.map (\x -> someAction x) someMap)
Or not - I really should've at least typechecked that before sending. Wonder how fast toList and fromList are?
"foldWithKey <#v%3AfoldWithKey> :: (k -> a -> b -> b) -> b -> Map

On Thu, Sep 01, 2005 at 12:41:06AM -0700, Juan Carlos Arevalo Baeza wrote:
You can get the correct order by using lists, but you want to use the "Asc" versions:
myMapM someAction someMap = do list <- sequence $ map (\(k, a) -> someAction a >>= (\b -> return (k,b))) $ Map.toAscList someMap return (Map.fromAscList list)
Should also be O(n).
I like this approach. You want to use fromDistinctAscList though. By analogy with the Prelude, I would make it slightly more flexible as follows: mySequence :: Monad m => Map.Map k (m a) -> m (Map.Map k a) mySequence someMap = do list <- sequence $ map liftTuple $ Map.toAscList someMap return $ Map.fromDistinctAscList list where liftTuple (x, y) = do z <- y return (x, z) myMapM :: Monad m => (a -> m b) -> Map.Map k a -> m (Map.Map k b) myMapM f = mySequence . Map.map f myMapM_ :: Monad m => (a -> m b) -> Map.Map k a -> m () myMapM_ f = sequence_ . map f . Map.elems Regards, Yitz

Perhaps you could write _everything_ in monadic style, and then derive the non-monadic version by running it on an "empty" state monad. But then if everything was already monadic you wouldn't need the non-monadic version.. :) ...
Perhaps the "inherent disadvantage" is that functions written in the monadic style must have different types compared with their conceptually similar non-monadic functions..
mapM :: Monad m => (a -> m b) -> [a] -> m [b] map :: (a -> b) -> [a] -> [b]
filter :: (a -> Bool) -> [a] -> [a] filterM :: (Monad m) => (a -> m Bool) -> [a] -> m [a]
foldl :: (a -> b -> a) -> a -> [b] -> a foldM :: (Monad m) => (a -> b -> m a) -> a -> [b] -> m a
Some would say "but they're different functions!", others would say "close enough".
I imagine this would be an absolute pain for library writers. Notice that we get Data.Map.map but no Data.Map.mapM - or perhaps there's some magical lifting combinator that I am not aware of?
Ben.

Ben Lippmeier wrote:
to monads. If the idea is most clearly expressed as a monad, use a monad. If the idea is most clearly expressed recursively, write it recursively (but perhaps wrap it in "return").
There is no inherent advantage or disadvantage
Perhaps the "inherent disadvantage" is that functions written in the monadic style must have different types compared with their conceptually similar non-monadic functions..
mapM :: Monad m => (a -> m b) -> [a] -> m [b] map :: (a -> b) -> [a] -> [b]
filter :: (a -> Bool) -> [a] -> [a] filterM :: (Monad m) => (a -> m Bool) -> [a] -> m [a]
foldl :: (a -> b -> a) -> a -> [b] -> a foldM :: (Monad m) => (a -> b -> m a) -> a -> [b] -> m a
Some would say "but they're different functions!", others would say "close enough".
Heh... I recently was experimenting with this separation... Check this out. If the Num class had been defined without having "Eq" as a prerequisite, you could do something like this: ---8<--------------------------------- class MyNum v where (.+) :: v -> v -> v instance MyNum Int where (.+) a b = a + b instance (Monad m, MyNum v) => MyNum (m v) where (.+) a b = do ra <- a rb <- b return (ra .+ rb) two = return 2 :: IO Int three = return 3 :: IO Int main = do result <- two .+ three putStr $ show result ---8<--------------------------------- I defined an operator to add Ints and made it work fine in a monadic environment. See what happened? Easy. Problem is, Num is a subclass of Eq (for no apparent technical reason, only for expressivity), which prevents using this mechanism with it. Eq could have been defined to parameterize on the boolean value (using multiparameter classes and functional dependencies, so no wonder it isn't): ---8<--------------------------------- class MyEq v b | v -> b where (.==) :: v -> v -> b instance MyEq Int Bool where (.==) a b = a == b instance (Monad m, MyEq v b) => MyEq (m v) (m b) where (.==) a b = do ra <- a rb <- b return (ra .== rb) two = return 2 :: IO Int three = return 3 :: IO Int main = do cond <- two .== three putStrLn $ show cond ---8<---------------------------------
I imagine this would be an absolute pain for library writers. Notice that we get Data.Map.map but no Data.Map.mapM - or perhaps there's some magical lifting combinator that I am not aware of?
The above works great. Not with the standard libraries, of course, but you can always use it in your own classes. I'm not sure yet what the "catch" will be, but it sounds like a pattern worth investigating. The same thing, I suspect, can be done with arrows. Maybe some day syntactic sugar can be added to overlay functions safely like this without having to manually create a class and two instances for it. Just beware: to make this JCAB

Hello Juan, Thursday, September 01, 2005, 12:03:15 PM, you wrote: JCAB> instance MyNum Int where JCAB> (.+) a b = a + b JCAB> instance (Monad m, MyNum v) => MyNum (m v) where JCAB> (.+) a b = do JCAB> ra <- a JCAB> rb <- b JCAB> return (ra .+ rb) JCAB> Just beware: to make this i think, it is very practical. we can make alternative Prelude, this question has been already discussed in light of redefining some list functions (append, head...) as belonging to some Collection class interestingly that Template Haskell, which uses Q monad to generate unique identifiers, also use technique of defining rich set of operations working immediately with monadic values. module Language.Haskell.TH.Lib is full of definitions like this: infixP p1 n p2 = do p1' <- p1 p2' <- p2 return (InfixP p1' n p2') btw, such definitions can be simplified by using liftM/ap operations: instance (Monad m, MyNum v) => MyNum (m v) where (.+) = liftM2 (.+) real program will also need mixed operations, for example addition of variable and constant -- Best regards, Bulat mailto:bulatz@HotPOP.com

Bulat Ziganshin wrote:
Language.Haskell.TH.Lib is full of definitions like this:
infixP p1 n p2 = do p1' <- p1 p2' <- p2 return (InfixP p1' n p2')
btw, such definitions can be simplified by using liftM/ap operations:
instance (Monad m, MyNum v) => MyNum (m v) where (.+) = liftM2 (.+)
Such simplified forms then occur often enough that, in a scrapping boilerplate kind of way, I would really like to be able to write something like instance (Monad m, MyNum v) => MyNum (m v) via lifting or lifted instance (Monad m, MyNum v) => MyNum (m v) or derived instance (Monad m, MyNum v) => MyNum (m v) where all the operations from MyNum are obtained via applying the correct arity liftM function from the Monad class. Jacques

Hello Jacques, Thursday, September 01, 2005, 6:55:43 PM, you wrote:
instance (Monad m, MyNum v) => MyNum (m v) where (.+) = liftM2 (.+)
JC> Such simplified forms then occur often enough that, in a scrapping JC> boilerplate kind of way, I would really like to be able to write JC> something like
JC> instance (Monad m, MyNum v) => MyNum (m v) via lifting JC> where all the operations from MyNum are obtained via applying the correct arity liftM function from the Monad class. Template Haskell is a good instrument to do it -- Best regards, Bulat mailto:bulatz@HotPOP.com
participants (8)
-
Bayley, Alistair
-
Ben Lippmeier
-
Bulat Ziganshin
-
Jacques Carette
-
Juan Carlos Arevalo Baeza
-
Philippa Cowderoy
-
Thomas Davie
-
Yitzchak Gale