<div dir="ltr">Hello,<br><br>these took me way too long :)  Here we go:<br><br><br><b>Module System<br>=============</b><br><br>ImportQualifiedPost: yes<br>-- ^ This is relatively new, but it seems quite simple, and it does make<br>-- things read nicer.<br><br>-- | These are only needed under very special circumstances,<br>-- so it's good to be explicit:<br>PackageImports: no<br>NoImplicitPrelude: no<br><br><br><b>Notation<br>========</b><br><br>BlockArguments: yes<br>-- ^ I use this all the time.<br><br>MultiWayIf: yes<br>-- ^ This is nice on occasion, and it does not seem to conflict with<br>-- anything.  Certainly nicer than the alternative `case () of _ | ... `:<br><br>LambdaCase: maybe<br>-- ^ Personally I don't use this, but I know a lot of folks like it,<br>-- so I'd be OK with it being enabled.<br><br>-- | The various literal notations seem useful when you need them<br>-- and don't conflict with anything.<br>BinaryLiterals: yes<br>HexFloatLiterals: yes<br>NumericUnderscores: yes<br>NumDecimals: maybe<br>-- ^ | Not too sure about this last one, I've never used, but it<br>-- I could see it being useful on occasion.<br><br>OverloadedStrings: yes<br>-- ^ | I use this a lot, and would be OK with it being on all the time.<br><br>OverloadedLists: maybe<br>-- | ^ I've never used this, but I could see it potentially being useful.<br><br>OverloadedLabels: no<br>-- | ^ This one seems for experimenting with various new features<br>-- (e.g., record selectors), so it seems reasonable to turn it on only<br>-- when it is needed.<br><br>EmptyCase: maybe<br>-- ^ Seems like a nicer notation for forcing `Void` values.<br>-- I agree that it is odd that it is strict.  OTOH, it'd be quite useless<br>-- if it was lazy, so I could go either way.<br><br>-- | I haven't really used any of those, so I could go either way:<br>PostfixOperators: maybe<br>LexicalNegation: maybe<br>UnicodeSyntax: maybe<br><br>NegativeLiterals: no<br>-- ^ It seems that `LexicalNegation` might be a nicer way to do this?<br><br>TupleSections: maybe<br>-- ^ I don't use this often, but I'd use it more often if it was on by default.<br><br>ImplicitParams: no<br>-- ^ I find these quite useful on occasion, but it does seem reasonable<br>-- to be explicit when you need them.<br><br>ParallelListComp: yes<br>-- ^ I find these to be a very nice generalization to list comprehensions<br>-- that makes some code way more readable than using `zip/zipWith`, just<br>-- like comprehensions are often nicer than `map` or `concatMap`<br><br>RecursiveDo: yes<br>-- ^ Seems useful when you need it, and it doesn't clash with anything,<br>-- so I see no reason to not have it on all the time.<br><br>TransformListComp: no<br>-- ^ In my mind these are just a bit too much syntactic sugar.<br><br>Arrows: no<br>-- ^ It's not used a lot, not terribly useful and overall feels "clunky".<br><br>ApplicativeDo: maybe<br>-- ^ I think the core of this extension is really useful,<br>-- but I would prefer a simpler syntactic version of it,<br>-- without the various transformations assuming that some laws hold.<br><br>QualifiedDo: no<br>-- ^ This is neat, but it is too new to be on by default.<br><br>MonadComprehensions: maybe<br>-- ^ I never really use these.<br>-- On occasion I've wanted `ApplicativeComprehensions` though.<br><br>NondecreasingIndentation: no<br>-- ^ This always felt like a hack to me.<br><br>RebindableSyntax: no<br>-- ^ This is a very special case thing<br><br>ExplicitNamespaces: maybe<br>-- ^ We need this if we also want pattern synonyms.<br><div><br></div><div><br></div><div><b>Data Types<br>==========<br></b><br>DatatypeContexts: no<br>-- ^ These are not really used much, and usually don't do what people expect.<br><br>ExistentialQuantification: yes<br>-- ^ This is quite useful, and has been around for a long time.<br><br>EmptyDataDecls: yes<br>-- ^ Seems more consistent to allow this<br><br>RoleAnnotations: no<br>-- ^ This only makes sense with `GeneralisedNewtypeDeriving` which<br>-- I don't think should be on by default.<br><br>StrictData: no<br>-- ^ This is very unHaskell :)<br><br>GADTSyntax: maybe<br>-- ^ I personally don't use this, but I know some folks like to write<br>-- their `data` declarations in this notation.<br><br>GADTs: no<br>-- ^ These can be useful, but it seems reasonable to enable them when<br>-- you need them, as they bring in quite a lot of machinery with them.<br></div><div><br></div><div><br></div><div><b>Patterns and Guards<br>===================</b><br>BangPatterns: yes<br>-- ^ Seem to be useful, and quite popular.<br><br>ViewPatterns: yes<br>-- ^ Useful on occasion, and I don't think calling out the extension<br>-- explicitly helps anyone.<br><br>PatternSynonyms: maybe<br>-- ^ These are quite useful, but I am not sure how stable is theiry design.<br><br>NoPatternGuards: no<br>-- ^ Conflicts with Haskell2010<br><br>NPlusKPatterns: no<br>-- ^ Conflicts with Haskell2010<br><br><br><b>Records<br>=======</b><br><br>-- | I find these two very useful when working with records,<br>-- especially large ones, and declaring the extension really adds no<br>-- information:<br>NamedFieldPuns: yes<br>RecordWildCards: yes<br><br>-- | These seem to be largely about experimenting with new record<br>system, and I don't think any of them are quite ready to be on by default:<br>DisambiguateRecordFields: no<br>DuplicateRecordFields: no<br>NoTraditionalRecordSyntax: no<br><br></div><div><b>Deriving<br>=======</b><br><br>-- | Declaring these as extensions explicitly adds very little information.<br>DeriveGeneric: yes<br>DeriveLift: yes<br>DeriveDataTypeable: yes<br><br>EmptyDataDeriving: yes<br>-- ^ Useful for consistency<br><br>StandaloneDeriving: yes<br>-- ^ I find this quite useful on occasion, and does not conflict with anything<br><br><br>-- | I think the rest of the deriving extensions are not particularly orthogonal<br>at the moment, so I don't think we should have them on by default, at least<br>not yet, even though I find some of them quite useful.<br><br>DeriveFunctor: no<br>DeriveFoldable: no<br>DeriveTraversable: no<br>DerivingStrategies: no<br>DerivingVia: no<br>GeneralisedNewtypeDeriving: no<br>DeriveAnyClass: no<br></div><div><br></div><div><br><b>Class System<br>============</b><br><br>MultiParamTypeClasses: yes<br>-- ^ Seems like a natural extension and does not really conflict with anything<br><br>NullaryTypeClasses: yes<br>-- ^ Seems like a natural extension and does not really conflict with anything<br><br>ConstraintKinds: maybe<br>-- ^ These seem like a very nice fit with the rest of the kind system,<br>-- so I think we can enable them.  The reason I wrote `maybe` is due to<br>-- the confusion between constraints and tuples.<br><br>-- | These 3 seem to be quite common.  There are some reasons to be careful<br>-- when writing `FlexibleInstances`, but it seems that having the extension<br>-- does not really help much with those.<br>TypeSynonymInstances: yes<br>FlexibleInstances: yes<br>FlexibleContexts: yes<br><br>-- | I haven't really used these much, so I don't have a strong opinion:<br>ConstrainedClassMethods: maybe<br>DefaultSignatures: maybe<br>InstanceSigs: maybe<br>ExtendedDefaultRules: maybe<br><br>FunctionalDependencies: no<br>-- ^ While I quite like the general idea here, I don't think we should<br>-- have these on by default.<br><br>QuantifiedConstraints: no<br>-- ^ These seem neat, but are quite new to be on by default.<br><br>UndecidableInstances: no<br>-- ^ These are a very special case, and ideally should be specified<br>-- on a per instance basis.<br><br>IncoherentInstances: no<br>-- ^ Why do we even have this? :)<br><br>UndecidableSuperClasses: no<br>-- ^ These are a very special case.<br><br>OverlappingInstances: no<br>-- ^ This has been subsumed by per-instance pragmas<br><b><br>Types<br>=====</b><br><br>RankNTypes: yes<br>-- ^ These are useful and have been around for a long time.  The design<br>-- seems to work well.<br><br>-- | These two seem useful, but I am not sure if they should be on by default.<br>-- If so, though, it makes sense to have both of them on.<br>StandaloneKindSignatures: maybe<br>KindSignatures: maybe<br><br>LiberalTypeSynonyms: maybe<br>-- ^ These seem useful, but can lead to some rather confusing situations<br>-- where types that look "normal" don't behave as you'd expect<br>-- (e..g, writing `[T]` fails because `T` happens to have `forall` in it)<br><br>-- | These two go together and seem quite useful, especially when writing<br>-- local type signatures.<br>ScopedTypeVariables: yes<br>ExplicitForAll: yes<br><br>AllowAmbiguousTypes: no<br>-- ^ Often these are unintentional, and are due to a mistake in the program.<br><br>ImpredicativeTypes: no<br>-- ^ These are being currently redesigned, so not ready.<br><br>MonoLocalBinds: maybe<br>-- ^ I don't know if this one is on by default or not already...<br><br>NoMonomorphismRestriction: yes<br>-- ^ The monomrphism restriction seems to cause a lot of confusion, and I<br>-- am not sure that it's helped that much with efficiency<br><br>-- | Doesn't really seem to be commonly used.<br>PartialTypeSignatures: no<br>NamedWildCards: no<br><br>LinearTypes: no<br>-- ^ Too new to be standardized<br><br>TypeApplications: no<br>-- ^ This one is quite useful, bit it seems that its design and how many users<br>-- understand it don't match, so maybe there is more work to be done.<br><br>-- | These are all related to type-level programming, and while I don't think<br>-- they should be on by default, it might be useful to have a single flag that<br>-- turns a bunch of them on.<br>PolyKinds: no<br>TypeOperators: no<br>StarIsType: maybe<br>TypeFamilies: no<br>TypeFamilyDependencies: no<br>DataKinds: no<br><br></div><div><b>FFI<br>===</b><br>I don't think the FFI should be on by default, as it is used relatively<br>infrequently, although it might be nice if `ForeignFunctionInterface`<br>implied `CApiFFI`<br><br>ForeignFunctionInterface: no<br>CApiFFI: no<br>GHCForeignImportPrim: no<br>InterruptibleFFI: no<br>UnliftedFFITypes: no<br>StaticPointers: no<br><br><br><b>Low Level<br>=========</b><br><br>These are for low-level hacking, so I don't think they should be<br>on by default.  However, I wouldn't mind having a flag that enabled<br>all of them with a single extension (e.g., `UnliftedTypes`)<br><br>UnboxedSums: no<br>UnboxedTuples: no<br>MagicHash: no<br>UnliftedNewtypes: no<br><br><b>Macros<br>======</b><br><br>CPP: no<br>This is quite specialized, so it seems reasonable to be explicit about it.<br><br><br>I don't think these should be on by default, but I wouldn't mind it<br>if `TemplateHaskell` implied `QuasiQuotes`, so that when I use TH<br>I just need to turn on a single extension.:<br><br>TemplateHaskell: no<br>TemplateHaskellQuotes: no<br>QuasiQuotes: no</div><div><br></div><div><br><b>Other<br>=====</b><br><br>-- | These are part of Safe Haskell and are there to be written explicitly<br>Unsafe: no<br>Safe: no<br>Trustworthy: no<br><br><br>Strict: no<br>-- ^ This is not Haskell! :-)<br><br><b>Obsolete/Deprecated<br>===================</b><br>CUSKs: no<br>TypeInType: no<br>MonadFailDesugaring: maybe<br><br><br><br><br></div><div><br></div><div><br></div><div><br></div></div><br><div class="gmail_quote"><div dir="ltr" class="gmail_attr">On Tue, Nov 24, 2020 at 1:34 AM Joachim Breitner <<a href="mailto:mail@joachim-breitner.de">mail@joachim-breitner.de</a>> wrote:<br></div><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left:1px solid rgb(204,204,204);padding-left:1ex">Dear Committee,<br>
<br>
the requested data (hackage and survey) is in, has been aggregated,<br>
cooked, seasoned and is ready for consumption. 116 extensions are<br>
waiting on your assessment, so time to vote!<br>
<br>
## Procedure<br>
<br>
Please vote by email to this list, in a response to this thread.<br>
<br>
I want to make tallying easy and automatic, and my code will consider<br>
an extension Foo voted for if you write "Foo: yes" on its own line.<br>
This means you can include rationales, write "Foo: maybe" and "Foo: no"<br>
to remind yourself and others that about where you are, and you can<br>
safely quote other’s mails. For example, if you write:<br>
<br>
---- begin<br>
example ----<br>
<br>
Easy ones:<br>
<br>
DeriveFooBar: yes<br>
OverloadedBen: no<br>
<br>
These ones are tricky:<br>
<br>
ImplicitExceptions: yes<br>
  I know nobody likes that one, but I do.<br>
<br>
RandomEvaluationOrder: maybe<br>
  Not sure about this one, here is why…<br>
<br>
<br>
> Richard wrote:<br>
> DependentHaskell: yes<br>
> Rationale: See my thesis<br>
<br>
I’m not convinced yet, tell me more, so<br>
DependentHaskell: maybe<br>
<br>
---- end example ----<br>
<br>
then you have voted for DeriveFooBar and ImplicitExceptions. Only “yes”<br>
matters, “no”, “maybe” and “later” are all ignored.<br>
<br>
I will shortly send my first ballot around. Also see the end of this<br>
mail for a copy’n’paste template.<br>
<br>
You can update your vote as often as you want. Please always send your<br>
full votes (I will only consider your latest email). I encourage you to<br>
do that early, e.g. maybe start with a mail where you list the obvious<br>
yes and nos, and keep some at maybe and then refine.<br>
<br>
The timeline says first votes should be in within two weeks, and then a<br>
bit more to refine. But the earlier the merrier!<br>
<br>
The quota is 8. In particular, if everyone votes (and I hope everyone<br>
will), an extension won’t make it this round if 4 don’t include it.<br>
<br>
## Data<br>
<br>
Please see <br>
<a href="https://github.com/ghc-proposals/ghc-proposals/blob/ghc2021/proposals/0000-ghc2021.rst#data" rel="noreferrer" target="_blank">https://github.com/ghc-proposals/ghc-proposals/blob/ghc2021/proposals/0000-ghc2021.rst#data</a><br>
for the data, including explanations. It is intentionally not sorted by<br>
the data, as the choice of ranking function would already be quite<br>
influencing.<br>
<br>
You may want to play around with that data, e.g. sort it by your own<br>
criteria etc. I looked long for an online service where I can upload<br>
the data and allow you to explore it, but then I noticed that that's a<br>
bit stupid, since we all probably can do it best with Haskell.<br>
<br>
So I made it easy to load the data into GHCi, see the instructions at<br>
<a href="https://github.com/nomeata/ghc-proposals-stats/blob/master/ext-stats/README.md" rel="noreferrer" target="_blank">https://github.com/nomeata/ghc-proposals-stats/blob/master/ext-stats/README.md</a><br>
which allow you, for example, to do this<br>
<br>
*Main> mapM_ (\E{..} -> Text.Printf.printf "%s: %d\n" ext survey_no) $ take 10 $ reverse $ sortOn (\E{..} -> survey_no) (M.elems exts)<br>
AllowAmbiguousTypes: 195<br>
CPP: 192<br>
IncoherentInstances: 176<br>
Arrows: 156<br>
Strict: 153<br>
ImplicitParams: 147<br>
UndecidableInstances: 144<br>
OverlappingInstances: 144<br>
Unsafe: 139<br>
TemplateHaskell: 137<br>
<br>
Of course, if someone wants to upload the data somewhere and share<br>
that, that's also useful.<br>
<br>
<br>
Let me know if some of this doesn't quite work for you, and should be<br>
improved. Maybe we need a web form instead of mails?<br>
<br>
<br>
## PS: Blank ballot<br>
<br>
To start, you could copy the following into an email<br>
<br>
AllowAmbiguousTypes: maybe<br>
ApplicativeDo: maybe<br>
Arrows: maybe<br>
BangPatterns: maybe<br>
BinaryLiterals: maybe<br>
BlockArguments: maybe<br>
CApiFFI: maybe<br>
CPP: maybe<br>
CUSKs: maybe<br>
ConstrainedClassMethods: maybe<br>
ConstraintKinds: maybe<br>
DataKinds: maybe<br>
DatatypeContexts: maybe<br>
DefaultSignatures: maybe<br>
DeriveAnyClass: maybe<br>
DeriveDataTypeable: maybe<br>
DeriveFoldable: maybe<br>
DeriveFunctor: maybe<br>
DeriveGeneric: maybe<br>
DeriveLift: maybe<br>
DeriveTraversable: maybe<br>
DerivingStrategies: maybe<br>
DerivingVia: maybe<br>
DisambiguateRecordFields: maybe<br>
DuplicateRecordFields: maybe<br>
EmptyCase: maybe<br>
EmptyDataDecls: maybe<br>
EmptyDataDeriving: maybe<br>
ExistentialQuantification: maybe<br>
ExplicitForAll: maybe<br>
ExplicitNamespaces: maybe<br>
ExtendedDefaultRules: maybe<br>
FlexibleContexts: maybe<br>
FlexibleInstances: maybe<br>
ForeignFunctionInterface: maybe<br>
FunctionalDependencies: maybe<br>
GADTSyntax: maybe<br>
GADTs: maybe<br>
GHCForeignImportPrim: maybe<br>
GeneralisedNewtypeDeriving: maybe<br>
HexFloatLiterals: maybe<br>
ImplicitParams: maybe<br>
ImportQualifiedPost: maybe<br>
ImpredicativeTypes: maybe<br>
IncoherentInstances: maybe<br>
InstanceSigs: maybe<br>
InterruptibleFFI: maybe<br>
KindSignatures: maybe<br>
LambdaCase: maybe<br>
LexicalNegation: maybe<br>
LiberalTypeSynonyms: maybe<br>
LinearTypes: maybe<br>
MagicHash: maybe<br>
MonadComprehensions: maybe<br>
MonadFailDesugaring: maybe<br>
MonoLocalBinds: maybe<br>
MultiParamTypeClasses: maybe<br>
MultiWayIf: maybe<br>
NPlusKPatterns: maybe<br>
NamedFieldPuns: maybe<br>
NamedWildCards: maybe<br>
NegativeLiterals: maybe<br>
NoImplicitPrelude: maybe<br>
NoMonomorphismRestriction: maybe<br>
NoPatternGuards: maybe<br>
NoTraditionalRecordSyntax: maybe<br>
NondecreasingIndentation: maybe<br>
NullaryTypeClasses: maybe<br>
NumDecimals: maybe<br>
NumericUnderscores: maybe<br>
OverlappingInstances: maybe<br>
OverloadedLabels: maybe<br>
OverloadedLists: maybe<br>
OverloadedStrings: maybe<br>
PackageImports: maybe<br>
ParallelListComp: maybe<br>
PartialTypeSignatures: maybe<br>
PatternSynonyms: maybe<br>
PolyKinds: maybe<br>
PostfixOperators: maybe<br>
QualifiedDo: maybe<br>
QuantifiedConstraints: maybe<br>
QuasiQuotes: maybe<br>
RankNTypes: maybe<br>
RebindableSyntax: maybe<br>
RecordWildCards: maybe<br>
RecursiveDo: maybe<br>
RoleAnnotations: maybe<br>
Safe: maybe<br>
ScopedTypeVariables: maybe<br>
StandaloneDeriving: maybe<br>
StandaloneKindSignatures: maybe<br>
StarIsType: maybe<br>
StaticPointers: maybe<br>
Strict: maybe<br>
StrictData: maybe<br>
TemplateHaskell: maybe<br>
TemplateHaskellQuotes: maybe<br>
TransformListComp: maybe<br>
Trustworthy: maybe<br>
TupleSections: maybe<br>
TypeApplications: maybe<br>
TypeFamilies: maybe<br>
TypeFamilyDependencies: maybe<br>
TypeInType: maybe<br>
TypeOperators: maybe<br>
TypeSynonymInstances: maybe<br>
UnboxedSums: maybe<br>
UnboxedTuples: maybe<br>
UndecidableInstances: maybe<br>
UndecidableSuperClasses: maybe<br>
UnicodeSyntax: maybe<br>
UnliftedFFITypes: maybe<br>
UnliftedNewtypes: maybe<br>
Unsafe: maybe<br>
ViewPatterns: maybe<br>
<br>
<br>
<br>
<br>
-- <br>
Joachim Breitner<br>
  <a href="mailto:mail@joachim-breitner.de" target="_blank">mail@joachim-breitner.de</a><br>
  <a href="http://www.joachim-breitner.de/" rel="noreferrer" target="_blank">http://www.joachim-breitner.de/</a><br>
<br>
<br>
_______________________________________________<br>
ghc-steering-committee mailing list<br>
<a href="mailto:ghc-steering-committee@haskell.org" target="_blank">ghc-steering-committee@haskell.org</a><br>
<a href="https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee" rel="noreferrer" target="_blank">https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee</a><br>
</blockquote></div>