Why does Haskell have both `Maybe a` and `Either a ()`?

Greetings, everyone! Recently I was involved in a discussion on the new ML-style language 'gleam'. Gleam has for quite a while now only had an `Either a b` type, with all functions that in Haskell one would use a `Maybe a` for, working on an `Either a ()` instead. In the discussion(https://github.com/gleam-lang/gleam/issues/591), the language designers were asking the community whether it would make sense to add `Maybe` to the language as well, or keep using only `Either a ()`. My question: Is the difference between `Maybe a` and `Either a ()` only semantic and are they functionally equivalent, or are there differences in functionality as well? Have a nice day, ~Marten / Qqwy

On Friday, May 29, 2020 12:24 PM, Wiebe-Marten Wijnja
Greetings, everyone!
Recently I was involved in a discussion on the new ML-style language 'gleam'.
Gleam has for quite a while now only had an `Either a b` type, with all functions that in Haskell one would use a `Maybe a` for, working on an `Either a ()` instead.
In the discussion(https://github.com/gleam-lang/gleam/issues/591), the language designers were asking the community whether it would make sense to add `Maybe` to the language as well, or keep using only `Either a ()`.
My question: Is the difference between `Maybe a` and `Either a ()` only semantic and are they functionally equivalent, or are there differences in functionality as well?
One can define instance Functor Maybe, and instance Functor (Either ()), but not something like instance Functor (\a -> Either a ()). Therefore, Either () a would be more like Maybe a than Either a (), in Haskell/GHC. kind regards, Arjen

One difference between Maybe a and Either a () in Haskell is also that `Nothing < Just a` for any a. But `Right () > Left a` for any a. On 5/29/20 12:24 PM, Wiebe-Marten Wijnja wrote:
Greetings, everyone!
Recently I was involved in a discussion on the new ML-style language 'gleam'.
Gleam has for quite a while now only had an `Either a b` type, with all functions that in Haskell one would use a `Maybe a` for, working on an `Either a ()` instead.
In the discussion(https://github.com/gleam-lang/gleam/issues/591), the language designers were asking the community whether it would make sense to add `Maybe` to the language as well, or keep using only `Either a ()`.
My question: Is the difference between `Maybe a` and `Either a ()` only semantic and are they functionally equivalent, or are there differences in functionality as well?
Have a nice day,
~Marten / Qqwy
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

On Fri, 29 May 2020, Wiebe-Marten Wijnja wrote:
Greetings, everyone!
Recently I was involved in a discussion on the new ML-style language 'gleam'.
Gleam has for quite a while now only had an `Either a b` type, with all functions that in Haskell one would use a `Maybe a` for, working on an `Either a ()` instead.
In Haskell `Maybe a` is more similar to `Either () a` than `Either a ()`. Either has one more redirection on the Left case. You can have both `Left undefined` and `Left ()` whereas Maybe can only have `Nothing`. I hardly think that people actually make use of this difference, though. Btw. from a software engineering point I'd prefer not to use Either for both exception handling with an according Monad and for cases where you just want to handle values of two possible types. I'd define an Except type for the exception usage. Could we remove Maybe in favor of Either? It would make some instances non-Haskell-98. E.g. instance C Maybe where is Haskell 98, but instance C (Either ()) where needs FlexibleInstances and instance (a ~ ()) => C (Either a) where needs TypeFamilies. Unless you find out that you can define a more general instance like instance (Super a) => C (Either a) where .

"Nothing" uses the same memory slot no matter how many times it's used, but "Left ()" will more than likely create a new object every time, or at the very least one for each module where it's used. Eq and Ord instances get slightly slower because they have to compare () with () every time they receive a pair of Lefts. Where you would pass "x" into the "maybe" deconstructor function, now you would have to pass "const x" to "either", which again uses more memory and (more importantly) more cognitive space. We have the problem other people have mentioned where FlexibleInstances or TypeFamilies/GADTs have to be used to define instances for Either (). However, the biggest problem is that Maybe is not actually isomorphic to Either () in a lazy language like Haskell. Maybe has * Nothing * Just x However, Either () has * Left () * Right x * Left undefined And that final value causes infinite problems, particularly when you pass it to other functions which handle strictness on the Left argument differently. Is the Eq () instance strict or lazy in its arguments? I honestly would not be able to tell you without firing up an instance of GHCi. I've seen different libraries which define singleton objects define it in different ways. On Fri, May 29, 2020, 05:40 Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Fri, 29 May 2020, Wiebe-Marten Wijnja wrote:
Greetings, everyone!
Recently I was involved in a discussion on the new ML-style language 'gleam'.
Gleam has for quite a while now only had an `Either a b` type, with all functions that in Haskell one would use a `Maybe a` for, working on an `Either a ()` instead.
In Haskell `Maybe a` is more similar to `Either () a` than `Either a ()`.
Either has one more redirection on the Left case. You can have both `Left undefined` and `Left ()` whereas Maybe can only have `Nothing`. I hardly think that people actually make use of this difference, though.
Btw. from a software engineering point I'd prefer not to use Either for both exception handling with an according Monad and for cases where you just want to handle values of two possible types. I'd define an Except type for the exception usage.
Could we remove Maybe in favor of Either? It would make some instances non-Haskell-98. E.g.
instance C Maybe where
is Haskell 98, but
instance C (Either ()) where
needs FlexibleInstances and
instance (a ~ ()) => C (Either a) where
needs TypeFamilies.
Unless you find out that you can define a more general instance like
instance (Super a) => C (Either a) where
. _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Wiebe-Marten Wijnja writes:
My question: Is the difference between `Maybe a` and `Either a ()` only semantic and are they functionally equivalent, or are there differences in functionality as well?
One difference that comes to mind is that there is only one way to write the failing case for `Maybe a` (namely `Nothing`), but two ways for `Either a ()`: `Right ()` and `Right ⊥`. -- Albert Krewinkel GPG: 8eed e3e2 e8c5 6f18 81fe e836 388d c0b2 1f63 1124

Am 29.05.20 um 12:24 schrieb Wiebe-Marten Wijnja:
Recently I was involved in a discussion on the new ML-style language 'gleam'.
Gleam has for quite a while now only had an `Either a b` type, with all functions that in Haskell one would use a `Maybe a` for, working on an `Either a ()` instead.
In the discussion(https://github.com/gleam-lang/gleam/issues/591), the language designers were asking the community whether it would make sense to add `Maybe` to the language as well, or keep using only `Either a ()`.
A separate data type makes the intention clearer and (as others have stated) is a bit more memory efficient (in Haskell, but I think in an ML-like language, too). The disadvantage is that you cannot easily re-use existing functionality. So there is a danger that implementations of functions on Maybe deviate from those for Either () for no good reason.
My question: Is the difference between `Maybe a` and `Either a ()` only semantic and are they functionally equivalent,
I'd say any semantic difference (apart from laziness) between (Maybe a) and (Either () a) is more accidental than expressly desired.
or are there differences in functionality as well?
There seem to be some, as was previously observed (e.g. the Ord instance). Whether this was intended is questionable. The mentioned differences regarding () vs. bottom are, I think, not of particular interest to you: if gleam is ML-style then it probably is a strict language, and thus Maybe and Either () would be fully equivalent as data types. Cheers Ben

There is a subtle difference between Haskell Either and Gleam Result.
Haskell:
data Either a b = Left a | Right b ...
Gleam:
pub type Result(a, e) {
Ok(a)
Error(e)
}
The computer doesn't care, but it's important for human thinking:
** Nothing is *not* an Error.
Suppose for example I have a function
next_smaller_prime :: Int -> Maybe Int
where next_smaller_prime 10 -> Just 7
and next_smaller_prime 2 -> Nothing
The second case is not an error. You get the answer Nothing
because the function *worked*, not because it didn't.
To return Error Nil is to commit the YouTube (social) offence:
"You are an evil-doer who has done something wrong.
I refuse to tell you WHAT you did wrong,
so you can't fix it, you wrong-thinking PEASANT."
Seriously, if you have decided to return Error(x),
x had BETTER be a 'reason' (as Erlang calls it) for WHY it is
an error. The pattern in Erlang is, after all,
{ok,Result} | {error,Reason}.
sans_reason (Left _) = Nothing
sans_reason (Right x) = Just x
with_reason (Nothing) s = Left s
with_reason (Just x) _ = Right x
are trivial conversion functions. As I said, the computer does not care.
There are (at least) three different situations we can consider.
(1) Sometimes there is no answer. Typically a search.
In this case, Maybe is appropriate.
(2) Sometimes you asked a question which fails to have an answer
for a reason.
In this case, Either is appropriate.
(3) Sometimes you asked a sensible question for which the system
might have been expected to produce an answer, but something
went wrong. Numeric overflow, database connection shut down
unexpectedly, hard drive developed a bad block.
In this case, an exception is appropriate.
And of course there are other reasons to use Either. Think of
divide-and-conquer: classify :: Problem -> Either SubProblems EasyProblem.
Because Gleam's Result isn't Haskell's Either in terms of connotations for
human beings, even if they are basically the same to a computer.
On Fri, 29 May 2020 at 22:26, Wiebe-Marten Wijnja
Greetings, everyone!
Recently I was involved in a discussion on the new ML-style language 'gleam'.
Gleam has for quite a while now only had an `Either a b` type, with all functions that in Haskell one would use a `Maybe a` for, working on an `Either a ()` instead.
In the discussion(https://github.com/gleam-lang/gleam/issues/591), the language designers were asking the community whether it would make sense to add `Maybe` to the language as well, or keep using only `Either a ()`.
My question: Is the difference between `Maybe a` and `Either a ()` only semantic and are they functionally equivalent, or are there differences in functionality as well?
Have a nice day,
~Marten / Qqwy
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
participants (8)
-
Albert Krewinkel
-
Ben Franksen
-
Henning Thielemann
-
Jaro Reinders
-
leesteken@pm.me
-
Richard O'Keefe
-
Wiebe-Marten Wijnja
-
Zemyla