Proposal: add new function "check" to Control.Monad

Trac ticket #3453. Two week time frame. Add check function to Control.Monad check :: (MonadPlus m) => (a -> Bool) -> a -> m a check p a | p a = return a | otherwise = mzero Rationale: The example that suggested the function to me is this: readMaybe :: Read a => String -> Maybe a readMaybe = join . fmap no_trailing_garbage . listToMaybe . reads where no_trailing_garbage = fmap fst . check (all isSpace . snd) but check is clearly more generally useful than guard. (guard = flip (check . const) ()) Discussion: I also note in the comments to check that we can define List.filter like this filter = (concat .) . map . check Now, concat is just join specialised to lists, and map [is fmap, but...] is liftM, so we would expect a function mfilter = (join .) . liftM . check to be useful. Should that also be added? -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

Add check function to Control.Monad
check :: (MonadPlus m) => (a -> Bool) -> a -> m a check p a | p a = return a | otherwise = mzero
I agree that such a function is occasionally useful. But I doubt your rationale:
Rationale: [...]
but check is clearly more generally useful than guard. (guard = flip (check . const) ())
This is a bit like saying that concatMap is more generally useful than map and concat because: map f = concatMap ((:[]).f) concat = concatMap id Although this is correct, map and concat are smaller pieces that can be easily combined to concatMap: concatMap f = concat . map f So the question is whether check is useful enough to be included as a shortcut for a combination of simpler primitives (as was decided for concatMap). If 'check' is added then I would prefer this definition: check f x = guard (f x) >> return x It emphasises how 'check' is combined from simpler parts.
so we would expect a function
mfilter = (join .) . liftM . check
to be useful. Should that also be added?
I would not object and prefer this definition: mfilter f m = m >>= check f It seems simpler. Cheers, Sebastian -- Underestimating the novelty of the future is a time-honored tradition. (D.G.)

I've been having network problems, and in addition, I usually use gmane to access this list, but Sebastian and Yitzchak's messages never turned up there. On 2009-08-24 at 09:59+0200 Sebastian Fischer wrote:
Add check function to Control.Monad
check :: (MonadPlus m) => (a -> Bool) -> a -> m a check p a | p a = return a | otherwise = mzero
I agree that such a function is occasionally useful. But I doubt your rationale:
Rationale: [...]
but check is clearly more generally useful than guard. (guard = flip (check . const) ())
This is a bit like saying that concatMap is more generally useful than map and concat because:
I think I wasn't clear. When I said "clearly" I thought that the general usefulness was clear; the remark about guard was an "and" rather than a "because". What makes it clear to me is the types: check is more polymorphic in the sense that it has a type variable where guard has ().
map f = concatMap ((:[]).f) concat = concatMap id
Although this is correct, map and concat are smaller pieces that can be easily combined to concatMap:
concatMap f = concat . map f
So the question is whether check is useful enough to be included as a shortcut for a combination of simpler primitives (as was decided for concatMap).
Well, while I agree with the general principle, (and have argued for it strongly in the past), I don't agree with the way you are using "simple" here. When designing a library, one should choose the primitives so that future definitions are simple, both in the complexity of the terms needed to define them and in the thought needed to define them, rather than the simplicity of definition of the primitives themselves. The reason that I suggested check is that it seems to me that it gives both of those things in a way that guard doesn't (and people may have to work a bit when weighing this, owing to the long-standing familiarity of guard). The reason I didn't suggest removal of guard was that long-standing familiarity. To my mind, MonadPlus m => m () is a very specific and rather peculiar type (consider [()], for example) and I think guard suggests a rather imperative outlook because of this. Getting from m () to Maybe Char strikes me as a longer thought process than getting from m a to Maybe Char.
so we would expect a function
mfilter = (join .) . liftM . check
to be useful. Should that also be added?
I would not object and prefer this definition:
mfilter f m = m >>= check f
It seems simpler.
I agree. The equation above was just the derivation. Jón -- Jón Fairbairn Jon.Fairbairn at cl.cam.ac.uk

On Aug 26, 2009, at 7:52 PM, Jon Fairbairn wrote:
When designing a library, one should choose the primitives so that future definitions are simple, both in the complexity of the terms needed to define them and in the thought needed to define them, rather than the simplicity of definition of the primitives themselves. The reason that I suggested check is that it seems to me that it gives both of those things in a way that guard doesn't
I see. Also the type of guard is indeed unusual. Historically, guard seems inspired by conditions in list comprehensions but I would appreciate a sensible refactoring. When designing MonadPlus combinators from scratch I would probably implement filter :: MonadPlus m => (a -> Bool) -> m a -> m a as a generalisation of the list function with the same name. After Davids remarks I'm not sure whether I would need check f = filter f . return I agree to you reasoning to prefer check over guard but go one step further and prefer filter over check. I would vote for adding a generalized filter to Control.Monad. Using the name of the Prelude function on lists is justified because it is a generalisation just like many functions in Data.Foldable which also reuse Prelude names. Cheers, Sebastian -- Underestimating the novelty of the future is a time-honored tradition. (D.G.)

Sebastian Fischer
On Aug 26, 2009, at 7:52 PM, Jon Fairbairn wrote:
When designing a library, one should choose the primitives so that future definitions are simple, both in the complexity of the terms needed to define them and in the thought needed to define them, rather than the simplicity of definition of the primitives themselves. The reason that I suggested check is that it seems to me that it gives both of those things in a way that guard doesn't
I see. Also the type of guard is indeed unusual. Historically, guard seems inspired by conditions in list comprehensions but I would appreciate a sensible refactoring.
When designing MonadPlus combinators from scratch I would probably implement
filter :: MonadPlus m => (a -> Bool) -> m a -> m a
as a generalisation of the list function with the same name. After Davids remarks I'm not sure whether I would need
check f = filter f . return
Now that /is/ a simple definition that would argue against inclusion of check.
I agree to you reasoning to prefer check over guard but go one step further and prefer filter over check.
I would be happy with that.
I would vote for adding a generalized filter to Control.Monad. Using the name of the Prelude function on lists is justified because it is a generalisation just like many functions in Data.Foldable which also reuse Prelude names.
Were I designing this stuff from scratch, I'd go the same way (actually, I'd want to restore monad comprehensions too), but there is currently an explicit naming scheme in Control.Monad, under which the name would be mfilter, so I think (in the absence of renaming fmap to map, which I would also strongly prefer -- etc) we should use the name mfilter for the time being. In view of this, I reckon I should change the proposal and reset the time limit. What's the procedure for this? -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

While I like the generic version of filter, and have written one myself, I am somewhat concerned about the fact that Control.Monad is probably the module most often imported unqualified and without an explicit import list due to the sheer number of combinators that it provides and filter is a very commonly used function in the Prelude. Adding the generic version of filter with the same name to such a module will likely break a good deal of code. Jon's suggestion of mfilter (filterM?) based on the ad hoc naming conventions in Control.Monad sounds pretty safe though. -Edward Kmett On Wed, Aug 26, 2009 at 3:44 PM, Sebastian Fischer < sebf@informatik.uni-kiel.de> wrote:
On Aug 26, 2009, at 7:52 PM, Jon Fairbairn wrote:
When designing a library, one should choose
the primitives so that future definitions are simple, both in the complexity of the terms needed to define them and in the thought needed to define them, rather than the simplicity of definition of the primitives themselves. The reason that I suggested check is that it seems to me that it gives both of those things in a way that guard doesn't
I see. Also the type of guard is indeed unusual. Historically, guard seems inspired by conditions in list comprehensions but I would appreciate a sensible refactoring.
When designing MonadPlus combinators from scratch I would probably implement
filter :: MonadPlus m => (a -> Bool) -> m a -> m a
as a generalisation of the list function with the same name. After Davids remarks I'm not sure whether I would need
check f = filter f . return
I agree to you reasoning to prefer check over guard but go one step further and prefer filter over check.
I would vote for adding a generalized filter to Control.Monad. Using the name of the Prelude function on lists is justified because it is a generalisation just like many functions in Data.Foldable which also reuse Prelude names.
Cheers, Sebastian
-- Underestimating the novelty of the future is a time-honored tradition. (D.G.)
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Edward Kmett
While I like the generic version of filter, and have written one myself, I am somewhat concerned about the fact that Control.Monad is probably the module most often imported unqualified and without an explicit import list due to the sheer number of combinators that it provides and filter is a very commonly used function in the Prelude. Adding the generic version of filter with the same name to such a module will likely break a good deal of code.
I don't think it would break the code as such: it does exactly the same thing. It would break the import declarations, though.
Jon's suggestion of mfilter (filterM?)
Definitely mfilter. filterM is there already, and does what its name implies. See proposal #3524. Jón

Jón Fairbairn wrote:
Trac ticket #3453. Two week time frame. Add check function to Control.Monad check :: (MonadPlus m) => (a -> Bool) -> a -> m a
I remember needing this on a number of occasions.
mfilter = (join .) . liftM . check
I might write that as: mFilter = (=<<) . check That is an intriguing dual to filterM. Regards, Yitz

Hello,
I don't really think that we need this function, it is plenty easy to
just write with "guard". Furthermore, if you choose to add it, then
please do not use "check" for the name. This is way too generic a
name which I often use for local functions that do some validation.
-Iavor
On Mon, Aug 24, 2009 at 1:03 AM, Yitzchak Gale
Jón Fairbairn wrote:
Trac ticket #3453. Two week time frame. Add check function to Control.Monad check :: (MonadPlus m) => (a -> Bool) -> a -> m a
I remember needing this on a number of occasions.
mfilter = (join .) . liftM . check
I might write that as:
mFilter = (=<<) . check
That is an intriguing dual to filterM.
Regards, Yitz _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On 2009-08-26 at 09:49PDT Iavor Diatchki wrote:
Hello, I don't really think that we need this function, it is plenty easy to just write with "guard".
See my response to Sebastian, but also, none of the definitions of check in terms of guard meet my criteria for being simple enough, namely no lambdas and only a small amount of plumbing (ie don't get round the "no lambdas" part by compiling it to S and K ;-)
Furthermore, if you choose to add it, then please do not use "check" for the name. This is way too generic a name which I often use for local functions that do some validation.
I was unsure of the name, for that very reason, so am open to suggestions. Jón -- Jón Fairbairn Jon.Fairbairn at cl.cam.ac.uk

On Wed, Aug 26, 2009 at 2:07 PM, Jon
Fairbairn
On 2009-08-26 at 09:49PDT Iavor Diatchki wrote:
Hello, I don't really think that we need this function, it is plenty easy to just write with "guard".
See my response to Sebastian, but also, none of the definitions of check in terms of guard meet my criteria for being simple enough, namely no lambdas and only a small amount of plumbing (ie don't get round the "no lambdas" part by compiling it to S and K ;-)
I'm usually opposed to adding small functions to the standard library, but check is something I've defined for myself dozens of times. (Although I usually call it "require".) In my experience, check is very natural if you're writing code using
= (and especially =<<), but guard is possibly more natural with do-notation. Similarly, guard scales better if you have multiple conditions. e.g.,
foo >>= require even >>= bar
is more convenient than
foo >>= \x -> guard (even x) >> bar x
but
foo >>= require (\x -> even x && x < y) >>= bar
is no better than
foo >>= \x -> guard (even x && x < y) >> bar x
On the other hand, the more applicative style,
bar =<< require even =<< foo
doesn't easily translate into using guard.
Finally, it's worth considering adding filter (or "mfilter", "sieve",
whatever). It's trivial to define check/require in terms of filter,
and the resulting code looks even cleaner.
filter even foo >>= bar
filter (\x -> even x && x < y) foo >>= bar
bar =<< filter even foo
--
Dave Menendez

Jon Fairbairn
Trac ticket #3453. Two week time frame.
Add check function to Control.Monad
check :: (MonadPlus m) => (a -> Bool) -> a -> m a check p a | p a = return a | otherwise = mzero
My impression is that the consensus is not to add this, mostly because of the "names for small functions" argument with which I heartily concur, though I suspect that I prejudiced things by not giving a strong enough justification to begin with (eg that what I'd really like to see is check -- by whatever name -- and to deprecate guard as something that encourages imperative thinking) So I've formally proposed mfilter instead. I imagine that I should close this ticket: is the correct resolution "wontfix"? -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

Ross Paterson
On Thu, Sep 17, 2009 at 04:15:15PM +0100, Jon Fairbairn wrote:
So I've formally proposed mfilter instead. I imagine that I should close this ticket: is the correct resolution "wontfix"?
Yes
OK, done. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk
participants (8)
-
David Menendez
-
Edward Kmett
-
Iavor Diatchki
-
Jon Fairbairn
-
Martijn van Steenbergen
-
Ross Paterson
-
Sebastian Fischer
-
Yitzchak Gale