My votes:

## 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
DeriveAnyClass: 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

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

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, 24 Nov 2020 at 09:34, Joachim Breitner <mail@joachim-breitner.de> wrote:
Dear Committee,

the requested data (hackage and survey) is in, has been aggregated,
cooked, seasoned and is ready for consumption. 116 extensions are
waiting on your assessment, so time to vote!

## Procedure

Please vote by email to this list, in a response to this thread.

I want to make tallying easy and automatic, and my code will consider
an extension Foo voted for if you write "Foo: yes" on its own line.
This means you can include rationales, write "Foo: maybe" and "Foo: no"
to remind yourself and others that about where you are, and you can
safely quote other’s mails. For example, if you write:

---- begin
example ----

Easy ones:

DeriveFooBar: yes
OverloadedBen: no

These ones are tricky:

ImplicitExceptions: yes
  I know nobody likes that one, but I do.

RandomEvaluationOrder: maybe
  Not sure about this one, here is why…


> Richard wrote:
> DependentHaskell: yes
> Rationale: See my thesis

I’m not convinced yet, tell me more, so
DependentHaskell: maybe

---- end example ----

then you have voted for DeriveFooBar and ImplicitExceptions. Only “yes”
matters, “no”, “maybe” and “later” are all ignored.

I will shortly send my first ballot around. Also see the end of this
mail for a copy’n’paste template.

You can update your vote as often as you want. Please always send your
full votes (I will only consider your latest email). I encourage you to
do that early, e.g. maybe start with a mail where you list the obvious
yes and nos, and keep some at maybe and then refine.

The timeline says first votes should be in within two weeks, and then a
bit more to refine. But the earlier the merrier!

The quota is 8. In particular, if everyone votes (and I hope everyone
will), an extension won’t make it this round if 4 don’t include it.

## Data

Please see
https://github.com/ghc-proposals/ghc-proposals/blob/ghc2021/proposals/0000-ghc2021.rst#data
for the data, including explanations. It is intentionally not sorted by
the data, as the choice of ranking function would already be quite
influencing.

You may want to play around with that data, e.g. sort it by your own
criteria etc. I looked long for an online service where I can upload
the data and allow you to explore it, but then I noticed that that's a
bit stupid, since we all probably can do it best with Haskell.

So I made it easy to load the data into GHCi, see the instructions at
https://github.com/nomeata/ghc-proposals-stats/blob/master/ext-stats/README.md
which allow you, for example, to do this

*Main> mapM_ (\E{..} -> Text.Printf.printf "%s: %d\n" ext survey_no) $ take 10 $ reverse $ sortOn (\E{..} -> survey_no) (M.elems exts)
AllowAmbiguousTypes: 195
CPP: 192
IncoherentInstances: 176
Arrows: 156
Strict: 153
ImplicitParams: 147
UndecidableInstances: 144
OverlappingInstances: 144
Unsafe: 139
TemplateHaskell: 137

Of course, if someone wants to upload the data somewhere and share
that, that's also useful.


Let me know if some of this doesn't quite work for you, and should be
improved. Maybe we need a web form instead of mails?


## PS: Blank ballot

To start, you could copy the following into an email

AllowAmbiguousTypes: maybe
ApplicativeDo: maybe
Arrows: maybe
BangPatterns: maybe
BinaryLiterals: maybe
BlockArguments: maybe
CApiFFI: maybe
CPP: maybe
CUSKs: maybe
ConstrainedClassMethods: maybe
ConstraintKinds: maybe
DataKinds: maybe
DatatypeContexts: maybe
DefaultSignatures: maybe
DeriveAnyClass: maybe
DeriveDataTypeable: maybe
DeriveFoldable: maybe
DeriveFunctor: maybe
DeriveGeneric: maybe
DeriveLift: maybe
DeriveTraversable: maybe
DerivingStrategies: maybe
DerivingVia: maybe
DisambiguateRecordFields: maybe
DuplicateRecordFields: maybe
EmptyCase: maybe
EmptyDataDecls: maybe
EmptyDataDeriving: maybe
ExistentialQuantification: maybe
ExplicitForAll: maybe
ExplicitNamespaces: maybe
ExtendedDefaultRules: maybe
FlexibleContexts: maybe
FlexibleInstances: maybe
ForeignFunctionInterface: maybe
FunctionalDependencies: maybe
GADTSyntax: maybe
GADTs: maybe
GHCForeignImportPrim: maybe
GeneralisedNewtypeDeriving: maybe
HexFloatLiterals: maybe
ImplicitParams: maybe
ImportQualifiedPost: maybe
ImpredicativeTypes: maybe
IncoherentInstances: maybe
InstanceSigs: maybe
InterruptibleFFI: maybe
KindSignatures: maybe
LambdaCase: maybe
LexicalNegation: maybe
LiberalTypeSynonyms: maybe
LinearTypes: maybe
MagicHash: maybe
MonadComprehensions: maybe
MonadFailDesugaring: maybe
MonoLocalBinds: maybe
MultiParamTypeClasses: maybe
MultiWayIf: maybe
NPlusKPatterns: maybe
NamedFieldPuns: maybe
NamedWildCards: maybe
NegativeLiterals: maybe
NoImplicitPrelude: maybe
NoMonomorphismRestriction: maybe
NoPatternGuards: maybe
NoTraditionalRecordSyntax: maybe
NondecreasingIndentation: maybe
NullaryTypeClasses: maybe
NumDecimals: maybe
NumericUnderscores: maybe
OverlappingInstances: maybe
OverloadedLabels: maybe
OverloadedLists: maybe
OverloadedStrings: maybe
PackageImports: maybe
ParallelListComp: maybe
PartialTypeSignatures: maybe
PatternSynonyms: maybe
PolyKinds: maybe
PostfixOperators: maybe
QualifiedDo: maybe
QuantifiedConstraints: maybe
QuasiQuotes: maybe
RankNTypes: maybe
RebindableSyntax: maybe
RecordWildCards: maybe
RecursiveDo: maybe
RoleAnnotations: maybe
Safe: maybe
ScopedTypeVariables: maybe
StandaloneDeriving: maybe
StandaloneKindSignatures: maybe
StarIsType: maybe
StaticPointers: maybe
Strict: maybe
StrictData: maybe
TemplateHaskell: maybe
TemplateHaskellQuotes: maybe
TransformListComp: maybe
Trustworthy: maybe
TupleSections: maybe
TypeApplications: maybe
TypeFamilies: maybe
TypeFamilyDependencies: maybe
TypeInType: maybe
TypeOperators: maybe
TypeSynonymInstances: maybe
UnboxedSums: maybe
UnboxedTuples: maybe
UndecidableInstances: maybe
UndecidableSuperClasses: maybe
UnicodeSyntax: maybe
UnliftedFFITypes: maybe
UnliftedNewtypes: maybe
Unsafe: maybe
ViewPatterns: maybe




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