[ghc-steering-committee] A plea for ForeignFunctionInterface
Tom Harding
i.am.tom.harding at gmail.com
Fri Dec 18 13:26:03 UTC 2020
I’ll happily change my vote to a ‘yes’ - I must’ve missed that it’s already implied while I was going through the list in the user manual. If it’s already on, I don’t see harm in leaving it that way.
Thanks,
Tom
> On 18 Dec 2020, at 08:59, Simon Peyton Jones via ghc-steering-committee <ghc-steering-committee at haskell.org> wrote:
>
> | In my experience, FFI is the kind of extension that you want to
> | isolate to a single module, and like Cale (or Iavor with the fancier
> | type system extensions) I like the indicator at the top of the file
> | that this module will be dealing with FFI concerns. In that sense, FFI
> | feels a lot like MagicHash to me, a very important and useful
> | extension, but one that you don't want (or at least don't *need*)
> | enabled everywhere. So it's interesting to me that while FFI has
> | 8 votes now, MagicHash (and UnboxedTuples and UnboxedSums) only has a
> | single vote.
>
> I have sympathy with this. If it wasn't "in" already I'd say leave it out now.
> But maybe we should not be so influenced by what it in now?
>
> I'm totally on the fence here.
>
> Simon
>
>
> |
> | I don't see excluding FFI from GHC2021 as an argument that it should
> | be avoided or deprecated, just that it's not a part of the every day
> | Haskell toolkit. I think it deserves to continue to be part of the
> | Haskell standard, but is also niche enough to warrant selective
> | enablement where it's needed. In other words, I think it would be
> | perfectly fine if the Haskell standard mandated FFI as an extension
> | that could be enabled on demand (in fact this is how I thought it
> | worked when I first learned that FFI was included in Haskell2010).
> |
> | That all said, there's clearly nothing wrong with enabling it
> | universally, it's been the default for a while and hasn't caused any
> | problems I'm aware of. So if Simon M and others feel strongly about
> | including FFI, I don't want to stand in the way. But I am curious why
> | we shouldn't include the other parts of the low-level Haskell toolkit
> | as well.
> |
> | Eric
> |
> | > On Dec 17, 2020, at 11:47, Cale Gibbard <cgibbard at gmail.com> wrote:
> | >
> | > My impression of the GHC2021 thing was that it's an arbitrary
> | > collection of extensions that would make for a sensible default,
> | > rather than something that was in any way tied to a standardisation
> | > process.
> | >
> | > ForeignFunctionInterface is obviously not going anywhere, but also,
> | > its use is generally confined to particular modules, where the {-#
> | > Language ForeignFunctionInterface #-} pragma at the top would be
> | good
> | > documentation for what sort of module we're about to see. I was also
> | > slightly concerned that switching that on may have an impact on
> | > overall compiler performance, seeing as it may need to interact with
> | > the driver in more ways than most extensions, but I don't really
> | know
> | > and haven't yet done any testing.
> | >
> | > I also had no idea it was turned on by default in Haskell2010,
> | though
> | > I'm not sure it matters all that much what was turned on in
> | > Haskell2010 for these purposes either?
> | >
> | > That said, I could go either way on this one.
> | >
> | > If we're going to turn FFI on, why not throw in all the other
> | > extensions to FFI? Given that they introduce their own bits of
> | syntax,
> | > so could hardly affect anything by accident, I think it would be
> | > appropriate.
> | >
> | >
> | >
> | > On Thu, 17 Dec 2020 at 11:40, Simon Marlow <marlowsd at gmail.com>
> | wrote:
> | >>
> | >> Dear Committee
> | >>
> | >> We're in danger of actually *removing* an extension from the
> | default set of extensions that is enabled in GHC, which is not what I
> | understood GHC2021 was all about. And it's not because anyone (at
> | least as far as I know) actually thinks that ForeignFunctionInterface
> | is a bad idea and should be deprecated or replaced. What other reasons
> | could there be for turning off an extension that has been on by
> | default for so many years?
> | >>
> | >> ForeignFunctionInterface is part of Haskell2010. Are we saying we
> | disagree with the decision to make it a part of the language standard?
> | I hope not!
> | >>
> | >> Please let's think very hard before doing this!
> | >>
> | >> Cheers
> | >> Simon
> | >>
> | >> On Mon, 14 Dec 2020 at 22:22, Joachim Breitner <mail at joachim-
> | breitner.de> wrote:
> | >>>
> | >>> Dear Committe,
> | >>>
> | >>> three weeks in, we have all votes. So now things are looking more
> | concrete.
> | >>>
> | >>> As always, the table
> | >>>
> | https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgi
> | >>> thub.com%2Fghc-proposals%2Fghc-
> | proposals%2Fblob%2Fghc2021%2Fproposal
> | >>> s%2F0000-
> | ghc2021.rst%23data&data=04%7C01%7Csimonpj%40microsoft.c
> | >>>
> | om%7C886f711c1ffc4fb881da08d8a3070f8d%7C72f988bf86f141af91ab2d7cd011
> | >>>
> | db47%7C1%7C0%7C637438598033649008%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC
> | >>>
> | 4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000&
> | >>>
> | sdata=NhvlIwuLVahY2XRkBXrPp08jGad5V%2B3dyUxxRfScuVI%3D&reserved=
> | >>> 0
> | >>> has the current data.
> | >>>
> | >>> Would it be helpful to add columns to that table for each
> | committee
> | >>> member? So that you can quickly see who voted what?
> | >>>
> | >>> The following in are safely in (= need more than one vote to
> | change to get out):
> | >>>
> | >>> BangPatterns, BinaryLiterals, ConstrainedClassMethods,
> | >>> ConstraintKinds, DeriveDataTypeable, DeriveFoldable,
> | DeriveFunctor,
> | >>> DeriveGeneric, DeriveLift, DeriveTraversable, EmptyCase,
> | >>> EmptyDataDecls, EmptyDataDeriving, ExplicitForAll,
> | FlexibleContexts,
> | >>> FlexibleInstances, GADTSyntax, GeneralisedNewtypeDeriving,
> | >>> HexFloatLiterals, ImportQualifiedPost, InstanceSigs,
> | KindSignatures,
> | >>> MultiParamTypeClasses, NamedFieldPuns, NumericUnderscores,
> | >>> PolyKinds, PostfixOperators, RankNTypes, StandaloneDeriving,
> | >>> StarIsType, TypeApplications, TypeSynonymInstances
> | >>>
> | >>> The following are barely in (exactly 8 votes in favor, and 3
> | against):
> | >>>
> | >>> ExistentialQuantification, NamedWildCards,
> | StandaloneKindSignatures,
> | >>> TypeOperators
> | >>>
> | >>> The following are short one vote (7 in favor, 4 against):
> | >>>
> | >>> DerivingStrategies, ForeignFunctionInterface, GADTs,
> | MonoLocalBinds,
> | >>> NegativeLiterals, RecordWildCards, ScopedTypeVariables,
> | >>> TupleSections, TypeFamilies
> | >>>
> | >>>
> | >>> I am sure we can have plenty of discussion for each of these.
> | >>> Probably without end. As Simon says, mailing lists don't scale. So
> | I
> | >>> think we have two choices:
> | >>>
> | >>> 1. Let the numbers decide, and accept whatever comes out.
> | According
> | >>> to the process (which we should only follow if we find it helpful)
> | >>> we'd maybe update our votes, and maybe point out new facets, for
> | one
> | >>> week, and then just take whatever has 8 votes.
> | >>>
> | >>> or
> | >>>
> | >>> 2. Explore a more efficient discussion format.
> | >>>
> | >>> For the latter I mentioned kialo.com before, and maybe it is worth
> | a
> | >>> try, so I set up a discussion there:
> | >>>
> | https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fww
> | >>> w.kialo.com%2Fwhich-haskell-extensions-should-go-into-ghc2021-
> | 43548%
> | >>>
> | 3Fpath%3D43548.0&data=04%7C01%7Csimonpj%40microsoft.com%7C886f71
> | >>>
> | 1c1ffc4fb881da08d8a3070f8d%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C
> | >>>
> | 0%7C637438598033659005%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiL
> | >>>
> | CJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000&sdata=EBMu9
> | >>> n%2BX917NG5L7k7tJMDDnxlclzO0LNAvimEettq4%3D&reserved=0
> | >>>
> | >>> So what do you see there?
> | >>>
> | >>> There is a discussion tree:
> | >>>
> | >>> The root is "what goes in GHC2021"
> | >>>
> | >>> The next layer are all extensions with 7 or 8 votes.
> | >>> (I assume we should focus on those initially, but feel free to add
> | >>> more or ask me to.) For example: TupleSections
> | >>>
> | >>> And then each of these has a column where we can collect Pros and
> | cons.
> | >>> For example:
> | >>> Pro: Opt-in Syntax
> | >>> Con: Possible clash with extra-comma syntax extensions.
> | >>>
> | >>> So you can treat it like a wiki, but with structure to organize
> | the
> | >>> discussion.
> | >>>
> | >>> In fact, each pro and con is itself a node where you can add
> | >>> supporting and disagreeing comments. This means that if you
> | >>> _disagree_ that TupleSections are actually Opt-in syntax, there is
> | a
> | >>> dedicated place to raise that point, rather than putting "Not
> | >>> actually opt-in" in the Con column of TupleSections...
> | >>>
> | >>> A good way to navigate the discussion seems to be the radial icon
> | in
> | >>> the top left; it opens a radial view of the whole discussion, and
> | >>> you can read arguments by hovering.
> | >>>
> | >>>
> | >>> The site doesn't offer voting, it is only about structuring the
> | >>> discussion, and it is designed for much larger and much more
> | >>> contentious debates (e.g. "Brexit"). So we'll see how well it
> | works
> | >>> for us and if it's helpful.
> | >>>
> | >>> Cheers,
> | >>> Joachim
> | >>>
> | >>>
> | >>> --
> | >>> Joachim Breitner
> | >>> mail at joachim-breitner.de
> | >>>
> | >>>
> | https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fwww
> | >>> .joachim-
> | breitner.de%2F&data=04%7C01%7Csimonpj%40microsoft.com%7
> | >>>
> | C886f711c1ffc4fb881da08d8a3070f8d%7C72f988bf86f141af91ab2d7cd011db47
> | >>>
> | %7C1%7C0%7C637438598033659005%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLj
> | >>>
> | AwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000&sdat
> | >>> a=5FRqUoTh1wBOS8Hrj6L5CK9uTtsXCDc2U4zVMKQ2UpY%3D&reserved=0
> | >>>
> | >>>
> | >>> _______________________________________________
> | >>> ghc-steering-committee mailing list
> | >>> ghc-steering-committee at haskell.org
> | >>>
> | https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fma
> | >>> il.haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-steering-
> | committ
> | >>>
> | ee&data=04%7C01%7Csimonpj%40microsoft.com%7C886f711c1ffc4fb881da
> | >>>
> | 08d8a3070f8d%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C6374385980
> | >>>
> | 33659005%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzI
> | >>>
> | iLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000&sdata=O%2FGAauT8sznxenlzP
> | >>> 7KMC661xIvVCip588OGEEUj0zI%3D&reserved=0
> | >>
> | >> _______________________________________________
> | >> ghc-steering-committee mailing list
> | >> ghc-steering-committee at haskell.org
> | >>
> | https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fmai
> | >> l.haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-steering-
> | committee
> | >>
> | &data=04%7C01%7Csimonpj%40microsoft.com%7C886f711c1ffc4fb881da08d
> | >>
> | 8a3070f8d%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C63743859803365
> | >>
> | 9005%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJB
> | >>
> | TiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000&sdata=O%2FGAauT8sznxenlzP7KMC66
> | >> 1xIvVCip588OGEEUj0zI%3D&reserved=0
> | > _______________________________________________
> | > ghc-steering-committee mailing list
> | > ghc-steering-committee at haskell.org
> | >
> | https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fmail
> | > .haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-steering-
> | committee&a
> | >
> | mp;data=04%7C01%7Csimonpj%40microsoft.com%7C886f711c1ffc4fb881da08d8a3
> | >
> | 070f8d%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637438598033659005
> | >
> | %7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6I
> | >
> | k1haWwiLCJXVCI6Mn0%3D%7C1000&sdata=O%2FGAauT8sznxenlzP7KMC661xIvVC
> | > ip588OGEEUj0zI%3D&reserved=0
> |
> | _______________________________________________
> | ghc-steering-committee mailing list
> | ghc-steering-committee at haskell.org
> | https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fmail
> | .haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-steering-
> | committee&data=04%7C01%7Csimonpj%40microsoft.com%7C886f711c1ffc4fb
> | 881da08d8a3070f8d%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C6374385
> | 98033659005%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMz
> | IiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000&sdata=O%2FGAauT8sznxenlzP7
> | KMC661xIvVCip588OGEEUj0zI%3D&reserved=0
> _______________________________________________
> ghc-steering-committee mailing list
> ghc-steering-committee at haskell.org
> https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee
More information about the ghc-steering-committee
mailing list