Proposal: Add singleton function to Data.List module

Kris Nuttycombe kris.nuttycombe at gmail.com
Wed Aug 21 16:00:37 UTC 2019


Since this has remained contentious, I'd like to contribute my +1 to the
argument, and to express my support for the points that Nathan and Matt
have raised. To this point in the discussion, however, I have not seen
raised the perspective that I hold, and so I'm going to add another color
to the bikeshed.

My point of view here is informed by my efforts to teach my children to
program, using Haskell.

In every case where we define a typeclass instance, we write the
implementation of that instance as a number of monomorphic functions. My
position is that these monomorphic functions should always be exported
directly, perhaps from an `.Internal` module.

My preferred way of writing typeclass instances is just this: I create two
modules, `Foo.Bar` and `Foo.Bar.Internal`. `Foo.Bar` is used only to
selectively reexport from `Foo.Bar.Internal`, which is where the relevant
types and typeclass instances are defined. For each typeclass method to be
implemented, I define a top-level monomorphic function, and this function
is used in the implementation of the instance; in this case, it would look
like:

module Data.List.Internal where
  ...

  singleton :: x -> [x]
  singleton x = [x]

instance Applicative [] where
  pure = singleton
  ...

When followed consistently, this gives the end user the greatest
flexibility in choosing whether to use the monomorphic version (in a
context where they want the compiler to alert them if the type changes) or
the polymorphic one. I dearly wish, for example, that this approach were
followed in `Data.Time.Clock`, for example, where a good deal of the
important functionality is awkwardly hidden in `Num` and `Integral`
instances (which, as an aside, are highly inappropriate).

In conclusion, I think that the proposal for Data.List.singleton is a good
one - I just wish that it went a great deal further.

Kris

On Wed, Aug 21, 2019 at 6:32 AM Taylor Fausak <taylor at fausak.me> wrote:

> Thanks for saying that, Nathan! I agree wholeheartedly.
>
> To George and the CLC: I'm disappointed to hear that I inadvertently
> suggested something that would require changing the Haskell Language
> Report. It is my understanding that work on the report has more or less
> stalled [1], and I would hate for this simple addition to be caught in that
> quagmire.
>
> Your mention of the report encouraged me to look for differences between
> the current Data.List module and the one specified in the report [2]. Aside
> from the obvious Foldable/Traversable changes brought by the FTP proposal,
> it didn't take long to find a difference: the uncons function [3]. I found
> its source in GHC.List [4], which pointed me to a Trac issue [5], a mailing
> list thread [6], and a Phabricator differential [7].
>
> I bring this up not because I expect the process to be exactly the same
> today as it was five years ago, but because the simple addition of the
> uncons function was accepted without nearly as much discussion. Also it was
> notably accepted without any mention of the report at all. Has something
> changed in the meantime, or did I suggest something that hit a nerve with
> the community?
>
> Regardless, I'm happy to hear that the CLC is considering my proposal
> among themselves. Is there an expected timeline? (I'm looking for a rough
> order of magnitude, not an exact date.) Thanks!
>
> 1: https://github.com/haskell/rfcs/issues/15
> 2:
> https://www.haskell.org/onlinereport/haskell2010/haskellch20.html#x28-22800020
> 3:
> https://hackage.haskell.org/package/base-4.12.0.0/docs/Data-List.html#v:uncons
> 4:
> https://gitlab.haskell.org/ghc/ghc/blob/83ca42de519cdfa28b38164e90d726034dba768e/libraries/base/GHC/List.hs#L65-72
> 5: https://gitlab.haskell.org/ghc/ghc/issues/9550
> 6: https://mail.haskell.org/pipermail/libraries/2014-July/023314.html
> 7: https://phabricator.haskell.org/D195
>
> On Wed, Aug 21, 2019, at 6:22 AM, Nathan Bouscal wrote:
>
> Hi all,
>
> I would strongly encourage anyone inclined to say things like “there's no benefit
> in having the function” to consider reframing the sentiment as “I wouldn’t
> benefit from having the function, and don’t understand the benefit others
> will gain.” Once you’ve done that reframe, you can notice that there’s a
> lack of understanding toward which the appropriate emotional stance is
> curiosity, not dismissiveness. A lot of people have clearly expressed in
> this thread that they would benefit from this function, and when you assert
> as fact that such benefit does not exist, you’re implicitly dismissing and
> devaluing their experience.
>
> Independent of any technical merits or readability concerns per se, there
> is a signaling aspect to this discussion. Already this thread has been
> referenced many times on social media, and it’s sending a very loud signal:
> “we don’t want you here”. Not because of the content of the discussion, but
> because of its tone. I happen to think that Haskell is a fantastic language
> for beginners, and I’ve been watching in real time as potential learners
> are deciding it isn’t for them. I’ve also been seeing experienced
> Haskellers deciding it’s not worth it to participate in the libraries
> process. You can argue as much as you want that people are wrong to get
> that signal from this thread, that they’re misinterpreting the comments
> here, etc, but none of that changes the outcome. We can do better than this.
>
>
> On the proposal itself: I’ve been writing Haskell for several years now
> and have founded a company that uses Haskell in production, so I’d like to
> think I’m at least a step or two beyond “beginner”, and yet I cannot recall
> the last time I saw (:[]) in my code or anyone else’s, and seeing it here
> caused me to double-take and take a moment to mentally parse it. If that’s
> the case for me, I’m sure it must be far worse for an actual beginner.
> Building things by composing primitives is good, but if anyone put this
> operator into my codebase I’d likely flag it in code review. Readability
> isn’t about whether it’s possible to read something, it’s about how easy it
> is to read, and for me this operator doesn’t pass that test. Personally I
> tend to use pure, but a monomorphic option would be better. I would happily
> change to using singleton if it becomes available, and am a +1 on the
> proposal for both List and NonEmpty.
>
>
> Nathan
>
>
> On Wed, Aug 21, 2019 at 6:32 AM George Wilson <george at wils.online> wrote:
>
> Hi Taylor,
>
> I'm on the Core Libraries Committee. Thank you for your proposal.
> Regarding the +-1 messages in this thread, they are useful to gauge
> community opinion, but they are not votes because the libraries
> process is not determined by a vote.
>
> Despite seeming innocuous, the proposed change requires careful
> consideration: Data.List is specified by the Haskell Report, so adding
> this function would affect the report.
> While simple changes to base are typically handled directly by one of
> base's maintainers, this change is report-affecting, so it is
> "controversial" (as defined in [1]). Hence the CLC is discussing the
> proposed change amongst ourselves before a maintainer makes their
> decision.
>
> [1] https://wiki.haskell.org/Library_submissions
>
> Cheers,
> George
>
>
>
>
>
> On Tue, 20 Aug 2019 at 11:24, Taylor Fausak <taylor at fausak.me> wrote:
> >
> > It has been a week since I submitted my proposal. During that time, 28
> people voted, with 16 expressing approval and 12 expressing disapproval. To
> everyone that voted so far: Thank you! You made for interesting discussion.
> >
> > I still feel that Haskell would be improved by the addition of a
> `singleton` function to the `Data.List` module. (And also
> `Data.List.NonEmpty`, even though that wasn't part of my original
> proposal.) I would be happy to open a merge request adding code, tests, and
> documentation.
> >
> > I haven't done so yet because I don't know what the next steps are. Can
> someone from the CLC tell me how an official approval or rejection can be
> reached, and how long that might take? Thanks!
> >
> > On Mon, Aug 19, 2019, at 6:39 AM, Helmut Schmidt wrote:
> >
> >
> > Andreas, you seem to be mistaken there'd only be one container API? But
> there's several container APIs besides "Data.Set" which provide some
> collection of elements!
> >
> >
> https://hackage.haskell.org/package/dlist-0.8.0.7/docs/Data-DList.html#v:cons
> >
> >
> https://hackage.haskell.org/package/dlist-0.8.0.7/docs/Data-DList.html#v:append
> >
> >
> >
> >
> >
> https://hackage.haskell.org/package/text-1.2.4.0/docs/Data-Text.html#v:cons
> >
> >
> https://hackage.haskell.org/package/text-1.2.4.0/docs/Data-Text.html#v:append
> >
> >
> http://hackage.haskell.org/package/vector-0.12.0.3/docs/Data-Vector.html#v:cons
> >
> >
> https://hackage.haskell.org/package/bytestring-0.10.10.0/docs/Data-ByteString.html#v:cons
> >
> >
> https://hackage.haskell.org/package/bytestring-0.10.10.0/docs/Data-ByteString.html#v:append
> >
> > Am Mo., 19. Aug. 2019 um 08:16 Uhr schrieb Andreas Abel <
> andreas.abel at ifi.lmu.de>:
> >
> > Helmut, do you actually know the container APIs?
> >
> > Show me cons and append in Data.Set!
> >
> > On 2019-08-18 19:40, Helmut Schmidt wrote:
> > >
> > >
> > > Am So., 18. Aug. 2019 um 17:17 Uhr schrieb Oliver Charles
> > > <ollie at ocharles.org.uk <mailto:ollie at ocharles.org.uk>>:
> > >
> > >     On Sun, 18 Aug 2019, 5:47 pm Helmut Schmidt,
> > >     <helmut.schmidt.4711 at gmail.com
> > >     <mailto:helmut.schmidt.4711 at gmail.com>> wrote:
> > >
> > >
> > >         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
> > >
> > >
> > >     I honestly have no problem with any of these.
> > >
> > >
> > > I forgot
> > >
> > >      append = (++)
> > >
> > > We also need to address another elephant in the room... those pesky
> > > tuples and their special privileged non-wordy syntax!
> > >
> > >     pair = (,)
> > >
> > >     triple = (,,)
> > >
> > >     quadruple = (,,,)
> > >
> > >     quituple = (,,,,)
> > >
> > >     sextuple = (,,,,,)
> > >
> > >     septuble = (,,,,,,)
> > >
> > >     octuple = (,,,,,,,)
> > >
> > > If Haskell were invented in this century's EU Haskell source code would
> > > be littered with €s instead of $s but then again I wonder why £ wasn't
> > > picked. But I digress. We can kill two birds with one stone here:
> > >
> > >     apply = ($)
> > >
> > >     strictApply = ($!)
> > >
> > >     compose = (.)
> > >
> > >
> > > It's fun to imagine how code using those definitions would like! But
> > > it's still a -1 for me, sorry!
> > >
> > >
> > >
> > >
> > > _______________________________________________
> > > Libraries mailing list
> > > Libraries at haskell.org
> > > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
> > >
> >
> > _______________________________________________
> > Libraries mailing list
> > Libraries at haskell.org
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
> >
> >
> > _______________________________________________
> > Libraries mailing list
> > Libraries at haskell.org
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>
>
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20190821/98c41d2d/attachment.html>


More information about the Libraries mailing list