[ghc-steering-committee] #380 GHC2021: Current status

Simon Marlow marlowsd at gmail.com
Thu Dec 3 11:26:09 UTC 2020


I agree with Simon that we must have GADTs!

I would be slightly sad to see ViewPatterns go in, for two reasons: (1)
PatternSynonyms covers some of the use cases but by abstracting over data
constructors, which doesn't require clients to adopt a non-idiomatic
pattern matching style, and (2) for the rest of the use cases, IMO this
design would be better:
https://gitlab.haskell.org/ghc/ghc/-/wikis/view-patterns-alternative

Cheers
Simon

On Thu, 3 Dec 2020 at 09:31, Joachim Breitner <mail at joachim-breitner.de>
wrote:

> Dear Committee,
>
>
> we have 9 votes in. Dear Cale and Eric, can we have your votes please?
>
> As always, the table
>
> https://github.com/ghc-proposals/ghc-proposals/blob/ghc2021/proposals/0000-ghc2021.rst#data
> has the current data.
>
> We had the most discussion so far about:
>
>  * The innnocence of PostfixOperators
>  * The effect of UnicodeSyntax on error messages
>  * Whether InstanceSigs is a good design
>  * Whether OverloadedString is harmless enough.
>
> I see that three is less clear signal on odd extensions that are
> obsolete, on by default, implied by others etc. That’s probably fine
> and no need to worry; some of them will be resolved by virtue of being
> implied by others. We can also sanity-check the final result, and
> include all implied ones in the final design.
>
> So where do we stand?
>
> Applying the actual quota of ⅔ out of 11, i.e. 8 votes, these would go
> in no matter how Cale and Eric vote:
>
>    BangPatterns, BinaryLiterals, ConstraintKinds, DeriveDataTypeable,
>    DeriveFoldable, DeriveFunctor, DeriveGeneric, DeriveLift,
>    DeriveTraversable, EmptyCase, EmptyDataDecls, EmptyDataDeriving,
>    ExplicitForAll, FlexibleContexts, FlexibleInstances, GADTSyntax,
>    HexFloatLiterals, ImportQualifiedPost, KindSignatures,
>    MultiParamTypeClasses, NamedFieldPuns, NumericUnderscores,
>    StandaloneDeriving, ViewPatterns
>
> The following have 6 or 7 votes, i.e. they’d go in if we extrapolate
> from the current votes:
>
>    ConstrainedClassMethods, DerivingStrategies,
>    ExistentialQuantification, GeneralisedNewtypeDeriving, InstanceSigs,
>    NegativeLiterals, PostfixOperators, RankNTypes, RecordWildCards,
>    ScopedTypeVariables, TupleSections, TypeApplications, TypeFamilies,
>    TypeOperators, TypeSynonymInstances
>
>    These extensions are short one vote:
>
>    DataKinds, DerivingVia, GADTs, LambdaCase, PolyKinds
>
>
>
>    So how sad would we all be? This is the sadness report for each
>    committee member, showing the symmetric difference between their ballot
>    and the (extrapolated) result.
>
>
>    alejandro
>    would miss:
>    DataKinds, DerivingVia, GADTs, LambdaCase, MonadFailDesugaring,
>    NamedWildCards, NoMonomorphismRestriction, NullaryTypeClasses,
>    NumDecimals, OverloadedLists, OverloadedStrings, PolyKinds,
>    StandaloneKindSignatures
>    doesn’t want:
>    RankNTypes
>
>    arnaud
>    would miss:
>    Arrows, ExplicitNamespaces, ForeignFunctionInterface,
>    FunctionalDependencies, GADTs, MonadFailDesugaring, MonoLocalBinds,
>    PartialTypeSignatures, StarIsType, TypeFamilyDependencies
>    doesn’t want:
>    ExistentialQuantification, ImportQualifiedPost, InstanceSigs,
>    NamedFieldPuns, RankNTypes, RecordWildCards, ScopedTypeVariables,
>    TupleSections, TypeSynonymInstances
>
>    iavor
>    would miss:
>    BlockArguments, MultiWayIf, NoMonomorphismRestriction,
>    NullaryTypeClasses, OverloadedStrings, ParallelListComp, RecursiveDo
>    doesn’t want:
>    ConstrainedClassMethods, ConstraintKinds, DeriveFoldable,
>    DeriveFunctor, DeriveTraversable, DerivingStrategies, EmptyCase,
>    GADTSyntax, GeneralisedNewtypeDeriving, InstanceSigs, KindSignatures,
>    NegativeLiterals, PostfixOperators, TupleSections, TypeApplications,
>    TypeFamilies, TypeOperators
>
>    joachim
>    would miss:
>    DataKinds, DerivingVia, ForeignFunctionInterface, GADTs, LambdaCase,
>    MonoLocalBinds, NamedWildCards, NondecreasingIndentation,
>    RoleAnnotations, StarIsType, UnicodeSyntax, UnliftedFFITypes,
>    UnliftedNewtypes
>    doesn’t want:
>    ConstrainedClassMethods, ScopedTypeVariables, TypeSynonymInstances
>
>    richard
>    would miss:
>    BlockArguments, DefaultSignatures, DerivingVia,
>    DisambiguateRecordFields, ExplicitNamespaces, LexicalNegation,
>    NamedWildCards, NumDecimals, ParallelListComp, PolyKinds,
>    RoleAnnotations, StandaloneKindSignatures, TemplateHaskellQuotes,
>    UnicodeSyntax, UnliftedNewtypes
>    doesn’t want:
>    NegativeLiterals, RecordWildCards, ScopedTypeVariables, TypeFamilies
>
>    simonm
>    would miss:
>    DataKinds, DefaultSignatures, ForeignFunctionInterface, GADTs,
>    LambdaCase, LiberalTypeSynonyms, MonoLocalBinds, MultiWayIf,
>    NoMonomorphismRestriction, NondecreasingIndentation, NumDecimals,
>    OverloadedStrings, PatternSynonyms, PolyKinds, UnicodeSyntax
>    doesn’t want:
>    DeriveLift, DerivingStrategies, NumericUnderscores, TypeApplications,
>    TypeOperators, ViewPatterns
>
>    spj
>    would miss:
>    MonoLocalBinds, NoMonomorphismRestriction, NullaryTypeClasses,
>    OverloadedLists, OverloadedStrings, ParallelListComp, PolyKinds,
>    RecursiveDo, RoleAnnotations, StandaloneKindSignatures, StarIsType
>    doesn’t want:
>    DerivingStrategies, GeneralisedNewtypeDeriving, NegativeLiterals,
>    RecordWildCards, TupleSections, TypeFamilies
>
>    tom
>    would miss:
>    BlockArguments, DataKinds, DefaultSignatures, DerivingVia,
>    DisambiguateRecordFields, DuplicateRecordFields, ExplicitNamespaces,
>    FunctionalDependencies, LambdaCase, LexicalNegation,
>    LiberalTypeSynonyms, MagicHash, MultiWayIf, NamedWildCards,
>    NullaryTypeClasses, NumDecimals, PackageImports, ParallelListComp,
>    PolyKinds, QuasiQuotes, RoleAnnotations, StandaloneKindSignatures,
>    TemplateHaskell, TemplateHaskellQuotes, TypeFamilyDependencies,
>    UnboxedSums, UnboxedTuples, UnicodeSyntax, UnliftedNewtypes
>    doesn’t want:
>    none!
>
>    vitaly
>    would miss:
>    DataKinds, DerivingVia, GADTs, LambdaCase, MonadFailDesugaring,
>    StarIsType
>    doesn’t want:
>    ConstrainedClassMethods, ExistentialQuantification, PostfixOperators
>
>
>    --
>    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/20201203/6d3f9fc1/attachment.html>


More information about the ghc-steering-committee mailing list