[ghc-steering-committee] #380 GHC2021: Voting starts

Eric Seidel eric at seidel.io
Fri Dec 4 02:19:58 UTC 2020


Here are my votes, sorry to be so slow!

## syntax

BangPatterns: yes
BinaryLiterals: yes
EmptyCase: yes
EmptyDataDecls: yes
ExplicitForAll: yes
ExplicitNamespaces: yes
GADTSyntax: yes
HexFloatLiterals: yes
ImportQualifiedPost: yes
InstanceSigs: yes
KindSignatures: yes
MonadFailDesugaring: yes
NegativeLiterals: yes
NumericUnderscores: yes
PatternSynonyms: yes
PostfixOperators: yes
TypeApplications: yes

OverloadedLists: yes
OverloadedStrings: yes
  I have to enable OverloadedStrings regularly,
  and it's one of the few extensions GHC
  cannot suggest, which trips up my editor, and by
  extension me, on a regular basis. I admit that I've
  never actually used OverloadedLists, but I like it
  as a direction for the language.

BlockArguments: maybe
  I like this one, but it feels a bit recent.
MonadComprehensions: maybe
NumDecimals: maybe
ParallelListComp: maybe
RecursiveDo: maybe

ApplicativeDo: no
Arrows: no
LexicalNegation: no
NPlusKPatterns: no
NondecreasingIndentation: no
OverloadedLabels: no
QualifiedDo: no
RebindableSyntax: no
StarIsType: no
  It's marked legacy syntax, let's be bold and get rid of it.
TransformListComp: no
TupleSections: no
  This conflicts with proposals around trailing commas
  that we may want to consider.
UnicodeSyntax: no
ViewPatterns: no

LambdaCase: no
MultiWayIf: no
  I like both of these, but I've been convinced to wait out
  the current discussion around alternate designs.


## types

ConstrainedClassMethods: yes
ConstraintKinds: yes
DataKinds: yes
DefaultSignatures: yes
ExistentialQuantification: yes
  This is occasionally useful, and purely opt-in.
FlexibleContexts: yes
FlexibleInstances: yes
FunctionalDependencies: yes
GADTs: yes
MonoLocalBinds: yes
  I think I actually prefer this even in the absence of GADTs.
MultiParamTypeClasses: yes
PolyKinds: yes
RankNTypes: yes
RoleAnnotations: yes
ScopedTypeVariables: yes
StandaloneKindSignatures: yes
TypeFamilies: yes
TypeFamilyDependencies: yes
TypeOperators: yes
TypeSynonymInstances: yes

NamedWildCards: yes
PartialTypeSignatures: yes
  These are useful for debugging and warned on by default.

UndecidableInstances: maybe
UndecidableSuperClasses: maybe
  Is it really that bad if we allow the possibility of the
  type checker looping? This does not introduce unsoundness.

CUSKs: no
DatatypeContexts: no
ImplicitParams: no
ImpredicativeTypes: no
IncoherentInstances: no
LiberalTypeSynonyms: no
LinearTypes: no
NullaryTypeClasses: no
OverlappingInstances: no
QuantifiedConstraints: no
TypeInType: no


## records

DisambiguateRecordFields: yes
  This only allows unambiguous uses of fields,
  so it seems very safe.

NamedFieldPuns: yes
RecordWildCards: yes
  I know these are controversial, but they're opt-in
  and super useful.

DuplicateRecordFields: maybe
  There are some valid critiques of this extension,
  but I think it's still generally useful, at least
  until RecordDotSyntax is implemented and stable.


## deriving

DeriveDataTypeable: yes
DeriveFoldable: yes
DeriveFunctor: yes
DeriveGeneric: yes
DeriveLift: yes
DeriveTraversable: yes
DerivingVia: yes
GeneralisedNewtypeDeriving: yes
StandaloneDeriving: yes

DerivingStrategies: maybe

DeriveAnyClass: no
EmptyDataDeriving: no


## low-level / ffi

CApiFFI: no
ForeignFunctionInterface: no
  I know this is part of Haskell2010, but I feel like
  FFI is niche and low-level enough to warrant a marker
GHCForeignImportPrim: no
InterruptibleFFI: no
MagicHash: no
UnboxedSums: no
UnboxedTuples: no
UnliftedFFITypes: no
UnliftedNewtypes: no


## other

AllowAmbiguousTypes: no
CPP: no
ExtendedDefaultRules: no
NoImplicitPrelude: no
NoMonomorphismRestriction: no
NoPatternGuards: no
NoTraditionalRecordSyntax: no
PackageImports: no
QuasiQuotes: no
Safe: no
StaticPointers: no
Strict: no
StrictData: no
TemplateHaskell: no
TemplateHaskellQuotes: no
Trustworthy: no
Unsafe: no


On Thu, Dec 3, 2020, at 11:15, Alejandro Serrano Mena wrote:
>  Here are my new votes, after several discussions, and reading a bit 
> about defaults (like for StarIsType) in the User Guide.
> 
> -- the ones with comments
> CUSKs: no
> -- ^ according to the guide, this is superseded by 
> StandaloneKindSignatures
> ConstrainedClassMethods: yes
> -- ^ it is implied by MultiParamTypeClasses anyway
> DefaultSignatures: no
> -- ^ as Joachim says, this should be succeeded by DerivingVia
> -- ^ anyway, this is one required for the writer of the class, so no 
> big deal
> DeriveAnyClass: no
> -- ^ given our discussion
> DerivingVia: yes
> -- ^ even though it’s quite recent, I think it’s quite sensible and I 
> don’t foresee many changes to it
> DisambiguateRecordFields: no
> DuplicateRecordFields: no
> -- ^ we seem to still be working on this
> FunctionalDependencies: maybe
> -- ^ this is a hard one! Not so terrible since it’s only required by 
> the creator of the class, not of the instances
> MonadFailDesugaring: yes
> -- ^ isn’t this the default nowadays?
> MonoLocalBinds: yes
> -- ^ this is implied by GADTs and TypeFamilies
> MultiWayIf: no
> -- ^ still in discussion
> NamedWildCards: yes
> -- ^ not many people use this, but I think this is the sane default
> OverloadedLists: yes
> OverloadedStrings: yes
> -- ^ I would love to see these included, but I agree with the sentiment 
> that they need more work
> PartialTypeSignatures: no
> -- ^ I really think that partial type signatures should not be accepted 
> by default
> QuantifiedConstraints: no
> -- ^ too early
> ScopedTypeVariables: yes
> -- ^ I think this is really well understood and people want it
> PatternSynonyms: maybe
> -- ^ we are still working out the edges of this
> ForeignFunctionInterface: yes
> RankNTypes: yes
> UnicodeSyntax: yes
> -- ^ following Joachim’s suggestion: enable this for syntax but *not* 
> for error messages
> TypeInType: maybe
> -- ^ this simply implies PolyKinds, DataKinds, KindSignatures, 
> according to the documentation
> StarIsType: yes
> -- ^ this is on by default, and I think it would be very confusing to 
> stop treating “*” different from “Type” as this moment
> 
> -- these seem simple syntactic extensions
> -- many of them bring compatibility with the syntax of Java-like languages
> BinaryLiterals: yes
> HexFloatLiterals: yes
> NegativeLiterals: yes
> NumDecimals: yes
> NumericUnderscores: yes
> 
> -- too early but wouldn’t care to introduce it
> StandaloneKindSignatures: yes
> ImportQualifiedPost: yes
> 
> -- don’t know
> GHCForeignImportPrim: maybe
> InterruptibleFFI: maybe
> LexicalNegation: maybe
> NondecreasingIndentation: maybe
> PackageImports: maybe
> ParallelListComp: maybe
> TransformListComp: maybe
> UnliftedFFITypes: maybe
> UnliftedNewtypes: maybe
> 
> -- the rest
> AllowAmbiguousTypes: no
> ApplicativeDo: no
> Arrows: no
> BangPatterns: yes
> BlockArguments: no
> CApiFFI: no
> CPP: no
> ConstraintKinds: yes
> DataKinds: yes
> DatatypeContexts: no
> DeriveDataTypeable: yes
> DeriveFoldable: yes
> DeriveFunctor: yes
> DeriveGeneric: yes
> DeriveLift: yes
> DeriveTraversable: yes
> DerivingStrategies: yes
> EmptyCase: yes
> EmptyDataDecls: yes
> EmptyDataDeriving: yes
> ExistentialQuantification: yes
> ExplicitForAll: yes
> ExplicitNamespaces: no
> ExtendedDefaultRules: no
> FlexibleContexts: yes
> FlexibleInstances: yes
> GADTSyntax: yes
> -- ^ implied by GADTs anyway
> GADTs: yes
> GeneralisedNewtypeDeriving: yes
> ImplicitParams: no
> ImpredicativeTypes: no
> IncoherentInstances: no
> InstanceSigs: yes
> KindSignatures: yes
> LambdaCase: yes
> LiberalTypeSynonyms: no
> LinearTypes: no
> MagicHash: no
> MonadComprehensions: no
> MultiParamTypeClasses: yes
> NPlusKPatterns: no
> NamedFieldPuns: yes
> NoImplicitPrelude: no
> NoMonomorphismRestriction: yes
> NoPatternGuards: no
> NoTraditionalRecordSyntax: no
> NullaryTypeClasses: yes
> OverlappingInstances: no
> OverloadedLabels: no
> PolyKinds: yes
> PostfixOperators: yes
> QualifiedDo: no
> QuasiQuotes: no
> RebindableSyntax: no
> RecordWildCards: yes
> RecursiveDo: no
> RoleAnnotations: no
> Safe: no
> StandaloneDeriving: yes
> StaticPointers: no
> Strict: no
> StrictData: no
> TemplateHaskell: no
> TemplateHaskellQuotes: no
> Trustworthy: no
> TupleSections: yes
> TypeApplications: yes
> TypeFamilies: yes
> TypeFamilyDependencies: no
> TypeOperators: yes
> TypeSynonymInstances: yes
> UnboxedSums: no
> UnboxedTuples: no
> UndecidableInstances: no
> UndecidableSuperClasses: no
> Unsafe: no
> ViewPatterns: yes
> _______________________________________________
> ghc-steering-committee mailing list
> ghc-steering-committee at haskell.org
> https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee
>


More information about the ghc-steering-committee mailing list