Why Either = Left | Right instead of something like Result = Success | Failure

Hi, I was just wondering if there's any particular reason for which the two constructors of the Either data type are named Left and Right. I'm thinking that something like Success | Failure or Right | Wrong would have been a little better. I've recently seen that Scala uses a similar convention for some error notifications so I'm starting to believe there's more background behind it than just an unfortunate naming. Thanks, -- Ionuț G. Stan | http://igstan.ro

2010/5/27 Ionut G. Stan
Hi,
I was just wondering if there's any particular reason for which the two constructors of the Either data type are named Left and Right. I'm thinking that something like Success | Failure or Right | Wrong would have been a little better.
I've recently seen that Scala uses a similar convention for some error notifications so I'm starting to believe there's more background behind it than just an unfortunate naming.
Hi, Either *can* be used to represent success and failures, but not necessarily. It is a convention, when using Either to model success/failure, to use Right for success and Left for failure. Even if Left as a word does not match with the meaning of failure, it is easy to get it Right :) Cheers, Thu

On May 27, 2010, at 10:53 , Vo Minh Thu wrote:
2010/5/27 Ionut G. Stan
: I was just wondering if there's any particular reason for which the two constructors of the Either data type are named Left and Right. I'm thinking that something like Success | Failure or Right | Wrong would have been a little better.
I've recently seen that Scala uses a similar convention for some error notifications so I'm starting to believe there's more background behind it than just an unfortunate naming.
Either *can* be used to represent success and failures, but not necessarily. It is a convention, when using Either to model success/failure, to use Right for success and Left for failure. Even if Left as a word does not match with the meaning of failure, it is easy to get it Right :)
Historically it *has* been related to negativity in many cultures. (Consider "sinister", cognate of Italian "sinistro/a", and the prevalence of and preference for right-handed-ness.) -- 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 27 May 2010, at 15:25, Ionut G. Stan wrote:
Hi,
I was just wondering if there's any particular reason for which the two constructors of the Either data type are named Left and Right. I'm thinking that something like Success | Failure or Right | Wrong would have been a little better.
The reason I guess is that Success/Failure and Right/Wrong are a lot less general than Left/Right. One can use Either for types with two possible valid types contained within, it doesn't only have to be used for types where one is for "correct" results and the other for "erroneous". Of course, there's nothing stopping you implementing your own type :) Bob

It's indeed arbitrary. Other common names are Inl and Inr (presumably
standing for "inject left/right"). Some Haskell project do indeed use
a more specific name. The advantage of using the generic Left/Right
is reusability of library code. The particular name of the datatype
and its constructors are competely arbitrary. The use of "Right" for
"Success" is a handy pun -- the program returned "the right answer".
HTH,
/ Thomas
On 27 May 2010 15:25, Ionut G. Stan
Hi,
I was just wondering if there's any particular reason for which the two constructors of the Either data type are named Left and Right. I'm thinking that something like Success | Failure or Right | Wrong would have been a little better.
I've recently seen that Scala uses a similar convention for some error notifications so I'm starting to believe there's more background behind it than just an unfortunate naming.
Thanks, -- Ionuț G. Stan | http://igstan.ro _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Push the envelope. Watch it bend.

On Thu, May 27, 2010 at 10:25 AM, Ionut G. Stan
I was just wondering if there's any particular reason for which the two constructors of the Either data type are named Left and Right. I'm thinking that something like Success | Failure or Right | Wrong would have been a little better.
Because that would confuse matters when using the type for something other than representing success or failure. Either is a generic sum type. That is, "Either A B" only means "either you have an A, or you have a B". Use of Left to represent failure is merely a matter of convention. Similarly, the generic product type in Haskell is the 2-tuple--"(A, B)" only means "you have both an A and a B". Left and Right work well because they don't carry much extra semantic baggage, and they make it easy to remember which type parameter goes with which constructor. Other than the mnemonic value, something even more bland like This and That would work as well. Personally, I advocate instead using "Sinister" and "Dexter". Nice and catchy, don't you think? - C.

Left-Right also good for representing binary trees.
2010/5/27 C. McCann
I was just wondering if there's any particular reason for which the two constructors of the Either data type are named Left and Right. I'm
On Thu, May 27, 2010 at 10:25 AM, Ionut G. Stan
wrote: thinking that something like Success | Failure or Right | Wrong would have been a little better.
Because that would confuse matters when using the type for something other than representing success or failure.
Either is a generic sum type. That is, "Either A B" only means "either you have an A, or you have a B". Use of Left to represent failure is merely a matter of convention. Similarly, the generic product type in Haskell is the 2-tuple--"(A, B)" only means "you have both an A and a B".
Left and Right work well because they don't carry much extra semantic baggage, and they make it easy to remember which type parameter goes with which constructor. Other than the mnemonic value, something even more bland like This and That would work as well.
Personally, I advocate instead using "Sinister" and "Dexter". Nice and catchy, don't you think?
- C. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

begin C. McCann quotation:
Personally, I advocate instead using "Sinister" and "Dexter". Nice and catchy, don't you think?
Has anyone done a "translation" of the Prelude into Latin?
modulus PraeLudus ubi
data Uter a b = Sinister a | Dexter b derivare (Aequo, Ordinaro, Lego, Monstro)
Ha. -md

Monstro I'm going to call it that from now on. Stay out of the IO Monstro.
-deech
On 5/27/10, Mike Dillon
begin C. McCann quotation:
Personally, I advocate instead using "Sinister" and "Dexter". Nice and catchy, don't you think?
Has anyone done a "translation" of the Prelude into Latin?
modulus PraeLudus ubi
data Uter a b = Sinister a | Dexter b derivare (Aequo, Ordinaro, Lego, Monstro)
Ha.
-md _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Thu, May 27, 2010 at 3:17 PM, Mike Dillon
begin C. McCann quotation:
Personally, I advocate instead using "Sinister" and "Dexter". Nice and catchy, don't you think?
Has anyone done a "translation" of the Prelude into Latin?
modulus PraeLudus ubi
data Uter a b = Sinister a | Dexter b derivare (Aequo, Ordinaro, Lego, Monstro)
Ha.
Not Haskell, but check this one out: http://search.cpan.org/~dconway/Lingua-Romana-Perligata-0.50/lib/Lingua/Roma... Patrick
-md _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- ===================== Patrick LeBoutillier Rosemère, Québec, Canada

Thank you all for the answers. It seems that a recurring reason is that being defined as a general type, Either can be used not only to handle errors, but choice in general. This, however, seems to make Either to overloaded in my opinion. If I decide that I want to use Either as a way to signal error, but a third party accepts Either for something different, then things will probably not work. I have little experience with Haskell, but I haven't seen Either used in contexts other than error/success. If you could point me to some piece of code that uses it in a different way it would be great. I'll probably use something different as an internal representation of failure in my programs, and only keep Either for the public API. Just my thoughts for the moment... On 5/27/10 6:26 PM, C. McCann wrote:
On Thu, May 27, 2010 at 10:25 AM, Ionut G. Stan
wrote: I was just wondering if there's any particular reason for which the two constructors of the Either data type are named Left and Right. I'm thinking that something like Success | Failure or Right | Wrong would have been a little better.
Because that would confuse matters when using the type for something other than representing success or failure.
Either is a generic sum type. That is, "Either A B" only means "either you have an A, or you have a B". Use of Left to represent failure is merely a matter of convention. Similarly, the generic product type in Haskell is the 2-tuple--"(A, B)" only means "you have both an A and a B".
Left and Right work well because they don't carry much extra semantic baggage, and they make it easy to remember which type parameter goes with which constructor. Other than the mnemonic value, something even more bland like This and That would work as well.
Personally, I advocate instead using "Sinister" and "Dexter". Nice and catchy, don't you think?
- C.
-- Ionuț G. Stan | http://igstan.ro

"Ionut G. Stan"
Thank you all for the answers. It seems that a recurring reason is that being defined as a general type, Either can be used not only to handle errors, but choice in general. This, however, seems to make Either to overloaded in my opinion. If I decide that I want to use Either as a way to signal error, but a third party accepts Either for something different, then things will probably not work.
You could then categorise a lot of types as being overloaded; for example Maybe is used to indicate success/failure, a list with no more than one value, etc.
I have little experience with Haskell, but I haven't seen Either used in contexts other than error/success. If you could point me to some piece of code that uses it in a different way it would be great.
I've used it with partitionEithers to map a function that categorises a list of values into two types (typically program arguments) and then split them up.
I'll probably use something different as an internal representation of failure in my programs, and only keep Either for the public API. Just my thoughts for the moment...
Unless you have a _very_ good reason to do this, I wouldn't for the sole reason that its yet another thing someone has to comprehend if they want to read your code. Whilst the Either type isn't officially used for errors, that is how it is usually treated in Haskell with the consensus that Left = failure and Right = success (note that due to how its defined it also has to be this way for Either's Monad instance to work). -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

Ionut G. Stan wrote:
Thank you all for the answers. It seems that a recurring reason is that being defined as a general type, Either can be used not only to handle errors, but choice in general. This, however, seems to make Either to overloaded in my opinion. If I decide that I want to use Either as a way to signal error, but a third party accepts Either for something different, then things will probably not work.
It's unlikely that the types would be compatible, unless you're using a type like Either String String. In that case, the solution may not be to switch to something other than Either, but rather to make the type more precise, like Either MyError MyValue, which can't be confused with other uses of Either. Keep in mind that a major point of the polymorphic type system in a language like Haskell is to be able to write typed code once and reuse it as widely as possible, so you should expect something as basic as choice between two alternatives to be represented by a very general type. A big advantage of using Either in a case like this is that any code written to operate on a general enough version of that type, such as "Either a b", may work just fine on your particular use of Either. That includes code which implements error monads, like these: http://hackage.haskell.org/packages/archive/transformers/0.2.1.0/doc/html/Co... http://hackage.haskell.org/packages/archive/mtl/1.1.0.2/doc/html/Control-Mon... or e.g. the Either utilities in MissingH: http://hackage.haskell.org/packages/archive/MissingH/1.1.0.3/doc/html/Data-E... By using Either, you're using the natural Haskell type for representing choice between two alternatives, that allows you to benefit from much of the code that's been written to use that type.
I have little experience with Haskell, but I haven't seen Either used in contexts other than error/success. If you could point me to some piece of code that uses it in a different way it would be great.
Choice between two alternatives is a pretty common requirement - think of it as the datatype equivalent of an 'if' expression. As a result, it's used quite a lot. There's an example in the main GHC driver program, http://darcs.haskell.org/ghc/ghc/Main.hs : type Mode = Either PreStartupMode PostStartupMode type PostStartupMode = Either PreLoadMode PostLoadMode Notice that it's not possible to confuse those types with something else. Further, using an alias defined with 'type', as in the above example allows you to name your type something relevant to your program, without losing the benefits of using a general type like Either. Anton

Quoth Ivan Lazar Miljenovic
Whilst the Either type isn't officially used for errors, that is how it is usually treated in Haskell with the consensus that Left = failure and Right = success (note that due to how its defined it also has to be this way for Either's Monad instance to work).
I'm glad you mentioned that, I was going to mention how natural it would seem for Either to be an instance of Monad, given that it is used as you say by consensus for errors ... but something seems to be wrong with my libraries: No instance for (Monad (Either [Char])) arising from a use of `return' at except.hs:25:24-29 Possible fix: add an instance declaration for (Monad (Either [Char])) So, I understand how to make a Monad instance, and I guess your point stands (as demonstrated by the expected type of (Either String)), but it's funny that Either is understood to have a Monad instance even though that's only implied, and not supplied. I think though that you can't have it both ways - Either Left "Either is universally understood to be for success/failure-with-error" or Right "Either does not imply any meaning, it represents any A/B option pair" We're really stuck with the latter - that's why, as explained early in this thread, the names are essentially value free (it's Left/Right, not Wrong/Right.) Since Either doesn't imply meaning, its use with errors presents an ambiguity that has to be resolved by the reader - something I have to comprehend if I read your code, and it might indeed be easier to read code that uses a type that, though unique to the code, has names that reflect its meaning. Donn Cave, donn@avvanta.com

2010/5/28 Donn Cave
Quoth Ivan Lazar Miljenovic
, Whilst the Either type isn't officially used for errors, that is how it is usually treated in Haskell with the consensus that Left = failure and Right = success (note that due to how its defined it also has to be this way for Either's Monad instance to work).
I'm glad you mentioned that, I was going to mention how natural it would seem for Either to be an instance of Monad, given that it is used as you say by consensus for errors ... but something seems to be wrong with my libraries:
No instance for (Monad (Either [Char])) arising from a use of `return' at except.hs:25:24-29 Possible fix: add an instance declaration for (Monad (Either [Char]))
So, I understand how to make a Monad instance, and I guess your point stands (as demonstrated by the expected type of (Either String)), but it's funny that Either is understood to have a Monad instance even though that's only implied, and not supplied.
[snip]
Hi, Control.Monad.Error provides an instance for Either. Cheers, Thu

Quoth Vo Minh Thu
Control.Monad.Error provides an instance for Either.
... in the mtl transformer library, in case anyone else besides myself didn't know that. And I see it has to be there because it depends on the Error typeclass. (So the documentation for Control.Monad.Error, is mistaken, where at the top it says Example type: Either String a ... which should be Either Error a ... ? Though I can't really be sure what the documentation is trying to say.) Donn Cave, donn@avvanta.com

On Friday 28 May 2010 20:44:20, Donn Cave wrote:
Quoth Vo Minh Thu
, ... Control.Monad.Error provides an instance for Either.
... in the mtl transformer library, in case anyone else besides myself didn't know that. And I see it has to be there because it depends on the Error typeclass.
Which is considered a wart by some. (Either left) has a perfectly valid Monad instance for any type left (the only slightly difficult thing might be 'fail').
(So the documentation for Control.Monad.Error, is mistaken, where at the top it says
Example type: Either String a
... which should be
Either Error a
... ?
No, String is an instance of Error, so (Either String) is fine.
Though I can't really be sure what the documentation is trying to say.)
In that case, have a look at the code, perhaps that is clearer. (And bug the maintainer(s) to improve the docs.)
Donn Cave, donn@avvanta.com

Daniel Fischer
On Friday 28 May 2010 20:44:20, Donn Cave wrote:
Quoth Vo Minh Thu
, ... Control.Monad.Error provides an instance for Either.
... in the mtl transformer library, in case anyone else besides myself didn't know that. And I see it has to be there because it depends on the Error typeclass.
Which is considered a wart by some. (Either left) has a perfectly valid Monad instance for any type left (the only slightly difficult thing might be 'fail').
Though how would you set the Left value for some arbitrary type?
Though I can't really be sure what the documentation is trying to say.)
In that case, have a look at the code, perhaps that is clearer. (And bug the maintainer(s) to improve the docs.)
IIRC, the basic point is that the Left type has to be one which can be converted from some arbitrary String value, to take into account the fail method for that type: fail :: (Monad m) => String -> m a -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On Saturday 29 May 2010 01:28:59, Ivan Lazar Miljenovic wrote:
Daniel Fischer
writes: On Friday 28 May 2010 20:44:20, Donn Cave wrote:
Quoth Vo Minh Thu
, ... Control.Monad.Error provides an instance for Either.
... in the mtl transformer library, in case anyone else besides myself didn't know that. And I see it has to be there because it depends on the Error typeclass.
Which is considered a wart by some. (Either left) has a perfectly valid Monad instance for any type left (the only slightly difficult thing might be 'fail').
Though how would you set the Left value for some arbitrary type?
That is the difficult thing. If you want to have instance Monad (Either e) where ... , there are only two possibilities for fail that I see, fail msg = error msg -- or error somethingElse fail msg = Left undefined -- or Left (error msg) Neither is entirely convincing, but the second is a little more robust (though you can't inspect failures without catching exceptions). Constructing more meaningful Left values is then a little dangerous (if you try to inspect them) or pointless (if not). But if you want to have instance Monad (Either ConcreteType) where ... , you can have fail msg = Left someDefaultValue (or let the value depend on the message) and you can construct Left someMeaningfulValue in concrete situations. Of course, you can then also write instance Error ConcreteType where noMsg = someDefaultValue strMsg msg = whatever which really is no more fuss, so the 'bad' thing about it is just that if you want a Monad instance for (Either ConcreteType), you have to - import Control.Monad.Error(.Class) and make ConcreteType an instance of Error, or - make sure it's never used in the same module as C.M.E, or - enable OverlappingInstances when they're used together. Need I explain why I prefer the first?
Though I can't really be sure what the documentation is trying to say.)
In that case, have a look at the code, perhaps that is clearer. (And bug the maintainer(s) to improve the docs.)
IIRC, the basic point is that the Left type has to be one which can be converted from some arbitrary String value, to take into account the fail method for that type:
fail :: (Monad m) => String -> m a
Yep.

Daniel Fischer
But if you want to have
instance Monad (Either ConcreteType) where ...
, you can have
fail msg = Left someDefaultValue
(or let the value depend on the message) and you can construct Left someMeaningfulValue in concrete situations.
Which happens to make it identical to Maybe ;-) -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On Saturday 29 May 2010 02:26:38, Ivan Lazar Miljenovic wrote:
Daniel Fischer
writes: But if you want to have
instance Monad (Either ConcreteType) where ...
, you can have
fail msg = Left someDefaultValue
(or let the value depend on the message) and you can construct Left someMeaningfulValue in concrete situations.
Which happens to make it identical to Maybe ;-)
If you use only the default value. But if you use more, making your type an instance of Error would be the sensible thing (unless you're one of the mtl-haters, but probably transformers has a similar instance).

Vo Minh Thu wrote:
Control.Monad.Error provides an instance for Either.
Donn Cave wrote:
... in the mtl transformer library, in case anyone else besides myself didn't know that. And I see it has to be there because it depends on the Error typeclass.
Daniel Fischer
Which is considered a wart by some. (Either left) has a perfectly valid Monad instance for any type left
Indeed, and it is one of the most useful Monads there is. The Either monad provides short-circuiting logic, so that you can exit an arbitrary number of levels of nested calculation. The type Either a b returns a if the calculation exits, or b if it completes without exiting. Exiting on an error condition is one tiny corner case of multi-level exit, so it is a shame that the mtl library defines an orphan instance. By doing that, it hijacks the Either monad and monopolizes it for its own specialized purpose. This is the classic example why defining orphan instances is so dangerous. Now, instead of the natural use of Either for short-circuiting logic, we are forced to find other solutions, such as: o use the MonadPlus instance of Maybe and write everything "additively", using mplus and return instead of (>>=) and Left. That is equivalent to the Either monad, but in practice it ends up looking a lot messier and harder to read. o use a CPS-based monad, like Cont or LogicT. I find those highly obfuscated, and a huge amount of complexity overkill for most tasks. o use a clone of Either, like the Exit monad. That is currently the best workaround, in my opinion. http://www.haskell.org/haskellwiki/New_monads/MonadExit Regards, Yitz

I have little experience with Haskell, but I haven't seen Either used in contexts other than error/success. If you could point me to some piece of code that uses it in a different way it would be great.
One example use case is datatype-generic programming.
{-# LANGUAGE TypeFamilies #-}
Suppose I have a type class that gives me a unique representation for a type. The functions 'from' and 'to' allow me to convert from a value of that type to a value in its representation. An instance of 'Representable' should encode an isomorphism between some type 'a' and its representation type 'Rep a'. An isomorphism means that we can translate between 'a' and 'Rep a' without losing important information such as the structure of the value.
class Representable a where type Rep a from :: a -> Rep a to :: Rep a -> a
I can establish some types from the Haskell Prelude as representations for other types. Here, I use the "unit" type (), 'Either' as is the topic of the current thread, and the pair type (,).
instance Representable () where type Rep () = () from = id to = id instance (Representable a, Representable b) => Representable (Either a b) where type Rep (Either a b) = Either a b from = id to = id instance (Representable a, Representable b) => Representable (a, b) where type Rep (a, b) = (a, b) from = id to = id
The reason that I pick (), 'Either', and (,) is that we can represent many typical Haskell user-defined datatypes with these so-called basic types. A simple example is 'Bool'. In this case, the representation type for 'Bool' is 'Either () ()' since 'Bool' can be either 'True' or 'False'. The constructors of 'Bool' take no arguments, so we can use () to fill in the arguments for the 'Left' and 'Right' constructors of 'Either'.
instance Representable Bool where type Rep Bool = Either () () from x = case x of False -> Left () True -> Right () to x = case x of Left () -> False Right () -> True
Here is a more interesting example with constructors that take zero, two, and three arguments.
data MyType a b = Zero | Two a a | Three a b a
In order to represent 'MyType', we use nesting of 'Either' and pairs. This allows us to utilize the basic types defined above to represent more complicated types.
instance Representable (MyType a b) where type Rep (MyType a b) = Either () (Either (a, a) (a, (b, a))) from x = case x of Zero -> Left () Two a1 a2 -> Right (Left (a1, a2)) Three a1 b1 a2 -> Right (Right (a1, (b1, a2))) to x = case x of Left () -> Zero Right (Left (a1, a2)) -> Two a1 a2 Right (Right (a1, (b1, a2))) -> Three a1 b1 a2
Now, what's the real point of all this? Well, if we can define functions over the basic types (unit, 'Either', and pair), we can easily extend those functions to other types that can be represented by the basic types. Some canonical examples are equality and ordering. There already exist instances for the basic types, so defining instances for 'MyType' is trivial. We simply convert each 'MyType' value into its representation as defined above. The functions then act on the representation value.
instance (Eq a, Eq b) => Eq (MyType a b) where x == y = from x == from y
instance (Ord a, Ord b) => Ord (MyType a b) where compare x y = compare (from x) (from y)
You might say that we already have "deriving (Eq, Ord)," and that's true. But the implementation of deriving is specified by the Language Report and built into each compiler. If you come up with a new generic function, you won't have deriving for that. It's also (currently) much easier to write the above than to build a new deriving implementation for a compiler. There are many examples of generic functions and uses of datatype-generic concepts in Haskell. Just search Hackage for "generics." Regards, Sean

* Ionut G. Stan wrote:
I was just wondering if there's any particular reason for which the two constructors of the Either data type are named Left and Right.
Yes. The basic function on this type is "either". either a b (Left x) = Left (a x) either a b (Right x) = Right (b x) So the names of the constuctors are "natural".
participants (18)
-
Aaron Denney
-
aditya siram
-
Alberto G. Corona
-
Anton van Straaten
-
Brandon S. Allbery KF8NH
-
C. McCann
-
Daniel Fischer
-
Donn Cave
-
Ionut G. Stan
-
Ivan Lazar Miljenovic
-
Lutz Donnerhacke
-
Mike Dillon
-
Patrick LeBoutillier
-
Sean Leather
-
Thomas Davie
-
Thomas Schilling
-
Vo Minh Thu
-
Yitzchak Gale