
I want to use 'lookup' inside an Either String monad. So I want to write something like eitherLookup :: Eq a => String -> a -> [(a,b)] -> Either String b eitherLookup s x ps = case lookup x ps of Just y -> Right y Nothing -> Left s Is there such a function existing? Thanks, Mike

I think there is no such function in standard library.
But you can also do the same by `maybe (Left err) Right (lookup key
assoc)` without defining eitherLookup.
HTH
-nwn
On Sun, Sep 13, 2009 at 12:14 AM, Michael Mossey
I want to use 'lookup' inside an Either String monad. So I want to write something like
eitherLookup :: Eq a => String -> a -> [(a,b)] -> Either String b eitherLookup s x ps = case lookup x ps of Just y -> Right y Nothing -> Left s
Is there such a function existing?
Thanks, Mike _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

I often times have to write a lookup function that returns its value into
any monad instead of just Maybe. For example:
mLookup :: (Eq k, Monad m) => k -> [(k, v)] -> m v
mLookup k pairs = case lookup k pairs of
Nothing -> fail "mLookup: nothing found"
Just v -> return v
Hope that helps.
On Sat, Sep 12, 2009 at 6:51 PM, Yusaku Hashimoto
I think there is no such function in standard library.
But you can also do the same by `maybe (Left err) Right (lookup key assoc)` without defining eitherLookup.
HTH -nwn
On Sun, Sep 13, 2009 at 12:14 AM, Michael Mossey
wrote: I want to use 'lookup' inside an Either String monad. So I want to write something like
eitherLookup :: Eq a => String -> a -> [(a,b)] -> Either String b eitherLookup s x ps = case lookup x ps of Just y -> Right y Nothing -> Left s
Is there such a function existing?
Thanks, Mike _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Sat, Sep 12, 2009 at 09:13:58PM +0300, Michael Snoyman wrote:
I often times have to write a lookup function that returns its value into any monad instead of just Maybe. For example:
mLookup :: (Eq k, Monad m) => k -> [(k, v)] -> m v mLookup k pairs = case lookup k pairs of Nothing -> fail "mLookup: nothing found" Just v -> return v
This is actually the type that the lookup function USED to have, but it was changed since monads actually have nothing to do with failing (the fail method is just a hack used to handle pattern-match failures in do-notation). Probably a better implementation of this would be mLookup :: (Eq k, MonadPlus m) => k -> [(k,v)] -> m v mLookup k pairs = maybe mzero return (lookup k pairs) -Brent

On Sun, Sep 13, 2009 at 3:40 PM, Brent Yorgey
On Sat, Sep 12, 2009 at 09:13:58PM +0300, Michael Snoyman wrote:
I often times have to write a lookup function that returns its value into any monad instead of just Maybe. For example:
mLookup :: (Eq k, Monad m) => k -> [(k, v)] -> m v mLookup k pairs = case lookup k pairs of Nothing -> fail "mLookup: nothing found" Just v -> return v
This is actually the type that the lookup function USED to have, but it was changed since monads actually have nothing to do with failing (the fail method is just a hack used to handle pattern-match failures in do-notation). Probably a better implementation of this would be
mLookup :: (Eq k, MonadPlus m) => k -> [(k,v)] -> m v mLookup k pairs = maybe mzero return (lookup k pairs)
I understand that fail being in Monad is controversial, but my version of the function works in *all* monads. This is very useful for: 1) Quickly writing up code in the IO monad (ie, for a shell script) 2) Check out the data-objects library; having an mLookup function makes dealing with mappings very convenient. Michael

On Mon, Sep 14, 2009 at 09:42:22PM +0300, Michael Snoyman wrote:
On Sun, Sep 13, 2009 at 3:40 PM, Brent Yorgey
wrote: On Sat, Sep 12, 2009 at 09:13:58PM +0300, Michael Snoyman wrote:
I often times have to write a lookup function that returns its value into any monad instead of just Maybe. For example:
mLookup :: (Eq k, Monad m) => k -> [(k, v)] -> m v mLookup k pairs = case lookup k pairs of Nothing -> fail "mLookup: nothing found" Just v -> return v
This is actually the type that the lookup function USED to have, but it was changed since monads actually have nothing to do with failing (the fail method is just a hack used to handle pattern-match failures in do-notation). Probably a better implementation of this would be
mLookup :: (Eq k, MonadPlus m) => k -> [(k,v)] -> m v mLookup k pairs = maybe mzero return (lookup k pairs)
I understand that fail being in Monad is controversial, but my version of the function works in *all* monads. This is very useful for:
It doesn't work in *all* monads -- it only works in monads which support a sensible notion of failure. This is exactly what is captured by the MonadPlus constraint on my version of mLookup. And, in fact, any monad in context of which you would want to use mLookup (IO, Maybe, [], ...) are already instances of MonadPlus. Also, fail being in Monad isn't controversial, it's just wrong. =) The only controversial thing is what to DO about it now that it's there... -Brent

On Tue, Sep 15, 2009 at 3:08 AM, Brent Yorgey
It doesn't work in *all* monads -- it only works in monads which support a sensible notion of failure. This is exactly what is captured by the MonadPlus constraint on my version of mLookup. And, in fact, any monad in context of which you would want to use mLookup (IO, Maybe, [], ...) are already instances of MonadPlus.
I'm looking at the Control.Monad documentation ( http://hackage.haskell.org/packages/archive/base/latest/doc/html/Control-Mon...), and it doesn't seem that IO is an instance of MonadPlus. I get the same results with a simple code check. Can you clarify? Calling lookup from IO is a common use case for me. Michael

On Sep 15, 2009, at 16:21 , Michael Snoyman wrote:
On Tue, Sep 15, 2009 at 3:08 AM, Brent Yorgey
wrote: It doesn't work in *all* monads -- it only works in monads which support a sensible notion of failure. This is exactly what is captured by the MonadPlus constraint on my version of mLookup. And, in fact, any monad in context of which you would want to use mLookup (IO, Maybe, [], ...) are already instances of MonadPlus. I'm looking at the Control.Monad documentation (http://hackage.haskell.org/packages/archive/base/latest/doc/html/Control-Mon... ), and it doesn't seem that IO is an instance of MonadPlus. I get the same results with a simple code check. Can you clarify? Calling lookup from IO is a common use case for me.
That's a bit of stupidity I wish would be fixed; for some bizarre reason, the instance is in Control.Monad.Error. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On Tue, Sep 15, 2009 at 11:49 PM, Brandon S. Allbery KF8NH < allbery@ece.cmu.edu> wrote:
On Sep 15, 2009, at 16:21 , Michael Snoyman wrote:
On Tue, Sep 15, 2009 at 3:08 AM, Brent Yorgey
wrote: It doesn't work in *all* monads -- it only works in monads which support a sensible notion of failure. This is exactly what is captured by the MonadPlus constraint on my version of mLookup. And, in fact, any monad in context of which you would want to use mLookup (IO, Maybe, [], ...) are already instances of MonadPlus.
I'm looking at the Control.Monad documentation ( http://hackage.haskell.org/packages/archive/base/latest/doc/html/Control-Mon...), and it doesn't seem that IO is an instance of MonadPlus. I get the same results with a simple code check. Can you clarify? Calling lookup from IO is a common use case for me.
That's a bit of stupidity I wish would be fixed; for some bizarre reason, the instance is in Control.Monad.Error.
And according to the documentation, that instance has a broken version of mzero. So it seems the argument of use MonadPlus because fail is not always defined properly doesn't exactly hold much water here. Can you tell me why you would still recommend representing lookup failure with the mzero function instead of the seemingly more aptly named and more available fail function? Michael

On Wed, Sep 16, 2009 at 01:19:53AM +0300, Michael Snoyman wrote:
On Tue, Sep 15, 2009 at 11:49 PM, Brandon S. Allbery KF8NH < allbery@ece.cmu.edu> wrote:
I'm looking at the Control.Monad documentation ( http://hackage.haskell.org/packages/archive/base/latest/doc/html/Control-Mon...), and it doesn't seem that IO is an instance of MonadPlus. I get the same results with a simple code check. Can you clarify? Calling lookup from IO is a common use case for me.
That's a bit of stupidity I wish would be fixed; for some bizarre reason, the instance is in Control.Monad.Error.
And according to the documentation, that instance has a broken version of mzero. So it seems the argument of use MonadPlus because fail is not always defined properly doesn't exactly hold much water here. Can you tell me why you would still recommend representing lookup failure with the mzero function instead of the seemingly more aptly named and more available fail function?
The IO instance of mzero is only broken in the sense that it does not satisfy the law m >> mzero === mzero since the effects of m will happen on the left but not on the right. But this is to be expected with the IO monad: if you have to perform some I/O effects in order to find out whether the computation fails or not, you can't expect to roll back the effects once you do fail. In practice I don't think this would be much of an issue. But anyway, the reason I recommend not using fail is because it is an inelegant, unprincipled hack. If you have no problem with inelegant, unprincipled hacks then I guess I won't be able to convince you. =) Also, if you haven't already, you should read the email from Conor McBride in this same thread: after reading his email I'm now of the opinion that you shouldn't even use MonadPlus, but simply use Maybe. -Brent

On Sep 15, 2009, at 18:19 , Michael Snoyman wrote:
And according to the documentation, that instance has a broken version of mzero. So it seems the argument of use MonadPlus because fail is not always defined properly doesn't exactly hold much water here. Can you tell me why you would still recommend representing lookup failure with the mzero function instead of the seemingly more aptly named and more available fail function?
It's "broken" because IO is impure, so pure invariants are kinda hard to maintain. If you're in IO, you should expect that (or you need to think hard about what you're doing). How do you undo a putStrLn followed by an mzero? As for fail, the reason it exists is that the Haskell 98 blithering idiots^W^Wcommittee decided it was better to deal with pattern match failures in do blocks with a hack, instead of requiring monads supporting pattern match failures to declare themselves as such by being members of MonadZero (which these days exists only as part of MonadPlus, not as a standalone entity). -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On Sep 14, 2009, at 14:42 , Michael Snoyman wrote:
I understand that fail being in Monad is controversial, but my version of the function works in *all* monads. This is very
Not really; "fail" in non-MonadPlus-es is a rather poorly defined notion, and there are no guarantees that the result will be at all sane. "mzero" is well defined. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

I prefer Alternative to MonadPlus for explaining failure. It has
better name and operator for failure and try-another.
import Control.Applicative
aLookup :: (Alternative f, Eq k) => k -> [(k,v)] -> f v
aLookup key pairs = maybe empty pure $ lookup key pairs
-nwn
On Tue, Sep 15, 2009 at 12:21 PM, Brandon S. Allbery KF8NH
On Sep 14, 2009, at 14:42 , Michael Snoyman wrote:
I understand that fail being in Monad is controversial, but my version of the function works in *all* monads. This is very
Not really; "fail" in non-MonadPlus-es is a rather poorly defined notion, and there are no guarantees that the result will be at all sane. "mzero" is well defined. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Hi This topic comes up a lot, and this is what I usually say when it does. It's a thing I learned from James McKinna, many years ago... Might I gently suggest that there is a much better, more natural way to abstract over every type-former which has some sort of return/pure-like thing and some sort of mzero/empty like thing? You could use the type-former which is inductively defined to be the least such thing, and as such has a canonical mapping to all the others, namely Maybe. It's not necessarily a good idea to fix on Monad or MonadPlus as there are other choices. For example, On 15 Sep 2009, at 07:14, Yusaku Hashimoto wrote:
I prefer Alternative to MonadPlus for explaining failure. It has better name and operator for failure and try-another.
import Control.Applicative
aLookup :: (Alternative f, Eq k) => k -> [(k,v)] -> f v aLookup key pairs = maybe empty pure $ lookup key pairs
there are notorious non-monadic instances for the above f (some formulations of parsing, in particular). So,
I understand that fail being in Monad is controversial, but my version of the function works in *all* monads.
this is a touch presumptuous. On the one hand, Brent is right when he says
It doesn't work in *all* monads -- it only works in monads which support a sensible notion of failure.
but he's perhaps excessive when he says
This is exactly what is captured by the MonadPlus constraint on my version of mLookup.
because it's not exact: it requires mplus as well as a sensible notion of failure. And yes, why should we insist on (>>=) when we just need a return and an mzero? Incidentally, I don't know where the MonadPlus instance
(IO, Maybe, [], ...) are already instances of MonadPlus.
of IO is coming from, but I want it caught and locked up now (in STM, for example) before it does any permanent damage. Why not factor out the failure-prone operations from the business of interpreting failure in some failure-supporting context? Work concretely while you can (types stay shorter, error messages make more sense) then apply adapters malt :: Alternative f => Maybe x -> f x malt = maybe empty pure mop :: MonadPlus m => Maybe x -> m x mop = maybe mzero return when you need to? This also reduces the risk of connecting an ambiguous supplier to an ambiguous consumer, (show . read) style. The message clearly bears repeating. Inductive definition is a concrete form of abstraction. Don't be fooled by its appearance: Maybe is the most abstract choice here -- the classier options demand more structure than is needed and thus exclude use-cases. I'll crawl back under my stone now. All the best Conor

Conor McBride wrote:
malt :: Alternative f => Maybe x -> f x malt = maybe empty pure
mop :: MonadPlus m => Maybe x -> m x mop = maybe mzero return
The message clearly bears repeating. Inductive definition is a concrete form of abstraction. Don't be fooled by its appearance: Maybe is the most abstract choice here -- the classier options demand more structure than is needed and thus exclude use-cases.
Seconded! Maybe is the most general choice. The only issue left here would be that the combinators malt and mop are missing from the standard library. Once again, their purpose is not generality, but the convenience of overloading. Regards, apfelmus -- http://apfelmus.nfshost.com

As a beginner, I'm not directly following the usefulness of these alternative implementations. I thought I would give some example code. Here I am trying to handle errors with Either String. You can read it here or in hpaste.org: http://hpaste.org/fastcgi/hpaste.fcgi/view?id=9393#a9393 import Data.Ratio import qualified Data.Map as Map -- An elemental music object such as note, rest, dynamic mark, etc. data MusicObject = MusicObject ... -- A composition has several "streams". A stream could be a continuous -- melody that appears on a single staff, or other types of data that -- are arranged serially in time. data Time = Rational data StreamId = StreamId ... data MusicStream = (StreadId, Map.Map Time MusicObject) data Comp = [MusicStream] -- A cursor is a concept used to "point to" a note or generalized location -- in the composition so that editing can be done at that point. For now, -- all we need is to point to the stream and time. data Cursor = Cursor { getCurId :: StreamId , getCurTime :: Time } -- Utility to make it easier to annotate an Either monad with a function -- that catches an error message, prepends a context message, and rethrows. ce :: String -> Either String a -> Either String a ce c = (flip catchError) (\s -> throwError (c ++ "\n" ++ s)) -- Utility to replace an item in an assoc list, inside the Either String -- monad. replaceAlist :: Eq a => a -> b -> [(a,b)] -> Either String [(a,b)] replaceAlist _ _ [] = throwError "Item not found in alist." replaceAlist iid obj (x:xs) = if fst x == iid then return $ (iid,obj) : xs else do rem <- replaceAlist iid obj xs return $ x : rem ... -- Delete a note from a composition. Deleting the last note in a stream is -- an error condition. -- -- Conditions that will cause an error: -- - cursor stream id doesn't exist in the composition -- - there is no note at the given cursor -- - there is only one note in the stream (so deleting it would delete -- the last note) compDeleteNote :: Cursor -> Comp -> Either String Comp compDeleteNote cur comp = ce "In compeDeleteNote:" $ do let Cursor { getCurId=iid, getCurTime=t } = cur -- First internal error might occur if no stream with the cursor's id -- occurs in the Comp. oldMap <- maybe (Left "no such stream") Right (lookup iid comp) -- Second internal error: no music object is found at the cursor's time. moAtCur <- maybe (Left "no m.o. at cursor") Right (Map.lookup t oldMap) let durAtCur = getDur moAtCur (l,r) = Map.split t oldMap r' = Map.mapKeys (\k -> k - durAtCur) r joined = Map.union l r' -- Third error condition: this action deleted the last note. if Map.null joined then (Left "deleted last note") else Right () replaceAlist iid joined comp

If I understood your post correctly, you said
- generalizing lookup to MonadPlus or Alternative or such classes are
not necessary
- use Maybe as usual, we should use adapters as we need
Conor, You have said this many times elsewhere, but unfortunatelly, I
heard it for the first time =) so please correct me if I'm wrong.
I thought generalizing lookup is good example for usage of the
MonadPlus as I read in RWH[1], but you said it's not necesarry.
Now, I understood there are two positions for such classes. One is
using generalizing for it, another is not.
So, I want to know that when such classes should be used from later position.
Heinrich suggested that is for overloading. But do any other usages are exist?
[1]: http://book.realworldhaskell.org/read/programming-with-monads.html#VCard.hs:...
Cheers
-nwn
On Tue, Sep 15, 2009 at 5:21 PM, Conor McBride
Hi
This topic comes up a lot, and this is what I usually say when it does. It's a thing I learned from James McKinna, many years ago...
Might I gently suggest that there is a much better, more natural way to abstract over every type-former which has some sort of return/pure-like thing and some sort of mzero/empty like thing? You could use the type-former which is inductively defined to be the least such thing, and as such has a canonical mapping to all the others, namely Maybe.
It's not necessarily a good idea to fix on Monad or MonadPlus as there are other choices. For example,
On 15 Sep 2009, at 07:14, Yusaku Hashimoto wrote:
I prefer Alternative to MonadPlus for explaining failure. It has better name and operator for failure and try-another.
import Control.Applicative
aLookup :: (Alternative f, Eq k) => k -> [(k,v)] -> f v aLookup key pairs = maybe empty pure $ lookup key pairs
there are notorious non-monadic instances for the above f (some formulations of parsing, in particular). So,
I understand that fail being in Monad is controversial, but my version of the function works in *all* monads.
this is a touch presumptuous. On the one hand, Brent is right when he says
It doesn't work in *all* monads -- it only works in monads which support a sensible notion of failure.
but he's perhaps excessive when he says
This is exactly what is captured by the MonadPlus constraint on my version of mLookup.
because it's not exact: it requires mplus as well as a sensible notion of failure. And yes, why should we insist on (>>=) when we just need a return and an mzero? Incidentally, I don't know where the MonadPlus instance
(IO, Maybe, [], ...) are already instances of MonadPlus.
of IO is coming from, but I want it caught and locked up now (in STM, for example) before it does any permanent damage.
Why not factor out the failure-prone operations from the business of interpreting failure in some failure-supporting context? Work concretely while you can (types stay shorter, error messages make more sense) then apply adapters
malt :: Alternative f => Maybe x -> f x malt = maybe empty pure
mop :: MonadPlus m => Maybe x -> m x mop = maybe mzero return
when you need to? This also reduces the risk of connecting an ambiguous supplier to an ambiguous consumer, (show . read) style.
The message clearly bears repeating. Inductive definition is a concrete form of abstraction. Don't be fooled by its appearance: Maybe is the most abstract choice here -- the classier options demand more structure than is needed and thus exclude use-cases.
I'll crawl back under my stone now.
All the best
Conor
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Yusaku Hashimoto wrote:
If I understood your post correctly, you said
- generalizing lookup to MonadPlus or Alternative or such classes are not necessary
In particular, it doesn't become more general, it becomes less general (in a sense).
- use Maybe as usual, we should use adapters as we need
Conor, You have said this many times elsewhere, but unfortunately, I heard it for the first time =) so please correct me if I'm wrong.
I thought generalizing lookup is good example for usage of the MonadPlus as I read in RWH[1], but you said it's not necessary.
Now, I understood there are two positions for such classes. One is using generalizing for it, another is not.
So, I want to know that when such classes should be used from later position.
Heinrich suggested that is for overloading.
To elaborate on generality versus overloading: the function lookupM :: MonadPlus m => k -> Map k a -> m a is not more general than lookup :: k -> Map k a -> Maybe a because you can implement the former with the latter lookupM k = mop . lookup k mop = maybe mzero return In other words, lookupM doesn't introduce new functionality. Rather, it gives you the syntactic convenience of not having to mention mop by overloading the result type. In other words, you can write lookup = lookupM or lookupE :: k -> Map k a -> Either e a lookupE = lookupM
But do any other usages are exist?
I'm not quite sure I understand what you mean here? Regards, apfelmus -- http://apfelmus.nfshost.com

On Fri, Sep 18, 2009 at 6:05 PM, Heinrich Apfelmus
Yusaku Hashimoto wrote:
- use Maybe as usual, we should use adapters as we need
Conor, You have said this many times elsewhere, but unfortunately, I heard it for the first time =) so please correct me if I'm wrong.
I thought generalizing lookup is good example for usage of the MonadPlus as I read in RWH[1], but you said it's not necessary.
Now, I understood there are two positions for such classes. One is using generalizing for it, another is not.
So, I want to know that when such classes should be used from later position.
Heinrich suggested that is for overloading.
To elaborate on generality versus overloading: the function
lookupM :: MonadPlus m => k -> Map k a -> m a
is not more general than
lookup :: k -> Map k a -> Maybe a
because you can implement the former with the latter
lookupM k = mop . lookup k
mop = maybe mzero return
In other words, lookupM doesn't introduce new functionality.
Rather, it gives you the syntactic convenience of not having to mention mop by overloading the result type. In other words, you can write
lookup = lookupM
or
lookupE :: k -> Map k a -> Either e a lookupE = lookupM
I got it. Thank you for explanation.
But do any other usages are exist?
I'm not quite sure I understand what you mean here?
I had misread the Conor's post like the raison d'etre of type classes was denied, so I asked how type class should be used. Thanks again. Cheers -nwn

On Tue, Sep 15, 2009 at 6:21 AM, Brandon S. Allbery KF8NH < allbery@ece.cmu.edu> wrote:
On Sep 14, 2009, at 14:42 , Michael Snoyman wrote:
I understand that fail being in Monad is controversial, but my version of the function works in *all* monads. This is very
Not really; "fail" in non-MonadPlus-es is a rather poorly defined notion, and there are no guarantees that the result will be at all sane. "mzero" is well defined.
mzero also does not allow giving error messages. There are times when you want to be able to fail with an explanation of why. fail seems to fit the bill properly for this (fail taking a String argument and all...). Now you point out that fail is not always properly defined. I quite agree with that. Nonetheless, in the simple cases I am trying to address here, it is IMO the best option available. If you end up using the function only with monads that properly define fail, then all the better. Michael

On Tue, Sep 15, 2009 at 8:56 AM, Michael Snoyman
On Tue, Sep 15, 2009 at 6:21 AM, Brandon S. Allbery KF8NH
wrote: On Sep 14, 2009, at 14:42 , Michael Snoyman wrote:
I understand that fail being in Monad is controversial, but my version of the function works in *all* monads. This is very
Not really; "fail" in non-MonadPlus-es is a rather poorly defined notion, and there are no guarantees that the result will be at all sane. "mzero" is well defined.
mzero also does not allow giving error messages. There are times when you want to be able to fail with an explanation of why. fail seems to fit the bill properly for this (fail taking a String argument and all...).
In general, I think this is a bad idea. Except for short, throwaway code, Strings should not be used to encode errors simply because if your error message is a String, client code basically has no choice but to show it to the user and probably exit: since it's quite hard for the code to parse the String back in to find out what the error message was, it's hard for client code to recover from the error. If you have multiple types of errors from a single function, it's better to define your own error type with constructors representing different types of errors so client code can figure out what went wrong. (And in many cases, I have found that if a function can fail in multiple ways, I am trying to do too much in one function. There are, of course, numerous exceptions.) Alex
participants (8)
-
Alexander Dunlap
-
Brandon S. Allbery KF8NH
-
Brent Yorgey
-
Conor McBride
-
Heinrich Apfelmus
-
Michael Mossey
-
Michael Snoyman
-
Yusaku Hashimoto