<div dir="ltr">Just for the record, I voted "yes" on view patterns... :)</div><br><div class="gmail_quote"><div dir="ltr" class="gmail_attr">On Sun, Dec 6, 2020 at 2:32 PM 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">Hi,<br>
<br>
as the week ends, a quick update summarizing various inline “I’m<br>
convinced” vote updates from me:<br>
<br>
PolyKinds: yes<br>
  -- ^ Got convinced by Richard<br>
<br>
CUSKs: no<br>
StandaloneKindSignatures: yes<br>
  -- ^ A change from Haskell2010, but in a corner where the target<br>
       audience probably prefers progress<br>
<br>
MonomorphismRestriction: yes<br>
  -- ^ Is in Haskell2010, I have no reason to change that<br>
<br>
Controversial and/or pleaded against:<br>
<br>
ViewPatterns: no (convinced by Iavor)<br>
GADTs: no (too controversial)<br>
ExistentialQuantification: no (convinced by Richard)<br>
<br>
I continue to advocate for UnicodeSyntax, with the implied provision<br>
that -XGHC2021 will make GHC _accept_ Unicode syntax, but without<br>
writing error messages using it (i.e. no implied -fprint-unicode-<br>
syntax). I hope that at least those who have this on maybe (Arnaud,<br>
Iavor and SPJ) might be swayed by that clarification.<br>
<br>
<br>
<br>
Unchanged votes follow:<br>
<br>
PostfixOperators: yes<br>
<br>
NamedWildCards: yes<br>
 -- ^ Following Alejandro here: Seems safe and maybe more useful if<br>
      it can be used without friction.<br>
<br>
ForeignFunctionInterface: yes<br>
 -- ^ As Simon M points out, this is part of Haskell2010, and<br>
      was put on the ballet in this form (rather than<br>
      NoForeignFunctionInterface) by accident. I do not want to remove<br>
      anything that’s there (and I assume that nobody does without<br>
      making that very explicit).<br>
<br>
MonoLocalBinds: yes<br>
 -- ^ Not an expert, but it’s probably nice if turning on GADTs or<br>
      TypeFamilies (if they don't make it on their own) don’t change<br>
      seemingly unrelated part of the code.<br>
<br>
ImportQualifiedPost: yes<br>
 -- ^ Personally don’t care a lot about it, but I don’t want to veto it<br>
      either, so following Iavor here.<br>
<br>
HexFloatLiterals: yes<br>
 -- ^ More syntax for literals doesn’t hurt<br>
<br>
<br>
<br>
<br>
Unchanged votes follow:<br>
<br>
<br>
Let’s first get all those out of the way that are too contentions<br>
according to the data (with 2*no>yes votes):<br>
<br>
My starting point here was:<br>
*Main> putStr $ unlines [ ext ++ ": no" | E{..} <- M.elems exts, survey_no > 10, survey_no * 2 > survey_yes ]<br>
<br>
And that gave me the following:<br>
<br>
AllowAmbiguousTypes: no<br>
ApplicativeDo: no<br>
Arrows: no<br>
BlockArguments: no<br>
CApiFFI: no<br>
CPP: no<br>
ConstrainedClassMethods: no<br>
DatatypeContexts: no<br>
DisambiguateRecordFields: no<br>
DuplicateRecordFields: no<br>
ExplicitNamespaces: no<br>
ExtendedDefaultRules: no<br>
ImplicitParams: no<br>
ImpredicativeTypes: no<br>
IncoherentInstances: no<br>
InterruptibleFFI: no<br>
LiberalTypeSynonyms: no<br>
MagicHash: no<br>
MonadComprehensions: no<br>
NPlusKPatterns: no<br>
NoImplicitPrelude: no<br>
NoPatternGuards: no<br>
NoTraditionalRecordSyntax: no<br>
NullaryTypeClasses: no<br>
NumDecimals: no<br>
 -- ^ Unsure about this one<br>
OverlappingInstances: no<br>
OverloadedLabels: no<br>
OverloadedLists: no<br>
PackageImports: no<br>
ParallelListComp: no<br>
PartialTypeSignatures: no<br>
 -- ^ Unsure about this one, but trusting the crowd until convinced <br>
<br>
otherwise<br>
QuantifiedConstraints: no<br>
QuasiQuotes: no<br>
RebindableSyntax: no<br>
RecursiveDo: no<br>
 -- ^ I like that one. But probably not widespread enough.<br>
StaticPointers: no<br>
Strict: no<br>
StrictData: no<br>
TemplateHaskell: no<br>
TemplateHaskellQuotes: no<br>
TransformListComp: no<br>
Trustworthy: no<br>
TypeFamilyDependencies: no<br>
TypeInType: no<br>
TypeSynonymInstances: no<br>
UnboxedSums: no<br>
UnboxedTuples: no<br>
UndecidableInstances: no<br>
UndecidableSuperClasses: no<br>
Unsafe: no<br>
<br>
Actually, some of them I disagree with, and believe they are safe to<br>
turn on by default, and would be happy to, with sufficient committee<br>
support:<br>
<br>
NegativeLiterals: yes<br>
RoleAnnotations: yes<br>
UnicodeSyntax: yes<br>
  -- ^ I ❤ unicode<br>
UnliftedNewtypes: yes<br>
  -- ^ or is there something wrong with that?<br>
<br>
Now to those with at least 20% popularity:<br>
<br>
*Main> putStr $ unlines [ ext ++ ": no" | E{..} <- M.elems exts, not (survey_no > 10 && survey_no * 2 > survey_yes), 5 * survey_yes > survey_total  ]<br>
<br>
These I happily go with, until I learn otherwise:<br>
<br>
BangPatterns: yes<br>
ConstraintKinds: yes<br>
DataKinds: yes<br>
DeriveDataTypeable: yes<br>
DeriveFoldable: yes<br>
DeriveFunctor: yes<br>
DeriveGeneric: yes<br>
DeriveTraversable: yes<br>
DerivingStrategies: yes<br>
DerivingVia: yes<br>
FlexibleContexts: yes<br>
FlexibleInstances: yes<br>
GeneralisedNewtypeDeriving: yes<br>
KindSignatures: yes<br>
LambdaCase: yes<br>
MultiParamTypeClasses: yes<br>
RankNTypes: yes<br>
StandaloneDeriving: yes<br>
TupleSections: yes<br>
TypeApplications: yes<br>
TypeFamilies: yes<br>
TypeOperators: yes<br>
<br>
There are some where I disagree with the crowd:<br>
<br>
ScopedTypeVariables: no<br>
  -- ^ Too much of a kitchen sink, some edges are rough, and some of <br>
       its semantics (“bind type signatures unless in scope”) are being<br>
       questioned.<br>
<br>
       If we had the plain PatternSignatures as a separate extension,<br>
       I’d vote that in though. If ScopedTypeVariables doesn't make it<br>
       this round, I will revive #119 to get that.<br>
<br>
OverloadedStrings: no<br>
  -- ^ yes, has many fans. But I believe that many might actuall<br>
       use that although what they really want is a monomorphic<br>
<br>
         "foo" :: Text<br>
<br>
       and I wonder if there is a way to give them that.<br>
<br>
       Also, some report that too much polymorphism can hurt, e.g. in<br>
<br>
         is_vowel c = c `elem` "aeiou"<br>
<br>
       Three is also 12% Aloofness and 12% Contentionsness, which are<br>
       not to be dismissed.<br>
<br>
       So I am inclined to leave this out, for this round at least.<br>
<br>
MultiWayIf: no<br>
  -- ^ in light of discussion around a multi-case, maybe premature<br>
<br>
<br>
The remaining ones,<br>
*Main> putStr $ unlines [ ext ++ ": yes" | E{..} <- M.elems exts, not<br>
(survey_no > 10 && survey_no * 2 > survey_yes), not (5 * survey_yes ><br>
survey_total)  ]<br>
<br>
Kinda clear:<br>
<br>
BinaryLiterals: yes<br>
DeriveLift: yes<br>
EmptyCase: yes<br>
EmptyDataDecls: yes<br>
EmptyDataDeriving: yes<br>
ExplicitForAll: yes<br>
GADTSyntax: yes<br>
  -- ^ In case GADTs don’t make it<br>
InstanceSigs: yes<br>
NamedFieldPuns: yes<br>
NondecreasingIndentation: yes<br>
  -- ^ It’s Haskell98<br>
and the current default(!), but not Haskell2010?<br>
NumericUnderscores: yes<br>
RecordWildCards: yes<br>
UnliftedFFITypes: yes<br>
StarIsType: yes<br>
  -- ^ It’s the default now. Probably too early to turn off!<br>
<br>
DefaultSignatures: no<br>
  -- ^ Deriving via is probably preferrable these days<br>
DeriveAnyClass: no<br>
LinearTypes: no<br>
PatternSynonyms: no<br>
  -- ^ I like them, but maybe a bit too early<br>
MonadFailDesugaring: no<br>
  -- ^ This extension is temporary, and will be deprecated in a future<br>
release.<br>
QualifiedDo: no<br>
Safe: no<br>
<br>
No expert on these, will read your rationales:<br>
<br>
FunctionalDependencies: maybe<br>
GHCForeignImportPrim: maybe<br>
LexicalNegation: maybe<br>
  -- ^ Unsure about the maturity of the whitespace sensitiviy trend<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>