
Hello,
these took me way too long :) Here we go:
*Module System=============*
ImportQualifiedPost: yes
-- ^ This is relatively new, but it seems quite simple, and it does make
-- things read nicer.
-- | These are only needed under very special circumstances,
-- so it's good to be explicit:
PackageImports: no
NoImplicitPrelude: no
*Notation========*
BlockArguments: yes
-- ^ I use this all the time.
MultiWayIf: yes
-- ^ This is nice on occasion, and it does not seem to conflict with
-- anything. Certainly nicer than the alternative `case () of _ | ... `:
LambdaCase: maybe
-- ^ Personally I don't use this, but I know a lot of folks like it,
-- so I'd be OK with it being enabled.
-- | The various literal notations seem useful when you need them
-- and don't conflict with anything.
BinaryLiterals: yes
HexFloatLiterals: yes
NumericUnderscores: yes
NumDecimals: maybe
-- ^ | Not too sure about this last one, I've never used, but it
-- I could see it being useful on occasion.
OverloadedStrings: yes
-- ^ | I use this a lot, and would be OK with it being on all the time.
OverloadedLists: maybe
-- | ^ I've never used this, but I could see it potentially being useful.
OverloadedLabels: no
-- | ^ This one seems for experimenting with various new features
-- (e.g., record selectors), so it seems reasonable to turn it on only
-- when it is needed.
EmptyCase: maybe
-- ^ Seems like a nicer notation for forcing `Void` values.
-- I agree that it is odd that it is strict. OTOH, it'd be quite useless
-- if it was lazy, so I could go either way.
-- | I haven't really used any of those, so I could go either way:
PostfixOperators: maybe
LexicalNegation: maybe
UnicodeSyntax: maybe
NegativeLiterals: no
-- ^ It seems that `LexicalNegation` might be a nicer way to do this?
TupleSections: maybe
-- ^ I don't use this often, but I'd use it more often if it was on by
default.
ImplicitParams: no
-- ^ I find these quite useful on occasion, but it does seem reasonable
-- to be explicit when you need them.
ParallelListComp: yes
-- ^ I find these to be a very nice generalization to list comprehensions
-- that makes some code way more readable than using `zip/zipWith`, just
-- like comprehensions are often nicer than `map` or `concatMap`
RecursiveDo: yes
-- ^ Seems useful when you need it, and it doesn't clash with anything,
-- so I see no reason to not have it on all the time.
TransformListComp: no
-- ^ In my mind these are just a bit too much syntactic sugar.
Arrows: no
-- ^ It's not used a lot, not terribly useful and overall feels "clunky".
ApplicativeDo: maybe
-- ^ I think the core of this extension is really useful,
-- but I would prefer a simpler syntactic version of it,
-- without the various transformations assuming that some laws hold.
QualifiedDo: no
-- ^ This is neat, but it is too new to be on by default.
MonadComprehensions: maybe
-- ^ I never really use these.
-- On occasion I've wanted `ApplicativeComprehensions` though.
NondecreasingIndentation: no
-- ^ This always felt like a hack to me.
RebindableSyntax: no
-- ^ This is a very special case thing
ExplicitNamespaces: maybe
-- ^ We need this if we also want pattern synonyms.
*Data Types==========*
DatatypeContexts: no
-- ^ These are not really used much, and usually don't do what people
expect.
ExistentialQuantification: yes
-- ^ This is quite useful, and has been around for a long time.
EmptyDataDecls: yes
-- ^ Seems more consistent to allow this
RoleAnnotations: no
-- ^ This only makes sense with `GeneralisedNewtypeDeriving` which
-- I don't think should be on by default.
StrictData: no
-- ^ This is very unHaskell :)
GADTSyntax: maybe
-- ^ I personally don't use this, but I know some folks like to write
-- their `data` declarations in this notation.
GADTs: no
-- ^ These can be useful, but it seems reasonable to enable them when
-- you need them, as they bring in quite a lot of machinery with them.
*Patterns and Guards===================*
BangPatterns: yes
-- ^ Seem to be useful, and quite popular.
ViewPatterns: yes
-- ^ Useful on occasion, and I don't think calling out the extension
-- explicitly helps anyone.
PatternSynonyms: maybe
-- ^ These are quite useful, but I am not sure how stable is theiry design.
NoPatternGuards: no
-- ^ Conflicts with Haskell2010
NPlusKPatterns: no
-- ^ Conflicts with Haskell2010
*Records=======*
-- | I find these two very useful when working with records,
-- especially large ones, and declaring the extension really adds no
-- information:
NamedFieldPuns: yes
RecordWildCards: yes
-- | These seem to be largely about experimenting with new record
system, and I don't think any of them are quite ready to be on by default:
DisambiguateRecordFields: no
DuplicateRecordFields: no
NoTraditionalRecordSyntax: no
*Deriving=======*
-- | Declaring these as extensions explicitly adds very little information.
DeriveGeneric: yes
DeriveLift: yes
DeriveDataTypeable: yes
EmptyDataDeriving: yes
-- ^ Useful for consistency
StandaloneDeriving: yes
-- ^ I find this quite useful on occasion, and does not conflict with
anything
-- | I think the rest of the deriving extensions are not particularly
orthogonal
at the moment, so I don't think we should have them on by default, at least
not yet, even though I find some of them quite useful.
DeriveFunctor: no
DeriveFoldable: no
DeriveTraversable: no
DerivingStrategies: no
DerivingVia: no
GeneralisedNewtypeDeriving: no
DeriveAnyClass: no
*Class System============*
MultiParamTypeClasses: yes
-- ^ Seems like a natural extension and does not really conflict with
anything
NullaryTypeClasses: yes
-- ^ Seems like a natural extension and does not really conflict with
anything
ConstraintKinds: maybe
-- ^ These seem like a very nice fit with the rest of the kind system,
-- so I think we can enable them. The reason I wrote `maybe` is due to
-- the confusion between constraints and tuples.
-- | These 3 seem to be quite common. There are some reasons to be careful
-- when writing `FlexibleInstances`, but it seems that having the extension
-- does not really help much with those.
TypeSynonymInstances: yes
FlexibleInstances: yes
FlexibleContexts: yes
-- | I haven't really used these much, so I don't have a strong opinion:
ConstrainedClassMethods: maybe
DefaultSignatures: maybe
InstanceSigs: maybe
ExtendedDefaultRules: maybe
FunctionalDependencies: no
-- ^ While I quite like the general idea here, I don't think we should
-- have these on by default.
QuantifiedConstraints: no
-- ^ These seem neat, but are quite new to be on by default.
UndecidableInstances: no
-- ^ These are a very special case, and ideally should be specified
-- on a per instance basis.
IncoherentInstances: no
-- ^ Why do we even have this? :)
UndecidableSuperClasses: no
-- ^ These are a very special case.
OverlappingInstances: no
-- ^ This has been subsumed by per-instance pragmas
*Types=====*
RankNTypes: yes
-- ^ These are useful and have been around for a long time. The design
-- seems to work well.
-- | These two seem useful, but I am not sure if they should be on by
default.
-- If so, though, it makes sense to have both of them on.
StandaloneKindSignatures: maybe
KindSignatures: maybe
LiberalTypeSynonyms: maybe
-- ^ These seem useful, but can lead to some rather confusing situations
-- where types that look "normal" don't behave as you'd expect
-- (e..g, writing `[T]` fails because `T` happens to have `forall` in it)
-- | These two go together and seem quite useful, especially when writing
-- local type signatures.
ScopedTypeVariables: yes
ExplicitForAll: yes
AllowAmbiguousTypes: no
-- ^ Often these are unintentional, and are due to a mistake in the program.
ImpredicativeTypes: no
-- ^ These are being currently redesigned, so not ready.
MonoLocalBinds: maybe
-- ^ I don't know if this one is on by default or not already...
NoMonomorphismRestriction: yes
-- ^ The monomrphism restriction seems to cause a lot of confusion, and I
-- am not sure that it's helped that much with efficiency
-- | Doesn't really seem to be commonly used.
PartialTypeSignatures: no
NamedWildCards: no
LinearTypes: no
-- ^ Too new to be standardized
TypeApplications: no
-- ^ This one is quite useful, bit it seems that its design and how many
users
-- understand it don't match, so maybe there is more work to be done.
-- | These are all related to type-level programming, and while I don't
think
-- they should be on by default, it might be useful to have a single flag
that
-- turns a bunch of them on.
PolyKinds: no
TypeOperators: no
StarIsType: maybe
TypeFamilies: no
TypeFamilyDependencies: no
DataKinds: no
*FFI===*
I don't think the FFI should be on by default, as it is used relatively
infrequently, although it might be nice if `ForeignFunctionInterface`
implied `CApiFFI`
ForeignFunctionInterface: no
CApiFFI: no
GHCForeignImportPrim: no
InterruptibleFFI: no
UnliftedFFITypes: no
StaticPointers: no
*Low Level=========*
These are for low-level hacking, so I don't think they should be
on by default. However, I wouldn't mind having a flag that enabled
all of them with a single extension (e.g., `UnliftedTypes`)
UnboxedSums: no
UnboxedTuples: no
MagicHash: no
UnliftedNewtypes: no
*Macros======*
CPP: no
This is quite specialized, so it seems reasonable to be explicit about it.
I don't think these should be on by default, but I wouldn't mind it
if `TemplateHaskell` implied `QuasiQuotes`, so that when I use TH
I just need to turn on a single extension.:
TemplateHaskell: no
TemplateHaskellQuotes: no
QuasiQuotes: no
*Other=====*
-- | These are part of Safe Haskell and are there to be written explicitly
Unsafe: no
Safe: no
Trustworthy: no
Strict: no
-- ^ This is not Haskell! :-)
*Obsolete/Deprecated===================*
CUSKs: no
TypeInType: no
MonadFailDesugaring: maybe
On Tue, Nov 24, 2020 at 1:34 AM Joachim Breitner
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-g... 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.... 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