Updated votes, resolving all my maybes:

Delta:

 * yes to NamedWildCards *and* PartialTypeSignatures (these are
   actually really useful and unless someone tells me otherwise I
   don't know any reason why the language with these is less
   principled than without.  I would also -Wno-partial-type-signatures
   by default if that was in scope for GHC2021)
 * yes to TypeApplications (sure, why not)
 * all other maybes -> no (mainly just being conservative, we can
   reconsider for GHC2022 any that miss out)

## Uncontroversial extensions

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: yes
  (changed to yes because it's needed to replace CUSKs)
StarIsType: yes
  (changed to yes following discussion)

## 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)

Undecided (later resolved):

AllowAmbiguousTypes: no
TypeApplications: yes
CApiFFI: no
  (harmless, but a bit niche)
DerivingVia: no
  (not very widely-used, quite new)
DerivingStrategies: no
  (not very widely-used, quite new)
FunctionalDependencies: no
  (slightly inclined to "no", given the overlap
  with TypeFamilies and the lack of widespread usage)
ExplicitNamespaces: no
  (might change, so defer?)
MonadComprehensions: no
  (does this make error messages worse?)
NamedWildCards: yes
NumericUnderscores: no
OverloadedLists: no
  (impact on error messages?)
PartialTypeSignatures: yes
RecursiveDo: no
  (but introduced by a keyword so relatively harmless)
RoleAnnotations: no
  (not widely used, but when you need it you need it)
TypeFamilyDependencies: no
  (not widely used, but when you need it you need it)
TypeOperators: no

On Mon, 7 Dec 2020 at 18:17, Joachim Breitner <mail@joachim-breitner.de> wrote:
Dear Committe,

it’s been two weeks since we started voting. We are still short one
vote (Cale, release the suspsense!). But also, there are still plenty
of “maybes” in your vote. I encourage you to change them to yes or no
(at least for those extensions that are near the edge), so that we have
more clarity on which extensions are actually worth spending emails on.

As always, the table
https://github.com/ghc-proposals/ghc-proposals/blob/ghc2021/proposals/0000-ghc2021.rst#data
has the current data. (And even even got community contributions to
improve its readability. Yay!)

We discussed many extensions on (and I might have missed some):

 * The innnocence of PostfixOperators was pointed out, and widely
   appreciated
 * Joachim pleads for UnicodeSyntax
 * InstanceSigs worries seems to have been addressed, it’s on its way
   in
 * Whether OverloadedString is harmless enough.
 * Whether ViewPatterns are good enough (given that alternative ideas
   exist)
 * That ForeignFunctionInterfaces is actually part of Haskell2010
 * That this isn’t quite the right time to ditch StarIsType
 * CUSKs vs. StandaloneKindSignatures
 * BlockArguments is liked by some, but may be too new
 * GADTs were advocated for a lot, but also a bit against, so not
   uncontroversial
 * Same with ExistentialQuantification
 * PolyKinds were advocated for (and got many votes)
 * ScopedTypeVariables is wanted on by default by some,
   despite the fact that nobody believes it’s the last
   word on that design corner. Alejandro argues that it’s
   ok to include it even if it will change in GHC202X again,
   but elsewhere SPJ says that GHC2021 should only include extensions
   we have reason to hope are stable and stay around .
 * Arnaud wonders about the hesitation to include
   FunctionalDependencies


Applying the actual quota of ⅔ out of 11, i.e. 8 votes, these would go
in no matter how Cale votes:

   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, TypeOperators, TypeSynonymInstances

The following have 7 votes, which is the quorum based on 10 ballots:

   ExistentialQuantification, ForeignFunctionInterface, MonoLocalBinds,
   NegativeLiterals, RecordWildCards, StandaloneKindSignatures,
   TypeFamilies

And these are one vote short:

   DataKinds, DerivingStrategies, GADTs, NamedWildCards,
   ScopedTypeVariables, TupleSections, UnicodeSyntax, ViewPatterns


Not sure how useful the list of symmetric difference report is, but
here it is:

alejandro
would miss:
DataKinds, DerivingStrategies, FunctionalDependencies, GADTs,
LambdaCase, MonadFailDesugaring, NamedWildCards,
NoMonomorphismRestriction, NullaryTypeClasses, NumDecimals,
OverloadedLists, OverloadedStrings, ScopedTypeVariables, TupleSections,
UnicodeSyntax, ViewPatterns
doesn’t want:
none!

arnaud
would miss:
Arrows, DerivingStrategies, ExplicitNamespaces, FunctionalDependencies,
GADTs, MonadFailDesugaring, PartialTypeSignatures,
TypeFamilyDependencies, ViewPatterns
doesn’t want:
ExistentialQuantification, ImportQualifiedPost, InstanceSigs,
NamedFieldPuns, PolyKinds, RankNTypes, RecordWildCards,
StandaloneKindSignatures, TypeSynonymInstances

eric
would miss:
DataKinds, DefaultSignatures, DisambiguateRecordFields,
ExplicitNamespaces, FunctionalDependencies, GADTs, MonadFailDesugaring,
NamedWildCards, OverloadedLists, OverloadedStrings,
PartialTypeSignatures, PatternSynonyms, RoleAnnotations,
ScopedTypeVariables, TypeFamilyDependencies
doesn’t want:
EmptyDataDeriving, ForeignFunctionInterface

iavor
would miss:
BlockArguments, CApiFFI, MultiWayIf, NoMonomorphismRestriction,
NullaryTypeClasses, ParallelListComp, RecursiveDo, UnicodeSyntax,
UnliftedNewtypes
doesn’t want:
ConstrainedClassMethods, EmptyCase, ExplicitForAll, GADTSyntax,
GeneralisedNewtypeDeriving, InstanceSigs, KindSignatures,
MonoLocalBinds, NegativeLiterals, PolyKinds, StandaloneKindSignatures,
StarIsType, TypeApplications, TypeFamilies, TypeOperators

joachim
would miss:
DataKinds, DerivingStrategies, DerivingVia, LambdaCase, NamedWildCards,
NondecreasingIndentation, RoleAnnotations, TupleSections,
UnicodeSyntax, UnliftedFFITypes, UnliftedNewtypes
doesn’t want:
ConstrainedClassMethods, ExistentialQuantification,
TypeSynonymInstances

richard
would miss:
BlockArguments, DefaultSignatures, DerivingStrategies, DerivingVia,
DisambiguateRecordFields, ExplicitNamespaces, LexicalNegation,
NamedWildCards, NumDecimals, ParallelListComp, RoleAnnotations,
TemplateHaskellQuotes, TupleSections, UnicodeSyntax, UnliftedNewtypes,
ViewPatterns
doesn’t want:
MonoLocalBinds, NegativeLiterals, RecordWildCards, TypeFamilies

simonm
would miss:
DataKinds, DefaultSignatures, GADTs, LambdaCase, LiberalTypeSynonyms,
MultiWayIf, NoMonomorphismRestriction, NondecreasingIndentation,
NumDecimals, OverloadedStrings, PatternSynonyms, ScopedTypeVariables,
TupleSections, UnicodeSyntax
doesn’t want:
DeriveLift, NumericUnderscores, TypeApplications, TypeOperators

spj
would miss:
NoMonomorphismRestriction, NullaryTypeClasses, OverloadedLists,
OverloadedStrings, ParallelListComp, RecursiveDo, RoleAnnotations,
ScopedTypeVariables, ViewPatterns
doesn’t want:
ForeignFunctionInterface, GeneralisedNewtypeDeriving, NegativeLiterals,
RecordWildCards, TypeFamilies

tom
would miss:
BlockArguments, DataKinds, DefaultSignatures, DerivingStrategies,
DerivingVia, DisambiguateRecordFields, DuplicateRecordFields,
ExplicitNamespaces, FunctionalDependencies, GADTs, LambdaCase,
LexicalNegation, LiberalTypeSynonyms, MagicHash, MultiWayIf,
NamedWildCards, NullaryTypeClasses, NumDecimals, PackageImports,
ParallelListComp, QuasiQuotes, RoleAnnotations, ScopedTypeVariables,
TemplateHaskell, TemplateHaskellQuotes, TupleSections,
TypeFamilyDependencies, UnboxedSums, UnboxedTuples, UnicodeSyntax,
UnliftedNewtypes, ViewPatterns
doesn’t want:
ForeignFunctionInterface, MonoLocalBinds, StarIsType

vitaly
would miss:
DataKinds, DerivingStrategies, DerivingVia, GADTs, LambdaCase,
MonadFailDesugaring, NamedWildCards, OverloadedLists,
OverloadedStrings, ScopedTypeVariables, TupleSections, ViewPatterns
doesn’t want:
ExistentialQuantification, StandaloneKindSignatures

Cheers,
Joachim

--
Joachim Breitner
  mail@joachim-breitner.de
  http://www.joachim-breitner.de/


_______________________________________________
ghc-steering-committee mailing list
ghc-steering-committee@haskell.org
https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee