Re: [Haskell] Types of when and unless in Control.Monad

On 22 April 2012 21:39, Christian Höner zu Siederdissen
* Julian Gilbey
[22.04.2012 09:22]: On Sat, Apr 21, 2012 at 08:28:27PM -0500, Strake wrote:
On 21/04/2012, Andreas Abel
wrote: to avoid silly "return ()" statements like in
when cond $ do monadicComputationWhoseResultIWantToDiscard return ()
(when cond ∘ void) monadicComputationWhoseResultIWantToDiscard or when cond $ () <$ monadicComputationWhoseResultIWantToDiscard
How is that simpler than
when cond monadicComputationWhoseResultIWantToDiscard
which it would be with the suggested new type?
Julian
Wouldn't "when_" and "unless_" or similar be better? I'd probably like to have the compiler annoy me, since it is not clear that I want to discard the result. If I really want to discard, I should have to make it clear as there is probably a good reason for the inner function to return a result in the first place?
Agreed; I'm not sure if I agree with having such functionality (Henning makes some good points), but if people deem it desirable then I think it would be better to have them with new names for the reasons you state. -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com

On Sun, 22 Apr 2012, Ivan Lazar Miljenovic wrote:
On 22 April 2012 21:39, Christian Höner zu Siederdissen
wrote: Wouldn't "when_" and "unless_" or similar be better? I'd probably like to have the compiler annoy me, since it is not clear that I want to discard the result. If I really want to discard, I should have to make it clear as there is probably a good reason for the inner function to return a result in the first place?
Agreed; I'm not sure if I agree with having such functionality (Henning makes some good points), but if people deem it desirable then I think it would be better to have them with new names for the reasons you state.
The underscores would also be consistent with mapM_, forM_ and so on. But please still count me as -1.

On 04/22/2012 01:49 PM, Ivan Lazar Miljenovic wrote:
On 22 April 2012 21:39, Christian Höner zu Siederdissen
wrote: * Julian Gilbey
[22.04.2012 09:22]: On Sat, Apr 21, 2012 at 08:28:27PM -0500, Strake wrote:
On 21/04/2012, Andreas Abel
wrote: to avoid silly "return ()" statements like in
when cond $ do monadicComputationWhoseResultIWantToDiscard return ()
(when cond ∘ void) monadicComputationWhoseResultIWantToDiscard or when cond $ ()<$ monadicComputationWhoseResultIWantToDiscard
How is that simpler than
when cond monadicComputationWhoseResultIWantToDiscard
which it would be with the suggested new type?
Julian
Wouldn't "when_" and "unless_" or similar be better? I'd probably like to have the compiler annoy me, since it is not clear that I want to discard the result. If I really want to discard, I should have to make it clear as there is probably a good reason for the inner function to return a result in the first place?
Agreed; I'm not sure if I agree with having such functionality (Henning makes some good points), but if people deem it desirable then I think it would be better to have them with new names for the reasons you state.
Mmh, this discussion has cooled down, but I just found your answers which had been stashed away by my mail agent, and I feel I have to reply... Concerning the suggestion that when_ would be in sync with forM_ and whenM_ I'd say: not really. forM_ and whenM_ discard the result of the monadic computation, while when and when_ do not even have such a result. They always just perform some monadic effect and return nothing. Repeating myself, 'when' can never have a result, since it is an if-then without an else. Thus, it is a proper command; and if you want to have a conditional monadic computation which does return a result, you can simply not use 'when' or 'unless', logic forces you to use 'if' or 'ifM'. I do not understand the worries that one could accidentially use 'when' with a monadic computation whose result one actually cares for. If that was the intention of the library designers, they should have given many other function a more specific type, most prominently
:: m () -> m b -> b
That would have ensured that you cannot discard the result of the first computation by accident. But would you want to work with this? My answer is no. Other types that would be changed to implement this kind of safety policy are: mapM_ :: (a -> m ()) -> [a] -> m () forM_ :: [a] -> (a -> m ()) -> m () sequence_ :: [m ()] -> m () forever :: m () -> m () and many more, like zipWithM_, foldM_, replicateM_. Sorry, but I think all these function have been given their maximal general type ==> to be able to ignore a result of a monadic computation ==> without further noise. In my opinion, the types of when and unless are not general enough, an that is, imho, just an accident of history. Because it is the type that inferred for the shortest definition, which is when cond m = if cond then m else return () Please reevaluate my proposal to change to when :: Bool -> m a -> m () unless :: Bool -> m a -> m () in the light of the above arguments. Cheers, Andreas -- Andreas Abel <>< Du bist der geliebte Mensch. Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/

On Mon, 4 Jun 2012, Andreas Abel wrote:
Concerning the suggestion that when_ would be in sync with forM_ and whenM_ I'd say: not really. forM_ and whenM_ discard the result of the monadic computation, while when and when_ do not even have such a result. They always just perform some monadic effect and return nothing.
What is whenM_ ? Do you mean mapM_ ?
:: m () -> m b -> b
mapM_ :: (a -> m ()) -> [a] -> m () forM_ :: [a] -> (a -> m ()) -> m () sequence_ :: [m ()] -> m () forever :: m () -> m ()
and many more, like zipWithM_, foldM_, replicateM_.
I would prefer these strict types, too. Alternatively I have wondered in the past whether it might be a good idea to generalize them to:
mapM_ :: Monoid b => (a -> m b) -> [a] -> m b forM_ :: Monoid b => [a] -> (a -> m b) -> m b sequence_ :: Monoid b => [m b] -> m b forever :: Monoid b => m b -> m b
This would still propagate monadic result type () if the final monadic action has result type (). http://www.haskell.org/pipermail/haskell-cafe/2009-January/054243.html
Sorry, but I think all these function have been given their maximal general type
==> to be able to ignore a result of a monadic computation
==> without further noise.
Since the addition of 'void' the noise has become acceptable for me. I would follow a kind of "separation of concerns". Ignoring results is one step and performing forM_, when etc. is the second step.
In my opinion, the types of when and unless are not general enough, an that is, imho, just an accident of history. Because it is the type that inferred for the shortest definition, which is
when cond m = if cond then m else return ()
Please reevaluate my proposal to change to
when :: Bool -> m a -> m () unless :: Bool -> m a -> m ()
in the light of the above arguments.
Last time I asked the question, what application you do have in mind. Is your code cluttered with void's or do you just need it occasionally?

On Mon, 4 Jun 2012, Henning Thielemann wrote:
On Mon, 4 Jun 2012, Andreas Abel wrote:
Concerning the suggestion that when_ would be in sync with forM_ and whenM_ I'd say: not really. forM_ and whenM_ discard the result of the monadic computation, while when and when_ do not even have such a result. They always just perform some monadic effect and return nothing.
What is whenM_ ? Do you mean mapM_ ?
Ah, I think whenM_ was this one whenM_ :: m Bool -> m a -> m ()

On 06/04/2012 09:25 PM, Henning Thielemann wrote:
On Mon, 4 Jun 2012, Andreas Abel wrote:
Concerning the suggestion that when_ would be in sync with forM_ and whenM_ I'd say: not really. forM_ and whenM_ discard the result of the monadic computation, while when and when_ do not even have such a result. They always just perform some monadic effect and return nothing.
What is whenM_ ? Do you mean mapM_ ?
Probably...
:: m () -> m b -> b
mapM_ :: (a -> m ()) -> [a] -> m () forM_ :: [a] -> (a -> m ()) -> m () sequence_ :: [m ()] -> m () forever :: m () -> m ()
and many more, like zipWithM_, foldM_, replicateM_.
I would prefer these strict types, too.
Ok, well, then you probably would not want to use mapM_ and the like, but instead mapM (void . f) l which instantiates the type b to (), giving above typings.
Alternatively I have wondered in the past whether it might be a good idea to generalize them to:
mapM_ :: Monoid b => (a -> m b) -> [a] -> m b forM_ :: Monoid b => [a] -> (a -> m b) -> m b sequence_ :: Monoid b => [m b] -> m b forever :: Monoid b => m b -> m b
This would still propagate monadic result type () if the final monadic action has result type ().
http://www.haskell.org/pipermail/haskell-cafe/2009-January/054243.html
But that would not be backwards compatible.
Sorry, but I think all these function have been given their maximal general type
==> to be able to ignore a result of a monadic computation
==> without further noise.
Since the addition of 'void' the noise has become acceptable for me.
I would follow a kind of "separation of concerns". Ignoring results is one step and performing forM_, when etc. is the second step.
Ok. But I am really surprised that an operation should not get the maximally sensible type. It seems that I like to think of () as a terminal type (in the sense of category theory), but this intuition is not shared by everyone. [I am aware that () is NOT the terminal type in Haskell.]
In my opinion, the types of when and unless are not general enough, an that is, imho, just an accident of history. Because it is the type that inferred for the shortest definition, which is
when cond m = if cond then m else return ()
Please reevaluate my proposal to change to
when :: Bool -> m a -> m () unless :: Bool -> m a -> m ()
in the light of the above arguments.
Last time I asked the question, what application you do have in mind. Is your code cluttered with void's or do you just need it occasionally?
The application is that I have a function that provides a resource that may be present or not. If it is not present, an exception is thrown (that is the monadic effect). If I am just interested in checking the presence of the resource, I can call this function in a do-block. But I am not allowed to call it in a 'when', without 'void'ing it. That is counterintuitive. To reconcile the 'strict' vs. 'liberal' programmers, it seems that library functions need to have different types depending on whether -fwarn-unused-do-bind is set or not... Cheers, Andreas -- Andreas Abel <>< Du bist der geliebte Mensch. Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/

On Tue, 5 Jun 2012, Andreas Abel wrote:
I would prefer these strict types, too.
Ok, well, then you probably would not want to use mapM_ and the like, but instead
mapM (void . f) l
This would result in 'm [()]' not in 'm ()'. I could e.g. get information from the number elements in the [()] list, but () tells me nothing. Thus they are really different.
Alternatively I have wondered in the past whether it might be a good idea to generalize them to:
mapM_ :: Monoid b => (a -> m b) -> [a] -> m b forM_ :: Monoid b => [a] -> (a -> m b) -> m b sequence_ :: Monoid b => [m b] -> m b forever :: Monoid b => m b -> m b
This would still propagate monadic result type () if the final monadic action has result type ().
http://www.haskell.org/pipermail/haskell-cafe/2009-January/054243.html
But that would not be backwards compatible.
Not completely. You may need additional type annotations.
Since the addition of 'void' the noise has become acceptable for me.
I would follow a kind of "separation of concerns". Ignoring results is one step and performing forM_, when etc. is the second step.
Ok. But I am really surprised that an operation should not get the maximally sensible type.
There are other functions, like 'asTypeOf' that have intentionally not the most general type. :-) My concern is safety and safety means to intentionally forbid things. That's why I prefer Haskell to C or MatLab. E.g. C by default ignores results from functions if they are not used. But this way, people may write (a==b;) instead of (a=b;) without noticing the mistake.
The application is that I have a function that provides a resource that may be present or not. If it is not present, an exception is thrown (that is the monadic effect). If I am just interested in checking the presence of the resource, I can call this function in a do-block. But I am not allowed to call it in a 'when', without 'void'ing it. That is counterintuitive.
How do you free the resource if you ignore the returned handle? If checking for an exception this way is a common pattern in your code, how about writing a function that catches the exception and run some code, if there is no exception? It might have a signature like whenAvailable :: IO resource -> IO () -> IO () and might be used like this whenAvailable getResource $ do thingsToDoWhenResourceIsAvailable
To reconcile the 'strict' vs. 'liberal' programmers, it seems that library functions need to have different types depending on whether
-fwarn-unused-do-bind
is set or not...
Something like a type system that does not only support 'correct' and 'wrong', but also 'suspect', would solve the problem. :-)
participants (4)
-
Andreas Abel
-
Andres Löh
-
Henning Thielemann
-
Ivan Lazar Miljenovic