All these philosophical arguments calling for "consistency" with the container APIs or that function need words for the human mind to comprehend seem short-sighted to me. If we were consistent about the proposal itself we'd also demand to add

  cons = (:)

  empty = []

  toList = id

  fromList = id

to the List module. For consistency's sake!

This reminds me of the famous quote

"A foolish consistency is the hobgoblin of little minds, adored by little statesmen and philosophers and divines."

In any case I'm -1 on adding singleton or any other consistency-feel-good names to Data.List





Am So., 18. Aug. 2019 um 15:47 Uhr schrieb Alexandre Esteves <alexandre.fmp.esteves@gmail.com>:
If the choice is between adding List.singleton or not, I vote for adding it.
The robot-ninja-monkey-gorilla-whathaveyou operator always causes me to do a double take, and I'm actually displeased with there being special syntax for `List` alone - I don't see any special syntax for `Set/Map`, or `Either`, which is even more fundamental, and on pair with tuples. 

But I'd actually prefer a singleton method. It seems a frequent point of debate is single-element-intent vs polymorphic-ness. I'd like to note that they're not mutually exclusive (whether we end up with best of both worlds or worst is up for discussion). 
When I think of a container of x, I think of some data structure with x values inside. Now, they need to be stored/organized/structured *somehow*, and there's a distinction here:
- some containers require each element to be paired with it's index/key/location (e.g. Map, HashMap, (->))
- some containers build the entire structure based on a single value/dictionary which can be known ahead of time, before any values are provided (e.g. Set uses Ord, HashSet uses Hashable, List trivially uses the empty constraint ())

For the second case, we can conceive of a fromList function (left and right inverse of toList), which then gives us singleton = fromList . (:[])
Something like:

-- contrast with https://hackage.haskell.org/package/semigroupoids-5.3.2/docs/Data-Semigroup-Foldable.html#t:Foldable1
class Unfoldable1 c a where
  fromNonEmpty :: NonEmpty a -> c a

  singleton :: a -> c a
  singleton = fromNonEmptyList . (:|[]) -- moustached gorilla operator

-- constrast with Foldable
class Unfoldable1 c a => Unfoldable c a where
  fromList :: [a] -> c a

  unfoldr :: (b -> Maybe (a, b)) -> b -> c a
  unfoldr f = fromList . Data.List.unfoldr f

instance Unfoldable1 [] a where
  fromNonEmpty = toList
instance Unfoldable  [] a where
  fromList = id

instance Unfoldable1 NonEmpty a where
  fromNonEmpty = id

instance Ord a => Unfoldable1 Set a where
  fromNonEmpty = fromList . toList
instance Ord a => Unfoldable Set a where
  fromList = Set.fromList

instance (Eq a, Hashable a) => Unfoldable1 HashSet a where
  fromNonEmpty = fromList . toList
instance (Eq a, Hashable a) => Unfoldable HashSet a where
  fromList = HashSet.fromList


On Sun, Aug 18, 2019 at 3:58 PM Henrik Nilsson <Henrik.Nilsson@nottingham.ac.uk> wrote:
Hi,

On 08/13/2019 11:56 PM, Herbert Valerio Riedel wrote:
> But we already have at least two monomorphic variants to express this
> with Haskell's concise native syntax and vocabulary which has by
> design a preferential treatment of lists (it was considered even more
> important than type-sigs so that we got the `:` cons operator for
> lists and the `::` for type-sig annotations) -- so let's not try to
> fight Haskell's core idioms by hiding them behind some trivial
> additional redundant synonyms! I still fail to see the actual
> *technical*  problem being solved by the original proposal asking to
> add yet another, wordy way to construct single-item-lists.

To me, the main argument for "singleton" is that of consistency with
other container types. But, on balance, I do agree with Herbert
and others: operator sections is a core Haskell idiom, and (:[]) is an
age-old and obvious instance: even beginner Haskell programmers will be
very familiar with (:) for list construction, and along with the basic
arithmetic operators, it is definitely one of the operators most
familiar to Haskell programmers.

So -1 from me.

/Henrik




This message and any attachment are intended solely for the addressee
and may contain confidential information. If you have received this
message in error, please contact the sender and delete the email and
attachment.

Any views or opinions expressed by the author of this email do not
necessarily reflect the views of the University of Nottingham. Email
communications with the University of Nottingham may be monitored
where permitted by law.




_______________________________________________
Libraries mailing list
Libraries@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________
Libraries mailing list
Libraries@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries