[ghc-steering-committee] #380 GHC2021: Voting starts

Spiwack, Arnaud arnaud.spiwack at tweag.io
Wed Dec 2 08:43:01 UTC 2020


Here is my updated vote:

## I don't know what these are

LexicalNegation: maybe
NondecreasingIndentation: maybe

## No opinion yet

Probably none of these are popular enough to be worth including in
this first round anyway.

BlockArguments: maybe
CUSKs: maybe
DataKinds: maybe
DefaultSignatures: maybe
DisambiguateRecordFields: maybe
DuplicateRecordFields: maybe
ImportQualifiedPost: maybe
MonadComprehensions: maybe
   ^ It's fairly popular this one, but I don't know the effects on
   type inference. I feel it may be a similar case as the OverloadedX
   extensions, in which case it feels premature to add it to GHC2021.
NamedFieldPuns: maybe
   ^ While I live and breath for NamedFieldPuns, it does remove some
   shadowing warnings, so it does make some things harder, and it's
   likely that we want this one left out of this round.
NamedWildCards: maybe
RecordWildCards: maybe
NullaryTypeClasses: maybe
NumDecimals: maybe
PackageImports: maybe
ParallelListComp: maybe
PolyKinds: maybe
RankNTypes: maybe
RecursiveDo: maybe
TransformListComp: maybe
TypeInType: maybe
TypeSynonymInstances: maybe
UnliftedFFITypes: maybe
ScopedTypeVariables: maybe
    ^ There seem to be discussion about the type-signature-in-pattern
    part of this extension, which I have no opinion about. I'm very
    much in favour of the bind-type-signature-variable parts. But I
    guess this is likely to be too controversial an extension for this
    round.
UnicodeSyntax: maybe
    ^ I think it changes error messages. I don't think that we can
    make error messages in Unicode by default. If it only affects
    parsing, then I'm in favour.

## Just adds syntax

These extensions simply add syntax, they bear little risk, I see no
reason not to avoid them. Let me include all of the deriving things in
this category.

Arrows: yes
BangPatterns: yes
BinaryLiterals: yes
DeriveDataTypeable: yes
DeriveFoldable: yes
DeriveFunctor: yes
DeriveGeneric: yes
DeriveLift: yes
DeriveTraversable: yes
DerivingStrategies: yes
GeneralisedNewtypeDeriving: yes
    ^ Though this technically collides with the DeriveX syntax, the
    collision is innocuous: you would derive the same functor whether
    you are using the stock strategy or the newtype strategy.
TypeFamilies: yes
TypeFamilyDependencies: yes
GADTs: yes
GADTSyntax: yes
    ^ Implied by GADTs
TypeOperators: yes
ConstraintKinds: yes
FunctionalDependencies: yes
EmptyCase: yes
HexFloatLiterals: yes
ConstrainedClassMethods: yes
ExplicitForAll: yes
ExplicitNamespaces: yes
KindSignatures: yes
NegativeLiterals: yes
NumericUnderscores: yes
PartialTypeSignatures: yes
ViewPatterns: yes
TypeApplications: yes
StandaloneDeriving: yes
PostfixOperators: yes
    ^ Not really new syntax, rather refined semantics in existing syntax.
But just as
    innocuous.

MonoLocalBinds: yes
   ^ MonoLocalBinds is implied by both GADTs and TypeFamilies. And it
   makes my addition of GADTs and TypeFamilies in this section a
   lie. We may want to have NoMonoLocalBinds turned on forcefully (or
   GADTSyntax but not GADTs nor TypeFamilies this time around). But
   MonoLocalBinds really want to become the default. So I'm inclined
   to let it be.

### Exceptions to the rule

DeriveAnyClass: no
   ^ This doesn't so much add syntax as generalises syntax (as opposed
   to DeriveFunctor, for instance, which may be read as adding Functor
   to the syntactic list of things which can appear in the Derive
   list). This probably leads to too many ambiguities for the first
   round.
DerivingVia: no
   ^ It's pretty innocuous, but too recent for inclusion.
TupleSections: probably not
   ^ I believe there has been some discussion about conflicts between
   TupleSection and terminal commas. So while it's a fairly popular
   extension, I think it's safer to keep it out.
ExistentialQuantification: probably notation
   ^ I don't think we need this syntax if GADTs are around. So maybe
   I'd rather see that as not being a default, so as to nudge
   programmers to the GADT syntax.
LambdaCase: probably not
   ^ As popular and lovely as this extension is, considering that
   there are some discussion on its future, I'm sadly compelled to
   give it a pass.

## Type class stuff

MultiParamTypeClasses: yes
FlexibleContexts: yes
FlexibleInstances: yes
   ^ I believe both FlexibleContexts and FlexibleInstances to be
   almost always innocuous, so they should probably make it in.
UndecidableInstances: no
UndecidableSuperClasses: no
   ^ The UndecidableX are not as scary as they look, yet, I don't
   think they ought to be there by default. This termination check
   exists for a reason. It's true that, today, many (most?) instances
   using MultiParamTypeClasses need UndecidableInstances, though. But
   it could probably be improved.

## Feature switches

These are switches for advanced feature (or "slow" features in the
case of the case of Template Haskell), they should never be on by
default.

NoImplicitPrelude: no
TemplateHaskell: no
TemplateHaskellQuotes: no
QuasiQuotes: no
RebindableSyntax: no
CApiFFI: no
CPP: no
ForeignFunctionInterface: no
GHCForeignImportPrim: no
InterruptibleFFI: no
MagicHash: no
UnboxedSums: no
UnboxedTuples: no
    ^ Though, frankly, all of MagicHash, UnboxedSums, and
    UnboxedTuples could very well become not-advanced in a
    not-so-far-future. Then we could turn them on by default as
    just-adding-syntax.

### Forks on the roads

These are not so much advanced features as features that change
significantly the meaning of the module they are in.

Strict: no
StrictData: no

## Module metadata

None of these should be on.

Safe: no
Trustworthy: no
Unsafe: no

## OverloadedX

These extensions can confuse type inference, yielding ambiguous type
variables message. And as much as I like them, I don't think it's safe
to include them yet. Not until we have a reasonable story for
defaulting literals.

OverloadedLabels: no
OverloadedLists: no
OverloadedStrings: no

## Difficult errors

These extension yield type errors which are quite a bit more difficult
than turning them off. So they are better left out.

AllowAmbiguousTypes: no

## Not ready yet

Hodgepodge list.

ApplicativeDo: no
LinearTypes: no
ImpredicativeTypes: no
QualifiedDo: no
QuantifiedConstraints: no
RoleAnnotations: no
StaticPointers: no
StandaloneKindSignatures: no
UnliftedNewtypes: no

## Already in GHC

MonadFailDesugaring: yes
StarIsType: yes
    ^ We should not turn this one off until standalone kind signatures
    are also the default, in my opinion.

## Already in Haskell 2010

EmptyDataDecls: yes
EmptyDataDeriving: yes

## Uncommon extensions

ExtendedDefaultRules: no
ImplicitParams: no
InstanceSigs: no
  -- ^ It does feel mostly innocuous on the surface, but it has a
  probably surprising semantics. Considering that it's quite rarely
  used, probably better left out.
LiberalTypeSynonyms: no
NoMonomorphismRestriction: no
NoPatternGuards: no
NoTraditionalRecordSyntax: no
PatternSynonyms: no

## Deprecated extensions

OverlappingInstances: no
DatatypeContexts: no
IncoherentInstances: no
MultiWayIf: no
NPlusKPatterns: no

On Tue, Dec 1, 2020 at 6:31 PM Simon Marlow <marlowsd at gmail.com> wrote:

> I will also change DeriveAnyClass to no:
>
> ## Uncontroversial extensions
>
> I've been writing code with most of these enabled by default for quite
> some time now. It saves a lot of LANGUAGE pragmas. Other than
> RecordWildCards I doubt any of these are controversial.
>
> BangPatterns: yes
> BinaryLiterals: yes
> DataKinds: yes
> DeriveDataTypeable: yes
> DeriveGeneric: yes
> EmptyCase: yes
> ExistentialQuantification: yes
> FlexibleContexts: yes
> FlexibleInstances: yes
> GADTs: yes
> GeneralisedNewtypeDeriving: yes
> LambdaCase: yes
> MultiParamTypeClasses: yes
> MultiWayIf: yes
> NoMonomorphismRestriction: yes
> OverloadedStrings: yes
> PatternSynonyms: yes
> RankNTypes: yes
> RecordWildCards: yes
> ScopedTypeVariables: yes
> StandaloneDeriving: yes
> TupleSections: yes
> TypeFamilies: yes
> TypeSynonymInstances: yes
> NondecreasingIndentation: yes
> ConstrainedClassMethods: yes
> ConstraintKinds: yes
> DefaultSignatures: yes
> DeriveFoldable: yes
> DeriveFunctor: yes
> DeriveTraversable: yes
> EmptyDataDecls: yes
> EmptyDataDeriving: yes
> HexFloatLiterals: yes
> ImportQualifiedPost: yes
> InstanceSigs: yes
> KindSignatures: yes
> LiberalTypeSynonyms: yes
> NamedFieldPuns: yes
>   (I don't personally like this, but I can't justify having
>   RecordWildcards but not having this)
> NegativeLiterals: yes
> NumDecimals: yes
> PolyKinds: yes
> PostfixOperators: yes
> UnicodeSyntax: yes
>   (but only the language extension, not the UI changes)
>
> ## Extensions that are implied by others, or are irrelevant:
>
> GADTSyntax: yes
> ExplicitForAll: yes
> MonadFailDesugaring: irrelevant
> MonoLocalBinds: yes
>
> ## Extensions that are deprecated or exist for legacy reasons:
>
> DatatypeContexts: no
> NPlusKPatterns: no
> CUSKs: no
> NoPatternGuards: no
> ForeignFunctionInterface: yes
>   (already implied by Haskell2010, why do we have this but
>   NoPatternGuards?)
> NullaryTypeClasses: no
> OverlappingInstances: no
> IncoherentInstances: no
> TypeInType: no
>
> ## No to extensions that are too new to include in GHC2021:
>
> QualifiedDo: no
> LinearTypes: no
> BlockArguments: no
> LexicalNegation: no
> QuantifiedConstraints: no
> StandaloneKindSignatures: no
> StarIsType: no
>
> ## No to extensions that are opt-in by design:
>
> ApplicativeDo: no
>   (can lead to non-deterministic behaviour with non-rule-abiding
>   Applicative instances)
> PackageImports: no
> CPP: no
> DeriveLift: no
>   (only makes sense with TemplateHaskell, which is opt-in)
> TemplateHaskell: no
> TemplateHaskellQuotes: no
> QuasiQuotes: no
> RebindableSyntax: no
> Safe: no
> Strict: no
> StrictData: no
> Trustworthy: no
> Unsafe: no
> ExtendedDefaultRules: no
> NoImplicitPrelude: no
>
> ## No to unsafe extensions:
>
> UndecidableInstances: no
> UndecidableSuperClasses: no
>
> ## No to low-level extensions, not intended to be on by default:
>
> UnboxedTuples: no
> UnboxedSums: no
> MagicHash: no
> UnliftedFFITypes: no
> UnliftedNewtypes: no
> GHCForeignImportPrim: no
> InterruptibleFFI: no
>
> ## No to record-related extensions
>
> Records are in flux, let's not do any of this in GHC2021.
>
> DisambiguateRecordFields: no
> DuplicateRecordFields: no
> NoTraditionalRecordSyntax: no
> OverloadedLabels: no
>
> ## The rest
>
> That leaves some tricky ones, I'm putting all these as "no" or
> "maybe"; we could conservatively just say "no" to all of them.
>
> I'm voting NO on these:
>
> Arrows: no
>   (not widely used)
> ImplicitParams: no
>   (not widely used; questionable semantics; functionality available
>   with reflection package)
> ImpredicativeTypes: no
>   (I don't think we want this on by default, right?)
> ParallelListComp: no
>   (not widely used, most uses are covered by zip)
> StaticPointers: no
>   (quite a niche extension, only really useful with Distributed Haskell)
> TransformListComp: no
>   (not widely used)
> ViewPatterns: no
>   (not widely used, and in my opinion not a good design)
> DeriveAnyClass: no
>   (see discussion on the mailing list)
>
> I'm undecided on these:
>
> AllowAmbiguousTypes: maybe
> TypeApplications: maybe
> CApiFFI: maybe
>   (harmless, but a bit niche)
> DerivingVia: maybe
>   (not very widely-used, quite new)
> DerivingStrategies: maybe
>   (not very widely-used, quite new)
> FunctionalDependencies: maybe
>   (slightly inclined to "no", given the overlap
>   with TypeFamilies and the lack of widespread usage)
> ExplicitNamespaces: maybe
>   (might change, so defer?)
> MonadComprehensions: maybe
>   (does this make error messages worse?)
> PartialTypeSignatures: maybe
> NamedWildCards: maybe
> NumericUnderscores: maybe
> OverloadedLists: maybe
>   (impact on error messages?)
> RecursiveDo: maybe
>   (but introduced by a keyword so relatively harmless)
> RoleAnnotations: maybe
>   (not widely used, but when you need it you need it)
> TypeFamilyDependencies: maybe
>   (not widely used, but when you need it you need it)
> TypeOperators: maybe
>
> On Tue, 1 Dec 2020 at 08:51, Joachim Breitner <mail at joachim-breitner.de>
> wrote:
>
>> Hi,
>>
>> Am Dienstag, den 01.12.2020, 00:43 -0800 schrieb Alejandro Serrano
>> Mena:
>> > Thanks everybody for an illuminating discussion about DeriveAnyClass.
>> > I was not aware of the dark corners of the extension (and actually,
>> > now I find it weird that GHC itself suggests that extension!). Here
>> > are my updated votes
>>
>> Noted!
>>
>> > apart from a ’No’ to DeriveAnyClass I’ve updated my votes of
>> > StandaloneKindSignatures and ImportQualifiedPost to ‘Yes’.
>>
>> JFTR, you also changed OverloadedLists and OverloadedStrings from maybe
>> to yes.
>>
>>
>> Cheers,
>> Joachim
>> --
>> Joachim Breitner
>>   mail at joachim-breitner.de
>>   http://www.joachim-breitner.de/
>>
>>
>> _______________________________________________
>> ghc-steering-committee mailing list
>> ghc-steering-committee at haskell.org
>> https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee
>>
> _______________________________________________
> ghc-steering-committee mailing list
> ghc-steering-committee at haskell.org
> https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-steering-committee/attachments/20201202/c3f078c0/attachment-0001.html>


More information about the ghc-steering-committee mailing list