<html><body>
        
        <div dir="ltr">-- the ones with comments</div><div dir="ltr">CUSKs: no<br></div><div dir="ltr">-- ^ according to the guide, this is superseded by StandaloneKindSignatures</div><div dir="ltr">ConstrainedClassMethods: yes<br></div><div dir="ltr">-- ^ it is implied by MultiParamTypeClasses anyway</div><div dir="ltr">DefaultSignatures: no<br></div><div dir="ltr">-- ^ as Joachim says, this should be succeeded by DerivingVia</div><div dir="ltr">-- ^ anyway, this is one required for the writer of the class, so no big deal</div><div dir="ltr">DeriveAnyClass: yes<br></div><div dir="ltr">-- ^ I think this makes no harm, and I tend to use deriving (ToJSON, FromJSON)</div><div dir="ltr">DerivingVia: yes<br></div><div dir="ltr">-- ^ even though it’s quite recent, I think it’s quite sensible and I don’t foresee many changes to it</div><div dir="ltr">DisambiguateRecordFields: no<br>DuplicateRecordFields: no<br></div><div dir="ltr">-- ^ we seem to still be working on this</div><div dir="ltr">FunctionalDependencies: maybe<br></div><div dir="ltr">-- ^ this is a hard one! Not so terrible since it’s only required by the creator of the class, not of the instances</div><div dir="ltr">MonadFailDesugaring: yes<br></div><div dir="ltr">-- ^ isn’t this the default nowadays?</div><div dir="ltr">MonoLocalBinds: maybe<br></div><div dir="ltr">-- ^ this is implied by GADTs, but otherwise we shouldn’t</div><div dir="ltr">MultiWayIf: no<br></div><div dir="ltr">-- ^ still in discussion</div><div dir="ltr">NamedWildCards: yes<br></div><div dir="ltr">-- ^ not many people use this, but I think this is the sane default</div><div dir="ltr">OverloadedLists: maybe<br>OverloadedStrings: maybe<br></div><div dir="ltr">-- ^ I would love to see these included, but I agree with the sentiment that they need more work</div><div dir="ltr">PartialTypeSignatures: no<br></div><div dir="ltr">-- ^ I really think that partial type signatures should not be accepted by default</div><div dir="ltr">QuantifiedConstraints: maybe<br></div><div dir="ltr">-- ^ too early, may want to refine this</div><div dir="ltr">ScopedTypeVariables: yes<br></div><div dir="ltr">-- ^ I think this is really well understood and people want it</div><div dir="ltr">PatternSynonyms: maybe<br></div><div dir="ltr">-- ^ we are still working out the edges of this</div><div dir="ltr"><br></div><div dir="ltr">-- these seem simple syntactic extensions</div><div dir="ltr">-- many of them bring compatibility with the syntax of Java-like languages</div><div dir="ltr">BinaryLiterals: yes<br></div><div dir="ltr">HexFloatLiterals: yes<br></div><div dir="ltr">NegativeLiterals: yes<br></div><div dir="ltr">NumDecimals: yes<br>NumericUnderscores: yes<br></div><div dir="ltr"><br></div><div dir="ltr"><div dir="ltr">-- too early but wouldn’t care to introduce it</div><div dir="ltr">StandaloneKindSignatures: maybe</div><div dir="ltr">ImportQualifiedPost: maybe</div></div><div dir="ltr"><br></div><div dir="ltr"><div dir="ltr">-- don’t know</div><div dir="ltr">ForeignFunctionInterface: maybe</div><div dir="ltr">GHCForeignImportPrim: maybe</div><div dir="ltr">InterruptibleFFI: maybe</div><div dir="ltr">LexicalNegation: maybe</div><div dir="ltr">NondecreasingIndentation: maybe</div><div dir="ltr">PackageImports: maybe</div><div dir="ltr">ParallelListComp: maybe</div><div dir="ltr">StarIsType: maybe<br></div><div dir="ltr">TransformListComp: maybe</div><div dir="ltr">UnliftedFFITypes: maybe<br>UnliftedNewtypes: maybe<br></div><div dir="ltr">UnicodeSyntax: maybe<br></div></div><div dir="ltr"><br></div><div dir="ltr">-- the rest</div><div dir="ltr">
    AllowAmbiguousTypes: no<br>ApplicativeDo: no<br>Arrows: no<br>BangPatterns: yes<br>BlockArguments: no<br>CApiFFI: no<br>CPP: no<br>ConstraintKinds: yes<br>DataKinds: yes<br>DatatypeContexts: no<br>DeriveDataTypeable: yes<br>DeriveFoldable: yes<br>DeriveFunctor: yes<br>DeriveGeneric: yes<br>DeriveLift: yes<br>DeriveTraversable: yes<br>DerivingStrategies: yes<br>EmptyCase: yes<br>EmptyDataDecls: yes<br>EmptyDataDeriving: yes<br>ExistentialQuantification: yes<br>ExplicitForAll: yes<br>ExplicitNamespaces: no<br>ExtendedDefaultRules: no<br>FlexibleContexts: yes<br>FlexibleInstances: yes<br>GADTSyntax: yes</div><div dir="ltr">-- ^ implied by GADTs anyway<br>GADTs: yes<br>GeneralisedNewtypeDeriving: yes<br>ImplicitParams: no<br>ImpredicativeTypes: no<br>IncoherentInstances: no<br>InstanceSigs: yes<br>KindSignatures: yes<br>LambdaCase: yes<br>LiberalTypeSynonyms: no<br>LinearTypes: no<br>MagicHash: no<br>MonadComprehensions: no<br>MultiParamTypeClasses: yes<br>NPlusKPatterns: no<br>NamedFieldPuns: yes<br>NoImplicitPrelude: no<br>NoMonomorphismRestriction: yes</div><div dir="ltr">NoPatternGuards: no<br>NoTraditionalRecordSyntax: no<br>NullaryTypeClasses: yes<br>OverlappingInstances: no<br>OverloadedLabels: no<br>PolyKinds: yes<br>PostfixOperators: yes<br>QualifiedDo: no<br>QuasiQuotes: no<br>RankNTypes: no<br>RebindableSyntax: no<br>RecordWildCards: yes<br>RecursiveDo: no<br>RoleAnnotations: no<br>Safe: no<br>StandaloneDeriving: yes<br>StaticPointers: no<br>Strict: no<br>StrictData: no<br>TemplateHaskell: no<br>TemplateHaskellQuotes: no<br>Trustworthy: no</div><div dir="ltr">TupleSections: yes<br>TypeApplications: yes<br>TypeFamilies: yes<br>TypeFamilyDependencies: no<br>TypeInType: maybe<br>TypeOperators: yes<br>TypeSynonymInstances: yes<br>UnboxedSums: no<br>UnboxedTuples: no<br>UndecidableInstances: no<br>UndecidableSuperClasses: no<br>Unsafe: no<br>ViewPatterns: yes</div><div dir="ltr"><br>
    <div class="gmail_quote">
        <div dir="ltr" class="gmail_attr">On 24 Nov 2020 at 10:34:18, 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">
            <div>
    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><blockquote type="cite"> Richard wrote:<br></blockquote><blockquote type="cite"> DependentHaskell: yes<br></blockquote><blockquote type="cite"> Rationale: See my thesis<br></blockquote><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">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">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">mail@joachim-breitner.de</a><br>  <a href="http://www.joachim-breitner.de/">http://www.joachim-breitner.de/</a><br><br><br>_______________________________________________<br>ghc-steering-committee mailing list<br><a href="mailto:ghc-steering-committee@haskell.org">ghc-steering-committee@haskell.org</a><br><a href="https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee">https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee</a><br>
</div>
        </blockquote>
    </div>
</div>
    

    
</body></html>