[ghc-steering-committee] #380 GHC2021: Vote update

Iavor Diatchki iavor.diatchki at gmail.com
Mon Dec 7 04:57:43 UTC 2020


Just for the record, I voted "yes" on view patterns... :)

On Sun, Dec 6, 2020 at 2:32 PM Joachim Breitner <mail at joachim-breitner.de>
wrote:

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


More information about the ghc-steering-committee mailing list