"Elvis" operator (?:) as a reverse infix form of "fromMaybe"

I suggest to include this operator in "Data.Maybe" and "Prelude". *Implementation:* (?:) :: Maybe a -> a -> a maybeA ?: b = fromMaybe b maybeA *Use cases:* 1. maybeValue ?: error "Value is unexpectedly empty. This is a bug." instead of fromMaybe (error "Value is unexpectedly empty. This is a bug.") maybeValue 2. maybeA ?: maybeB ?: c instead of fromMaybe (fromMaybe c maybeB) maybeA *Name collisions:* Hayoo search gives only 6 collisions with 5 hardly fundamental libraries. * The nickname and the operator itself are inspired by the ones from Groovy language. ** The symbols of the operator are a reminder of plain old ternary construct. *** To understand the nickname look at the operator as on emoticon.

I've never considered writing fromMaybe painful, personally.
On 12 October 2013 14:40, Nikita Volkov
I suggest to include this operator in "Data.Maybe" and "Prelude".
Implementation:
(?:) :: Maybe a -> a -> a maybeA ?: b = fromMaybe b maybeA
Use cases:
1. maybeValue ?: error "Value is unexpectedly empty. This is a bug."
instead of
fromMaybe (error "Value is unexpectedly empty. This is a bug.") maybeValue
2. maybeA ?: maybeB ?: c
instead of
fromMaybe (fromMaybe c maybeB) maybeA
Name collisions:
Hayoo search gives only 6 collisions with 5 hardly fundamental libraries.
* The nickname and the operator itself are inspired by the ones from Groovy language.
** The symbols of the operator are a reminder of plain old ternary construct.
*** To understand the nickname look at the operator as on emoticon.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

I agree, it seems a bit wasteful of operator names to start aliasing things
that are already in idiomatic use.
As more get added to Base there are less to play with when you want to
design a nice EDSL.
On 12 October 2013 13:48, Christopher Done
I've never considered writing fromMaybe painful, personally.

On Oct 12, 2013, at 2:47 PM, Stephen Tetley
wrote: I agree, it seems a bit wasteful of operator names to start aliasing things that are already in idiomatic use.
As more get added to Base there are less to play with when you want to design a nice EDSL.
+1 to stemming the operator tide; -1 to Elvis. The claim such operators make on the space of available identifiers has to be justified. Prelude gives us 'maybe', and that meets most of my needs by itself. Anthony
On 12 October 2013 13:48, Christopher Done
wrote: I've never considered writing fromMaybe painful, personally.
Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

I'd prefer it if we had an operator in Control.Applicative such as
|> :: Alternative f => f a -> a -> f a
l |> r = l <|> pure r
if it doesn't already exist, this would generalize fromMaybe, and
complicated cases could be written as
maybeA <|> maybeB |> c
but even this could be easily written using <|> and pure, so I'm not sure
it pulls its weight.
John L.
On Sat, Oct 12, 2013 at 7:40 AM, Nikita Volkov
I suggest to include this operator in "Data.Maybe" and "Prelude".
*Implementation:*
(?:) :: Maybe a -> a -> a maybeA ?: b = fromMaybe b maybeA
*Use cases:*
1. maybeValue ?: error "Value is unexpectedly empty. This is a bug."
instead of
fromMaybe (error "Value is unexpectedly empty. This is a bug.") maybeValue
2. maybeA ?: maybeB ?: c
instead of
fromMaybe (fromMaybe c maybeB) maybeA
*Name collisions:*
Hayoo search gives only 6 collisions with 5 hardly fundamental libraries.
* The nickname and the operator itself are inspired by the ones from Groovy language.
** The symbols of the operator are a reminder of plain old ternary construct.
*** To understand the nickname look at the operator as on emoticon.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

John Lato, you're offering a completely different thing and I would totally
vote against it. Please don't flood.
2013/10/12 John Lato
I'd prefer it if we had an operator in Control.Applicative such as
|> :: Alternative f => f a -> a -> f a l |> r = l <|> pure r
if it doesn't already exist, this would generalize fromMaybe, and complicated cases could be written as
maybeA <|> maybeB |> c
but even this could be easily written using <|> and pure, so I'm not sure it pulls its weight.
John L.
On Sat, Oct 12, 2013 at 7:40 AM, Nikita Volkov
wrote: I suggest to include this operator in "Data.Maybe" and "Prelude".
*Implementation:*
(?:) :: Maybe a -> a -> a maybeA ?: b = fromMaybe b maybeA
*Use cases:*
1. maybeValue ?: error "Value is unexpectedly empty. This is a bug."
instead of
fromMaybe (error "Value is unexpectedly empty. This is a bug.") maybeValue
2. maybeA ?: maybeB ?: c
instead of
fromMaybe (fromMaybe c maybeB) maybeA
*Name collisions:*
Hayoo search gives only 6 collisions with 5 hardly fundamental libraries.
* The nickname and the operator itself are inspired by the ones from Groovy language.
** The symbols of the operator are a reminder of plain old ternary construct.
*** To understand the nickname look at the operator as on emoticon.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

It's not a completely different thing, it's the very same thing, but more
general.
-- Dan Burton
On Sat, Oct 12, 2013 at 12:41 PM, Nikita Volkov
John Lato, you're offering a completely different thing and I would totally vote against it. Please don't flood.
2013/10/12 John Lato
I'd prefer it if we had an operator in Control.Applicative such as
|> :: Alternative f => f a -> a -> f a l |> r = l <|> pure r
if it doesn't already exist, this would generalize fromMaybe, and complicated cases could be written as
maybeA <|> maybeB |> c
but even this could be easily written using <|> and pure, so I'm not sure it pulls its weight.
John L.
On Sat, Oct 12, 2013 at 7:40 AM, Nikita Volkov
wrote:
I suggest to include this operator in "Data.Maybe" and "Prelude".
*Implementation:*
(?:) :: Maybe a -> a -> a maybeA ?: b = fromMaybe b maybeA
*Use cases:*
1. maybeValue ?: error "Value is unexpectedly empty. This is a bug."
instead of
fromMaybe (error "Value is unexpectedly empty. This is a bug.") maybeValue
2. maybeA ?: maybeB ?: c
instead of
fromMaybe (fromMaybe c maybeB) maybeA
*Name collisions:*
Hayoo search gives only 6 collisions with 5 hardly fundamental libraries.
* The nickname and the operator itself are inspired by the ones from Groovy language.
** The symbols of the operator are a reminder of plain old ternary construct.
*** To understand the nickname look at the operator as on emoticon.
_______________________________________________ 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

Dan Burton, `maybeA <|> maybeB |> c` has type `Maybe a`, while `maybeA ?:
maybeB ?: c` has type `a`. The sole purpose of `?:` is in extracting a
value from `Maybe`, not lifting to it.
2013/10/12 Dan Burton
It's not a completely different thing, it's the very same thing, but more general.
-- Dan Burton
On Sat, Oct 12, 2013 at 12:41 PM, Nikita Volkov
wrote:
John Lato, you're offering a completely different thing and I would totally vote against it. Please don't flood.
2013/10/12 John Lato
I'd prefer it if we had an operator in Control.Applicative such as
|> :: Alternative f => f a -> a -> f a l |> r = l <|> pure r
if it doesn't already exist, this would generalize fromMaybe, and complicated cases could be written as
maybeA <|> maybeB |> c
but even this could be easily written using <|> and pure, so I'm not sure it pulls its weight.
John L.
On Sat, Oct 12, 2013 at 7:40 AM, Nikita Volkov < nikita.y.volkov@gmail.com> wrote:
I suggest to include this operator in "Data.Maybe" and "Prelude".
*Implementation:*
(?:) :: Maybe a -> a -> a maybeA ?: b = fromMaybe b maybeA
*Use cases:*
1. maybeValue ?: error "Value is unexpectedly empty. This is a bug."
instead of
fromMaybe (error "Value is unexpectedly empty. This is a bug.") maybeValue
2. maybeA ?: maybeB ?: c
instead of
fromMaybe (fromMaybe c maybeB) maybeA
*Name collisions:*
Hayoo search gives only 6 collisions with 5 hardly fundamental libraries.
* The nickname and the operator itself are inspired by the ones from Groovy language.
** The symbols of the operator are a reminder of plain old ternary construct.
*** To understand the nickname look at the operator as on emoticon.
_______________________________________________ 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

Oh, you're right, my mistake.
-- Dan Burton
On Sat, Oct 12, 2013 at 12:53 PM, Nikita Volkov
Dan Burton, `maybeA <|> maybeB |> c` has type `Maybe a`, while `maybeA ?: maybeB ?: c` has type `a`. The sole purpose of `?:` is in extracting a value from `Maybe`, not lifting to it.
2013/10/12 Dan Burton
It's not a completely different thing, it's the very same thing, but more general.
-- Dan Burton
On Sat, Oct 12, 2013 at 12:41 PM, Nikita Volkov < nikita.y.volkov@gmail.com> wrote:
John Lato, you're offering a completely different thing and I would totally vote against it. Please don't flood.
2013/10/12 John Lato
I'd prefer it if we had an operator in Control.Applicative such as
|> :: Alternative f => f a -> a -> f a l |> r = l <|> pure r
if it doesn't already exist, this would generalize fromMaybe, and complicated cases could be written as
maybeA <|> maybeB |> c
but even this could be easily written using <|> and pure, so I'm not sure it pulls its weight.
John L.
On Sat, Oct 12, 2013 at 7:40 AM, Nikita Volkov < nikita.y.volkov@gmail.com> wrote:
I suggest to include this operator in "Data.Maybe" and "Prelude".
*Implementation:*
(?:) :: Maybe a -> a -> a maybeA ?: b = fromMaybe b maybeA
*Use cases:*
1. maybeValue ?: error "Value is unexpectedly empty. This is a bug."
instead of
fromMaybe (error "Value is unexpectedly empty. This is a bug.") maybeValue
2. maybeA ?: maybeB ?: c
instead of
fromMaybe (fromMaybe c maybeB) maybeA
*Name collisions:*
Hayoo search gives only 6 collisions with 5 hardly fundamental libraries.
* The nickname and the operator itself are inspired by the ones from Groovy language.
** The symbols of the operator are a reminder of plain old ternary construct.
*** To understand the nickname look at the operator as on emoticon.
_______________________________________________ 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

Yes, I understand |> :: Alternative f => f a -> a -> a as what you are asking for, for an Alternative that can default to something. Back to your suggestion, I personally find a written-out `fromMaybe` nicer syntax, especially because it fits well into the naming of the other `from...` functions, and the fact that the value comes from a maybe suggests to me that I have to give a defaul there.

This type is what I would like (and is the proper generalization of the
proposed function), but I don't know if it's feasible. It might fit into
Alternative, but it may need a separate class. I don't see how it could be
written as a standalone function without extra support. So I suggested a
"next best thing. "
As to flooding, I thought this was germane to the proposal, and I do
apologize if others disagree. I just don't think ?. is useful or general
enough to deserve a place in base.
On Oct 12, 2013 4:20 PM, "Niklas Hambüchen"
Yes, I understand
|> :: Alternative f => f a -> a -> a
as what you are asking for, for an Alternative that can default to something.
Back to your suggestion, I personally find a written-out `fromMaybe` nicer syntax, especially because it fits well into the naming of the other `from...` functions, and the fact that the value comes from a maybe suggests to me that I have to give a defaul there. _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

I'm pretty strongly -1 on this proposal.
Operator names are fairly precious, and nothing about this operator name
really screams "Maybe".
Seen in code without prior knowledge `fromMaybe` can have its meaning
intuited. (?:) on the other hand comes across as gratuitous.
-Edward
On Sat, Oct 12, 2013 at 8:40 AM, Nikita Volkov
I suggest to include this operator in "Data.Maybe" and "Prelude".
*Implementation:*
(?:) :: Maybe a -> a -> a maybeA ?: b = fromMaybe b maybeA
*Use cases:*
1. maybeValue ?: error "Value is unexpectedly empty. This is a bug."
instead of
fromMaybe (error "Value is unexpectedly empty. This is a bug.") maybeValue
2. maybeA ?: maybeB ?: c
instead of
fromMaybe (fromMaybe c maybeB) maybeA
*Name collisions:*
Hayoo search gives only 6 collisions with 5 hardly fundamental libraries.
* The nickname and the operator itself are inspired by the ones from Groovy language.
** The symbols of the operator are a reminder of plain old ternary construct.
*** To understand the nickname look at the operator as on emoticon.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Sun, Oct 13, 2013 at 12:30 AM, Edward Kmett
Seen in code without prior knowledge `fromMaybe` can have its meaning intuited. (?:) on the other hand comes across as gratuitous.
Worse, if you're at all familiar with C or languages which borrowed its ternary operator, your expectation is that it will be related to Bool, not Maybe a. (And no, I wouldn't recommend it for that either; the next question is figuring out how the then and else legs are distinguished... and I don't consider the ternary operator particularly readable anyway.) -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
participants (9)
-
Anthony Cowley
-
Brandon Allbery
-
Christopher Done
-
Dan Burton
-
Edward Kmett
-
John Lato
-
Nikita Volkov
-
Niklas Hambüchen
-
Stephen Tetley