#2309: containers: specialize functions that fail in a Monad to Maybe

Several functions on containers used to have types like lookup :: (Ord k) => k -> Map k a -> Maybe a but these were generalized to lookup :: (Monad m, Ord k) => k -> Map k a -> m a The only methods of Monad used are return and fail. The problem is that, depending on the monad, fail can be an ordinary value or a runtime error: this device makes it harder to check whether a program is safe, because it hides possible runtime errors among testable conditions. The proposal is to change these signatures back, specializing them to Maybe. The functions involved are: lookup :: Ord k => k -> Map k a -> Maybe a lookupIndex :: Ord k => k -> Map k a -> Maybe Int minViewWithKey :: Map k a -> Maybe ((k,a), Map k a) maxViewWithKey :: Map k a -> Maybe ((k,a), Map k a) minView :: Map k a -> Maybe (a, Map k a) maxView :: Map k a -> Maybe (a, Map k a) lookup :: Key -> IntMap a -> Maybe a maxViewWithKey :: IntMap a -> Maybe ((Key, a), IntMap a) minViewWithKey :: IntMap a -> Maybe ((Key, a), IntMap a) maxView :: IntMap a -> Maybe (a, IntMap a) minView :: IntMap a -> Maybe (a, IntMap a) minView :: Set a -> Maybe (a, Set a) maxView :: Set a -> Maybe (a, Set a) maxView :: IntSet -> Maybe (Int, IntSet) minView :: IntSet -> Maybe (Int, IntSet) No information is lost, because in each case there is a single failure mode.

+1 in favour. This is Haskell, and as such, program crashable effects should not be the default, whenever possible. Regarding support for older programs relying on IO effects here, deprecated versions with the old type would be a good concession to backwards compatibility, or adding a lifter of, ... => Maybe a -> m a to Maybe might also be wise. -- Don ross:
Several functions on containers used to have types like
lookup :: (Ord k) => k -> Map k a -> Maybe a
but these were generalized to
lookup :: (Monad m, Ord k) => k -> Map k a -> m a
The only methods of Monad used are return and fail. The problem is that, depending on the monad, fail can be an ordinary value or a runtime error: this device makes it harder to check whether a program is safe, because it hides possible runtime errors among testable conditions.
The proposal is to change these signatures back, specializing them to Maybe.
The functions involved are:
lookup :: Ord k => k -> Map k a -> Maybe a lookupIndex :: Ord k => k -> Map k a -> Maybe Int minViewWithKey :: Map k a -> Maybe ((k,a), Map k a) maxViewWithKey :: Map k a -> Maybe ((k,a), Map k a) minView :: Map k a -> Maybe (a, Map k a) maxView :: Map k a -> Maybe (a, Map k a)
lookup :: Key -> IntMap a -> Maybe a maxViewWithKey :: IntMap a -> Maybe ((Key, a), IntMap a) minViewWithKey :: IntMap a -> Maybe ((Key, a), IntMap a) maxView :: IntMap a -> Maybe (a, IntMap a) minView :: IntMap a -> Maybe (a, IntMap a)
minView :: Set a -> Maybe (a, Set a) maxView :: Set a -> Maybe (a, Set a)
maxView :: IntSet -> Maybe (Int, IntSet) minView :: IntSet -> Maybe (Int, IntSet)
No information is lost, because in each case there is a single failure mode. _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

+1 in favour too.
This is Haskell, and as such, program crashable effects should not be the default, whenever possible.
Indeed!
Regarding support for older programs relying on IO effects here, deprecated versions with the old type would be a good concession to backwards compatibility, or adding a lifter of,
... => Maybe a -> m a
fromJustM?
No information is lost, because in each case there is a single failure mode.
Also, they call fail with a String, which pretty much means there is no information beyond debugging hints present anyway. If you wanted to indicate failure either added information, Monad.fail, Maybe or Either String would not be the way to do it,. Thanks Neil

On Sat, May 24, 2008 at 05:04:25PM -0700, Don Stewart wrote:
This is Haskell, and as such, program crashable effects should not be the default, whenever possible.
Note that there are still functions that can crash, like findMin :: Map k a -> (k, a) Perhaps they could be deprecated in a separate proposal. But at least one can easily check that a program does not use these, or at least find the places that need checking (by looking for findMin by name). The functions that return in a monad are worse, because you're supposed to use them if you want safe behaviour, but you can't tell whether a particular use is safe without figuring out which monad it's in.

Ross Paterson wrote:
The proposal is to change these signatures back, specializing them to Maybe.
To retain most of the convenience I would propose we use MonadPlus instead, which is arguably where fail should have been put in the first place (*). Twan (*) Actually in a superclass MonadZero, but let's work with what we have now.

On Saturday 24 May 2008, Twan van Laarhoven wrote:
To retain most of the convenience I would propose we use MonadPlus instead, which is arguably where fail should have been put in the first place (*).
Twan
(*) Actually in a superclass MonadZero, but let's work with what we have
This is where I'd cast my vote, as well. MonadPlus is, currently, the proper generalization of Maybe's safe failure behavior. We should use it. I don't see how specializing to Maybe and requiring people to explicitly inject into an arbitrary MonadPlus gains anything over restricting to MonadPlus in the first place. -- Dan

On Sat, May 24, 2008 at 09:23:10PM -0400, Dan Doel wrote:
On Saturday 24 May 2008, Twan van Laarhoven wrote:
To retain most of the convenience I would propose we use MonadPlus instead, which is arguably where fail should have been put in the first place (*).
(*) Actually in a superclass MonadZero, but let's work with what we have
This is where I'd cast my vote, as well. MonadPlus is, currently, the proper generalization of Maybe's safe failure behavior. We should use it.
I don't see how specializing to Maybe and requiring people to explicitly inject into an arbitrary MonadPlus gains anything over restricting to MonadPlus in the first place.
What it gains is safety: with Maybe you know what you're getting, while with a class it depends on how the instance was defined. I'm not sure whether those arguing for MonadPlus are suggesting that these functions should use fail or mzero to signal failure. If fail, there will be instances that implement it using error or an exception. If mzero, there's less gained over Maybe, but still no guarantee of safety.

Ross Paterson wrote:
I'm not sure whether those arguing for MonadPlus are suggesting that these functions should use fail or mzero to signal failure. If fail, there will be instances that implement it using error or an exception.
Oh, no, they must mean mzero. I thought that was the whole point.
If mzero, there's less gained over Maybe, but still no guarantee of safety.
If a program has a safety problem with mzero, that anyway needs to be detected. So I don't think that will have an effect on overall program safety, it's an orthogonal safety concern. Other than minor convenience adavantages one way or the other depending on what program I happen to be writing, there is only one thing I can think of that might make a difference. Current compilers might produce programs that are slightly less efficient with MonadPlus, and there might be no easy way to work around that if MonadPlus is hard-wired into the library. Efficiency experts? For me, even if that is true, it would rarely be an issue. -Yitz

Hi
If mzero, there's less gained over Maybe, but still no guarantee of safety.
If a program has a safety problem with mzero, that anyway needs to be detected. So I don't think that will have an effect on overall program safety, it's an orthogonal safety concern.
I don't think this is the case. mzero vs. Nothing One doesn't crash, the other may crash depending on what is floating around. Perhaps I've used type inference extensively, and the actual decision of what mzero means is 10 functions away. Now its really hard to see the program is safe, versus not. Of course, if you use an automated thing, this is irrelevant (traditional plug of Catch: http://www-users.cs.york.ac.uk/~ndm/catch/) - but I think its still useful for humans to be able to decide this easily.
Other than minor convenience adavantages one way or the other depending on what program I happen to be writing, there is only one thing I can think of that might make a difference. Current compilers might produce programs that are slightly less efficient with MonadPlus, and there might be no easy way to work around that if MonadPlus is hard-wired into the library. Efficiency experts?
Discussions about the ideal and perfect API should not come down to such minor considerations as efficiency :-) In reality, I don't think it makes any difference, and in fact I think the Monad class might make some things more efficient, as the class is likely to be specialised away but returns of Maybe with a liftMaybe aren't likely to be optimised out, as its essentially deforestation on a non-list type, which GHC can't do (but something like Supero could http://www-users.cs.york.ac.uk/~ndm/supero/) Thanks Neil

Hello Neil, Sunday, May 25, 2008, 4:28:45 PM, you wrote:
mzero vs. Nothing
One doesn't crash, the other may crash depending on what is floating around. Perhaps I've used type inference extensively, and the actual decision of what mzero means is 10 functions away. Now its really hard to see the program is safe, versus not.
it looks like argument against type-inferencing languages as whole. once you have jumped into this wagon, it's depend on your experience how much polymorphism you will use. i know people who doesn't like monads at all because they think that monads are just fool way to implement imperativeness. i'm not comfortable with MonadPlus instances, but i don't see this as reason why more advanced haskellers shouldn't be able to use findMin in mre advanced ways -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

I wrote:
If a program has a safety problem with mzero, that anyway needs to be detected. So I don't think that will have an effect on overall program safety, it's an orthogonal safety concern.
Neil Mitchell wrote:
mzero vs. Nothing One doesn't crash, the other may crash depending on what is floating around. Perhaps I've used type inference extensively, and the actual decision of what mzero means is 10 functions away. Now its really hard to see the program is safe, versus not.
Why is that any different than than the risk of Nothing when there may be an incomplete pattern match on Just that is 10 functions away? Functions, methods, and constructors each have their own associated risks. Aren't those risks orthogonal to which type we choose?
Current compilers might produce programs that are slightly less efficient with MonadPlus, and there might be no easy way to work around that if MonadPlus is hard-wired into the library. Efficiency experts?
Discussions about the ideal and perfect API should not come down to such minor considerations as efficiency :-) In reality, I don't think it makes any difference, and in fact I think the Monad class might make some things more efficient,
Well then, it's back to deuce, as far as I'm concerned. Which is bad, because in the meantime we're still stuck with fail. Thanks, Yitz

On Sun, May 25, 2008 at 01:28:45PM +0100, Neil Mitchell wrote:
Hi
If mzero, there's less gained over Maybe, but still no guarantee of safety.
If a program has a safety problem with mzero, that anyway needs to be detected. So I don't think that will have an effect on overall program safety, it's an orthogonal safety concern.
I don't think this is the case.
mzero vs. Nothing
One doesn't crash, the other may crash depending on what is floating around. Perhaps I've used type inference extensively, and the actual decision of what mzero means is 10 functions away. Now its really hard to see the program is safe, versus not.
Can you name a single instance of MonadPlus in the standard libraries where mzero uses error or undefined? The closest example I can think of is the instance for IO which throws an exception, but this really isn't the same as crashing. Cheers, Spencer Janssen

On Sun, May 25, 2008 at 02:26:36AM +0200, Twan van Laarhoven wrote:
Ross Paterson wrote:
The proposal is to change these signatures back, specializing them to Maybe.
To retain most of the convenience I would propose we use MonadPlus instead, which is arguably where fail should have been put in the first place (*).
(*) Actually in a superclass MonadZero, but let's work with what we have now.
Also, for a map to be empty or not contain a particular key is not intrinsically an error; in particular the view functions are just views. If one wants to treat these cases as errors, it seems reasonable to mark this explicitly.

(+1) for Maybe
I think the proposal to generalize to MonadPlus is even worse. In this
case the function can indicate failure with either fail or mzero which
makes things even worse.
Regards,
Krasimir
On Sun, May 25, 2008 at 1:59 AM, Ross Paterson
Several functions on containers used to have types like
lookup :: (Ord k) => k -> Map k a -> Maybe a
but these were generalized to
lookup :: (Monad m, Ord k) => k -> Map k a -> m a
The only methods of Monad used are return and fail. The problem is that, depending on the monad, fail can be an ordinary value or a runtime error: this device makes it harder to check whether a program is safe, because it hides possible runtime errors among testable conditions.
The proposal is to change these signatures back, specializing them to Maybe.
The functions involved are:
lookup :: Ord k => k -> Map k a -> Maybe a lookupIndex :: Ord k => k -> Map k a -> Maybe Int minViewWithKey :: Map k a -> Maybe ((k,a), Map k a) maxViewWithKey :: Map k a -> Maybe ((k,a), Map k a) minView :: Map k a -> Maybe (a, Map k a) maxView :: Map k a -> Maybe (a, Map k a)
lookup :: Key -> IntMap a -> Maybe a maxViewWithKey :: IntMap a -> Maybe ((Key, a), IntMap a) minViewWithKey :: IntMap a -> Maybe ((Key, a), IntMap a) maxView :: IntMap a -> Maybe (a, IntMap a) minView :: IntMap a -> Maybe (a, IntMap a)
minView :: Set a -> Maybe (a, Set a) maxView :: Set a -> Maybe (a, Set a)
maxView :: IntSet -> Maybe (Int, IntSet) minView :: IntSet -> Maybe (Int, IntSet)
No information is lost, because in each case there is a single failure mode. _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

I personally would be happy with either Maybe or MonadPlus. I hope we don't miss out on getting rid of fail by arguing about Maybe vs. MonadPlus. Dan Doel wrote:
I don't see how specializing to Maybe and requiring people to explicitly inject into an arbitrary MonadPlus gains anything over restricting to MonadPlus in the first place.
Maybe is not arbitrary. It is the "unit" instance of MonadPlus. It can be lifted trivially into any other instance. Krasimir Angelov wrote:
I think the proposal to generalize to MonadPlus is even worse. In this case the function can indicate failure with either fail or mzero which makes things even worse.
The same is true for Maybe. But once we are in Maybe or MonadPlus, fail becomes a red herring. Any program that uses fail can be marked as unsafe, just like any program that uses error. -Yitz

On Sunday 25 May 2008, Yitzchak Gale wrote:
I personally would be happy with either Maybe or MonadPlus.
I hope we don't miss out on getting rid of fail by arguing about Maybe vs. MonadPlus.
I don't think we should get rid of fail. There's nothing wrong with it, per se. It just shouldn't be in Monad, it should be in MonadPlus (or MonadZero if things get split back up 1.4 style). fail is mzero that takes a string to explain what happened. In fact, if the functions were revised to be restricted to MonadPlus, I'd expect it'd be a change only in the declared type signature. They'd likely still call fail because it provides slightly more information to the monads that can actually use it (Either e, IO, ...). Having both fail and mzero as failure options isn't a real problem, because they should do the same thing in monads that have both (at least, off the top of my head; I may be forgetting some). The problem is calling fail in monads that don't have an mzero, because they don't have a notion of failure.
Maybe is not arbitrary. It is the "unit" instance of MonadPlus. It can be lifted trivially into any other instance.
I didn't mean to say that Maybe is arbitrary. I meant that specializing to Maybe makes it more inconvenient to use with other MonadPlus instances, and I don't see a benefit to counter that. Yes, you can trivially inject Maybe into an arbitrary MonadPlus. You can do it for any Foldable, in fact: Data.Foldable.msum . fmap return But having to write liftMaybe whenever you want that has the potential to be annoying. We currently have the same problem with IO functions, where you have to stick a liftIO on everything if you want to wrap IO in a monad transformer. That's not to mention potential information loss compared to fail. For instance, readMaybe doesn't subsume readIO, because the latter can report the difference between no parse and ambiguous parses. Using Either String covers that, except it's not declared a Monad except in mtl, because fail is in the wrong place. I just think it's frustrating that we have abstractions that do exactly what we want, and then don't use them. :) -- Dan

On Sun, May 25, 2008 at 07:58:44AM -0400, Dan Doel wrote:
I don't think we should get rid of fail. There's nothing wrong with it, per se. It just shouldn't be in Monad, it should be in MonadPlus (or MonadZero if things get split back up 1.4 style). fail is mzero that takes a string to explain what happened.
No, it's a different value: one can write programs that distinguish them. Haskell 98 treats error "string" as _|_ only because it can't analyse _|_.
[...] The problem is calling fail in monads that don't have an mzero, because they don't have a notion of failure.
That is indeed part of the problem, because someone will define an instance for those monads, for the sake of convenience.
I didn't mean to say that Maybe is arbitrary. I meant that specializing to Maybe makes it more inconvenient to use with other MonadPlus instances, and I don't see a benefit to counter that.
There is a choice here between convenience and safety. What would Haskell choose?
[...] That's not to mention potential information loss compared to fail.
which does not arise in this particular case.
[...] I just think it's frustrating that we have abstractions that do exactly what we want, and then don't use them. :)
It's not an abstraction: it's overloading. It conflates three different things (an element of a view, exceptions and runtime errors).

On Tuesday 27 May 2008, Ross Paterson wrote:
On Sun, May 25, 2008 at 07:58:44AM -0400, Dan Doel wrote:
I don't think we should get rid of fail. There's nothing wrong with it, per se. It just shouldn't be in Monad, it should be in MonadPlus (or MonadZero if things get split back up 1.4 style). fail is mzero that takes a string to explain what happened.
No, it's a different value: one can write programs that distinguish them. Haskell 98 treats error "string" as _|_ only because it can't analyse _|_.
fail is not identical to error. That is merely the default implementation. For instance: fail s = Nothing :: Maybe a fail s = [] :: [a] fail s = Left s :: Either String a In particular, a monad that is an instance of MonadPlus should have an implementation of fail that is a proper value in that monad, and not just bottom. If not, I'd wager it's a bug in the Monad instance. If fail were moved to MonadPlus(Zero), we could have: class Monad m => MonadPlus m where ... fail s = mzero mzero = fail "mzero" And the only way to even accidentally define fail as bottom would be to define neither fail nor mzero.
[...] The problem is calling fail in monads that don't have an mzero, because they don't have a notion of failure.
That is indeed part of the problem, because someone will define an instance for those monads, for the sake of convenience.
Define an instance of what? If someone uses error to define an instance of MonadZero to get fail in a monad that shouldn't have it, that's their problem. It doesn't mean that using a monads-with-proper-fail class in the standard library is flawed.
There is a choice here between convenience and safety. What would Haskell choose?
Monads that are instances of MonadPlus are (or ought to be) precisely the ones in which it's safe to call fail, so how are we giving up safety with the more general solution (the only exception I can think of is IO, where fail/mzero throws an IO exception, and people think that this isn't exceptional enough to warrant that, but I think that's more of a case against IO being MonadPlus than against using MonadPlus + fail in lookup/readM/...).
[...] That's not to mention potential information loss compared to fail.
which does not arise in this particular case.
No, but it does arise with readM, but proper use of fail got shouted down there, too.
[...] I just think it's frustrating that we have abstractions that do exactly what we want, and then don't use them. :)
It's not an abstraction: it's overloading. It conflates three different things (an element of a view, exceptions and runtime errors).
How is it not abstraction? Elsewhere, Isaac Dupree said that for proper implementation of lookup, we want two operations: unit :: a -> m a zero :: m a unit injects a proper value into a possibly-failing computation, and zero expresses failure. But, as we know, using only those, and pattern matching, we end up with code like this: case lookup k m of Nothing -> Nothing -- overall computation is a failure Just a -> case lookup k' m of Nothing -> Nothing -- same as above Just b -> ... which is annoying. So, in general, we want one more sort of operation, for chaining together computations in a way that propagates failure: (>>=) :: m a -> (a -> m b) -> m b zero >>= f = zero -- (and m >>= const zero = zero, but IO fails there) Maybe is a concrete type (constructor) that provides all this, but the general name for such things is, precisely, MonadZero[1]. Defining lookup and other fallible operations in terms of a general class of things that properly support failure instead of one particular one sounds like abstraction to me, but I'd settle for just calling it 'useful'. :) And although Maybe a provides the above operations, it doesn't strike me as the most commonly used type to do so. Specializing to Maybe means it doesn't automatically work in any of [], Either e, MaybeT m or FooT all-of-the-above. At best, you'll have to manually annotate with lifts everywhere. It's the exact same issue we currently have with transformers over IO, where one has to place liftIO all over such code. But, this is, of course, all merely my opinion. -- Dan 1: One could, of course, decide to go with some kind of ApplicativeZero, or so on. Or even PointedFunctorZero, because fmap is a generic way to use a possibly-failing computation with a pure function with automatic failure propagation. Strictly speaking, the composition/chaining operation isn't needed by lookup/etc., and Isaac's point is valid, but I don't think MonadZero or something like it is too overly specific. Perhaps with class aliases we could hope for some kind of pointed pseudo-functor with zero that isn't too arduous to use, but we don't have those currently.

well, what we need is (unit :: a -> m a) and (zero :: m a). Maybe gives us that nicely (Just,Nothing). Monad is not nice, (return,fail "..."). MonadPlus has (return,mzero) BUT is too specific, as some types with a (unit,zero) aren't even Monads, or don't have mplus. Alternative (of Applicative fame) has (pure,empty) and no "fail" to be confused with... but it's less used yet, and it still requires fmap, ap and mplus (er, I mean, <*> and <|>). Do we want every return type that's simple pattern-matchable data to be a type-class instead, so that we can have fewer explicit conversions applied to them? (I suppose this is considered explicit deforestation in the sense that ndm says GHC doesn't know how to do with returned "data") I was assuming that we don't want that, and that therefore I prefer Maybe. But I'm not sure anymore. It seems that can give conciseness without harm... except for making it harder to tell what type everything is (when looking a text-editor that doesn't know Haskell type inference). -Isaac

On Sun, May 25, 2008 at 6:34 AM, Yitzchak Gale
Dan Doel wrote:
I don't see how specializing to Maybe and requiring people to explicitly inject into an arbitrary MonadPlus gains anything over restricting to MonadPlus in the first place.
Maybe is not arbitrary. It is the "unit" instance of MonadPlus. It can be lifted trivially into any other instance.
This is somewhat off-topic, but it's worth noting that there is some
controversy over whether Maybe is an appropriate instance of MonadPlus
at all. One of the laws commonly given for MonadPlus is left
distribution, which Maybe does not satisfy.
Left distribution: mplus a b >>= f = mplus (a >>= f) (b >>= f)
(The actual controversy is whether left distribution should be
required for MonadPlus instances. Unfortunately, the issue is fairly
quiet, so it is unlikely to be resolved.)
Back on topic: I vote in favor of explicit Maybe return types over
Monad or MonadPlus. Every time I've used functions like lookup, they
ended up returning a Maybe, even their callers immediately threw
exceptions on receiving Nothing. Much easier to create a wrapper
function that does exactly what you want than to create an instance of
Monad(Plus) just to handle partial functions correctly.
--
Dave Menendez

Ross Paterson wrote:
Several functions on containers used to have types like
lookup :: (Ord k) => k -> Map k a -> Maybe a
but these were generalized to
lookup :: (Monad m, Ord k) => k -> Map k a -> m a
The proposal is to change these signatures back, specializing them to Maybe.
I'm all for Maybe in the question Monad VS Maybe. Concerning MonadZero VS Maybe, the first observation is of course that both approaches have the same expressiveness, lift :: MonadZero m => Maybe a -> m a lift = maybe mzero return unlift :: (forall m . MonadZero m => m a) -> Maybe a unlift = id are inverse to each other. In other words, Maybe has a universal property (this sounds much fancier than it really is). So, the only decision here is whether the library should factor things via Maybe or include an automatic lift for extra convenience. I'm not sure whether this convenience is actually used, can someone dig up statistics from hackage? Also, it's not entirely clear whether MonadZero is the most general abstraction. Is ApplicativeZero better? Or something else? In any case, I prefer Maybe here as well because it's straightforward and simple. Every other abstraction is just a lift away. Regards, apfelmus

Hi On 28 May 2008, at 10:21, apfelmus wrote:
Ross Paterson wrote:
Several functions on containers used to have types like lookup :: (Ord k) => k -> Map k a -> Maybe a but these were generalized to lookup :: (Monad m, Ord k) => k -> Map k a -> m a The proposal is to change these signatures back, specializing them to Maybe.
I'm all for Maybe in the question Monad VS Maybe.
Me too. (+1) for Ross's proposal. [..]
Also, it's not entirely clear whether MonadZero is the most general abstraction. Is ApplicativeZero better? Or something else?
Maybe is the most general abstraction. Requiring (>>=), or even (<*>) seems excessive. What we need is "any f with zero and return", so why not pick the canonical, initial, inductively defined such thing?
In any case, I prefer Maybe here as well because it's straightforward and simple. Every other abstraction is just a lift away.
And that's no coincidence, of course. The whole point of inductive definition is to, er, induce such lifts to other settings with /at least/ the same structure. The point was well made to me by James McKinna, years ago, when he suggested that we mediate Epigram's system of "views" via datatypes: the cheap way of abstracting over "all predicates closed under this and that" is to consider the initial one, ie the inductively defined thing with this and that. A whole bunch of higher-order jiggery-pokery with control operators became plain first-order code at a stroke. So it's not a question of concrete-vs-abstract here. The concrete is by inductive (morally anyway) definition, the most abstract thing you can have. All the best Conor

On Wed, 2008-05-28 at 11:11 +0100, Conor McBride wrote:
Ross Paterson wrote:
Several functions on containers used to have types like lookup :: (Ord k) => k -> Map k a -> Maybe a but these were generalized to lookup :: (Monad m, Ord k) => k -> Map k a -> m a The proposal is to change these signatures back, specializing them to Maybe.
I'm all for Maybe in the question Monad VS Maybe.
Me too. (+1) for Ross's proposal.
If we need any more (+1) votes you can count mine.
Also, it's not entirely clear whether MonadZero is the most general abstraction. Is ApplicativeZero better? Or something else?
Maybe is the most general abstraction. Requiring (>>=), or even (<*>) seems excessive. What we need is "any f with zero and return", so why not pick the canonical, initial, inductively defined such thing?
Good. I like that argument. As others have pointed out, it's easy to lift maybe into something else when that's needed. maybe :: a -> (b -> a) -> Maybe b -> a Duncan

And here's another vote for Maybe. That's almost always the return
type that you want anyway, so the inconvenience in minimal.
And anyone who wants the old behavior can easily make a utility
function that provides it.
The current behaviour encourages sloppy programming.
-- Lennart
On Wed, May 28, 2008 at 7:51 PM, Duncan Coutts
On Wed, 2008-05-28 at 11:11 +0100, Conor McBride wrote:
Ross Paterson wrote:
Several functions on containers used to have types like lookup :: (Ord k) => k -> Map k a -> Maybe a but these were generalized to lookup :: (Monad m, Ord k) => k -> Map k a -> m a The proposal is to change these signatures back, specializing them to Maybe.
I'm all for Maybe in the question Monad VS Maybe.
Me too. (+1) for Ross's proposal.
If we need any more (+1) votes you can count mine.
Also, it's not entirely clear whether MonadZero is the most general abstraction. Is ApplicativeZero better? Or something else?
Maybe is the most general abstraction. Requiring (>>=), or even (<*>) seems excessive. What we need is "any f with zero and return", so why not pick the canonical, initial, inductively defined such thing?
Good. I like that argument.
As others have pointed out, it's easy to lift maybe into something else when that's needed.
maybe :: a -> (b -> a) -> Maybe b -> a
Duncan
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

I also vote for Maybe. I have never used the feature for failing in
any other monad than Maybe.
Josef
On Thu, May 29, 2008 at 1:27 AM, Lennart Augustsson
And here's another vote for Maybe. That's almost always the return type that you want anyway, so the inconvenience in minimal. And anyone who wants the old behavior can easily make a utility function that provides it. The current behaviour encourages sloppy programming.
-- Lennart
On Wed, May 28, 2008 at 7:51 PM, Duncan Coutts
wrote: On Wed, 2008-05-28 at 11:11 +0100, Conor McBride wrote:
Ross Paterson wrote:
Several functions on containers used to have types like lookup :: (Ord k) => k -> Map k a -> Maybe a but these were generalized to lookup :: (Monad m, Ord k) => k -> Map k a -> m a The proposal is to change these signatures back, specializing them to Maybe.
I'm all for Maybe in the question Monad VS Maybe.
Me too. (+1) for Ross's proposal.
If we need any more (+1) votes you can count mine.
Also, it's not entirely clear whether MonadZero is the most general abstraction. Is ApplicativeZero better? Or something else?
Maybe is the most general abstraction. Requiring (>>=), or even (<*>) seems excessive. What we need is "any f with zero and return", so why not pick the canonical, initial, inductively defined such thing?
Good. I like that argument.
As others have pointed out, it's easy to lift maybe into something else when that's needed.
maybe :: a -> (b -> a) -> Maybe b -> a
Duncan
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

apfelmus wrote:
In any case, I prefer Maybe here as well because it's straightforward and simple. Every other abstraction is just a lift away.
Following this line of reasoning: why is 1 syntactic sugar for fromIntegral 1? If 1 has type Integer then the generic value is just a fromIntergal away! If we can make a function more convenient to use by making it more generic, I see no reason not to do so, as long as things remain safe. Twan

On 28 May 2008, at 1:14 PM, Twan van Laarhoven wrote:
apfelmus wrote:
In any case, I prefer Maybe here as well because it's straightforward and simple. Every other abstraction is just a lift away.
Following this line of reasoning: why is 1 syntactic sugar for fromIntegral 1? If 1 has type Integer then the generic value is just a fromIntergal away!
That's a good point the other way --- I suspect, like most things Num, numeric literals were rather grand-fathered in than designed intentionally that way. jcc

Hi
Following this line of reasoning: why is 1 syntactic sugar for fromIntegral 1? If 1 has type Integer then the generic value is just a fromIntergal away!
That's a good point the other way --- I suspect, like most things Num, numeric literals were rather grand-fathered in than designed intentionally that way.
fromIntegral is essential if you have two "integer" types, namely Int and Integer. If you are looking for something to blame, then its the premature optimisation that is Int. Int is really just a performance hack around Integer. Of course, we all want the performance of Int, so I'm not saying its a bad thing. But one hack often leads to another. Thanks Neil

On 29 May 2008, at 1:30 AM, Neil Mitchell wrote:
Hi
Following this line of reasoning: why is 1 syntactic sugar for fromIntegral 1? If 1 has type Integer then the generic value is just a fromIntergal away!
That's a good point the other way --- I suspect, like most things Num, numeric literals were rather grand-fathered in than designed intentionally that way.
fromIntegral is essential if you have two "integer" types, namely Int and Integer. If you are looking for something to blame, then its the premature optimisation that is Int. Int is really just a performance hack around Integer.
Um, that de-railed quickly... ‘fromIntegral’ in the original is a typo or mis-understanding for ‘fromInteger’. My comment was re: implicit fromInteger (and polymorphic numeric literals). GP was arguing for making Map.lookup polymorphic in the failure monad; I replied I thought, in the case of numeric literals, that no-one designing Haskell without the tradition that 3 `member` IR, no-one would have thought that 3 :: Integer and 3 :: Double both made sense. Explicit conversions are not really the issue here. jcc

Hi,
I also like Maybe---it is simpler, it is what you want most of the time.
-Iavor
On Thu, May 29, 2008 at 6:57 AM, Jonathan Cast
On 29 May 2008, at 1:30 AM, Neil Mitchell wrote:
Hi
Following this line of reasoning: why is 1 syntactic sugar for fromIntegral 1? If 1 has type Integer then the generic value is just a fromIntergal away!
That's a good point the other way --- I suspect, like most things Num, numeric literals were rather grand-fathered in than designed intentionally that way.
fromIntegral is essential if you have two "integer" types, namely Int and Integer. If you are looking for something to blame, then its the premature optimisation that is Int. Int is really just a performance hack around Integer.
Um, that de-railed quickly... 'fromIntegral' in the original is a typo or mis-understanding for 'fromInteger'. My comment was re: implicit fromInteger (and polymorphic numeric literals). GP was arguing for making Map.lookup polymorphic in the failure monad; I replied I thought, in the case of numeric literals, that no-one designing Haskell without the tradition that 3 `member` IR, no-one would have thought that 3 :: Integer and 3 :: Double both made sense. Explicit conversions are not really the issue here.
jcc
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Following this line of reasoning: why is 1 syntactic sugar for fromIntegral 1? If 1 has type Integer then the generic value is just a fromIntergal away!
If we can make a function more convenient to use by making it more generic, I see no reason not to do so, as long as things remain safe.
From my point of view, the automatic fromIntegral *does* cause confusion (wasn't there a question wondering about that just recently?). However, it's so common to want integer-looking literals to actually be Ints or Doubles or something that the convenience outweighs the extra complexity.
What some people seem to be saying is that using lookup with some other monad is just not common enough for it to be worth the extra complexity. I always use it with Maybe myself, and I'm all for keeping things concrete unless there's a need. I see the point about lifts though and could imagine maybe someone has some pattern where they use their own monad a lot and lifts would be a hassle... but that's just "imagine" for me :) Also, I wouldn't say more generic (or rather, less explicit lifting needed) is really totally "free"... it always looks more complicated when you see some polymorphic typeclass constrained type constructor parameter vs. a monomorphic concrete one. And I think even just *looking* simple is important!

Evan Laforge wrote:
Also, I wouldn't say more generic (or rather, less explicit lifting needed) is really totally "free"... it always looks more complicated when you see some polymorphic typeclass constrained type constructor parameter vs. a monomorphic concrete one. And I think even just *looking* simple is important!
Agree. If you usually use it with Maybe, then -- the documentation should clue you in on the fact -- after you realize it is, then on the occasion that it's used with a different type than Maybe, you're likely to get confused doing type-inference-in-your-head. Also, ad-hoc polymorphism in *both* function results and arguments, quickly leads to ambiguity and the type checker may yell at you. +1 for Maybe. Conor put it best (though the argument was incomplete without the practical arguments and personal opinions and experiences) -Isaac

To summarize: Several container classes have types like lookup :: (Monad m, Ord k) => k -> Map k a -> m a and use fail to signal exceptional conditions. This allows them to be used with a range of monads, e.g. [], IO and parser monads. Some of these use the string passed to fail. However the strings are not very useful, and probably shouldn't be exposed in production code: Data.Map.lookup: Key not found Data.Map.lookupIndex: Key not found Data.Map.minViewWithKey: empty map Data.Map.maxViewWithKey: empty map Data.Map.minView: empty map Data.Map.maxView: empty map The problem with this device is that depending on the monad, fail can be an ordinary value, an exception or a runtime error (the default). It complicates checking whether a program is safe, because it hides possible runtime errors among testable conditions. The proposal was to revert these types to the simpler lookup :: (Ord k) => k -> Map k a -> Maybe a No information would be lost, as each of these functions has only one use of fail -- the Maybe type describes the situation precisely. As the initial "thing with zero and return", it can be lifted to any other. Several people argued that the non-Maybe case is rare, and explicitly marking use of a different monad is no bad thing. Changing the monad classes is not a possibility at this stage: we need to work with the classes as defined in Haskell 98. No-one defended the status quo, but Twan van Laarhoven and Dan Doel argued that if the constraint were changed from Monad to MonadPlus, one should be able to assume a safe fail, while avoiding the the need for lifting. At present, fail in STM and Seq use the default error, which could be changed. Haskell 98 specifies the fail in IO as throwing an exception (the MonadPlus instance is in the mtl package). In favour of the proposal were: apfelmus, Conor McBride, David Menendez, Don Stewart, Duncan Coutts, Iavor Diatchki, Isaac Dupree, Josef Svenningsson, Krasimir Angelov, Lennart Augustsson, Neil Mitchell, Ross Paterson. That's not consensus, but it is a substantial majority, and I think we've explored all the issues. So I propose to make the change.

Excerpts from Ross Paterson's message of Sat Jul 19 01:29:40 +0200 2008:
To summarize:
Several container classes have types like
lookup :: (Monad m, Ord k) => k -> Map k a -> m a
And what about keeping the monadic version under another name like lookupM? Cheers, -- Nicolas Pouillard aka Ertai

On Mon, Jul 21, 2008 at 03:19:43PM +0200, Nicolas Pouillard wrote:
Excerpts from Ross Paterson's message of Sat Jul 19 01:29:40 +0200 2008:
To summarize:
Several container classes have types like
lookup :: (Monad m, Ord k) => k -> Map k a -> m a
And what about keeping the monadic version under another name like lookupM?
Well, the aim was to make the API safer.

Ross Paterson wrote:
That's not consensus, but it is a substantial majority, and I think we've explored all the issues. So I propose to make the change.
Well, what are the guidelines in this case? Proposer's discretion? If a week has gone by and no one has commented further, I guess you should commit the change (or ask someone who can, to do so). At least, the ticket shouldn't be closed until either (1) the patches have been applied (and this stated), or (2) until it's explicitly (or clearly) been dropped with no change made. If the patches are different from what you actually posted before, you might want to first post the actual patches you're planning to apply. -Isaac

Quoting Isaac Dupree
Ross Paterson wrote:
That's not consensus, but it is a substantial majority, and I think we've explored all the issues. So I propose to make the change.
Well, what are the guidelines in this case? Proposer's discretion? If a week has gone by and no one has commented further, I guess you should commit the change (or ask someone who can, to do so). At least, the ticket shouldn't be closed until either (1) the patches have been applied (and this stated), or (2) until it's explicitly (or clearly) been dropped with no change made. If the patches are different from what you actually posted before, you might want to first post the actual patches you're planning to apply.
I applied the patch, with only a minor change in a doc comment. ---------------------------------------------------------------- This message was sent using IMP, the Internet Messaging Program.
participants (21)
-
apfelmus
-
Bulat Ziganshin
-
Conor McBride
-
Dan Doel
-
David Menendez
-
Don Stewart
-
Duncan Coutts
-
Evan Laforge
-
Iavor Diatchki
-
Isaac Dupree
-
Jonathan Cast
-
Josef Svenningsson
-
Krasimir Angelov
-
Lennart Augustsson
-
Neil Mitchell
-
Nicolas Pouillard
-
Ross Paterson
-
ross@soi.city.ac.uk
-
Spencer Janssen
-
Twan van Laarhoven
-
Yitzchak Gale