
Dear Comittee, for those who enjoy a little bit of random statistics on a weekend, let’s see how we are doing on the GHC20201 front. We got 5 votes already (thanks!). The table at https://github.com/ghc-proposals/ghc-proposals/blob/ghc2021/proposals/0000-g... is updated to reflect these votes, and sorted by number of votes received. If we’d stop voting now, and if the comittee were indeed only these 5 people, we’d accept everything with 4 or 5 votes. That would be these 35 extensions: *Main> putStrLn $ intercalate ", " $ sort [ ext | E{..} <- M.elems exts, votes >= 4] BangPatterns, BinaryLiterals, ConstraintKinds, DataKinds, DeriveDataTypeable, DeriveFoldable, DeriveFunctor, DeriveGeneric, DeriveLift, DeriveTraversable, DerivingStrategies, EmptyCase, EmptyDataDecls, EmptyDataDeriving, ExplicitForAll, FlexibleContexts, FlexibleInstances, GADTSyntax, GADTs, GeneralisedNewtypeDeriving, HexFloatLiterals, InstanceSigs, KindSignatures, LambdaCase, MultiParamTypeClasses, NamedFieldPuns, NegativeLiterals, NumericUnderscores, RecordWildCards, StandaloneDeriving, TupleSections, TypeApplications, TypeFamilies, TypeOperators, ViewPatterns Of these, the most conlater on.tentious are related to literals, followed by RecordWildCards: *Main Data.List> mapM_ putStrLn [ printf "%s: %0.2f" ext cont | E{..} <- M.elems exts, votes >= 4, survey_yes > 0, let cont = fromIntegral survey_no / fromIntegral survey_yes, then sortOn by Down cont, then take 3 ] NegativeLiterals: 0.58 HexFloatLiterals: 0.52 RecordWildCards: 0.39 (I think this is the first time in my life that I am using -XTransformListComp. Quite neat actually, maybe I need to change my vote here ;-) …) A number of extensions already have 4 or more “no”-votes and (pending changes to the ballots), are out: *Main Data.List> putStrLn $ intercalate ", " $ sort [ ext | E{..} <- M.elems exts, votes_total - votes >= 4] AllowAmbiguousTypes, ApplicativeDo, Arrows, BlockArguments, CApiFFI, CPP, CUSKs, DatatypeContexts, DefaultSignatures, DisambiguateRecordFields, DuplicateRecordFields, ExplicitNamespaces, ExtendedDefaultRules, ForeignFunctionInterface, FunctionalDependencies, GHCForeignImportPrim, ImplicitParams, ImpredicativeTypes, IncoherentInstances, InterruptibleFFI, LexicalNegation, LiberalTypeSynonyms, LinearTypes, MagicHash, MonadComprehensions, MultiWayIf, NPlusKPatterns, NamedWildCards, NoImplicitPrelude, NoPatternGuards, NoTraditionalRecordSyntax, NullaryTypeClasses, OverlappingInstances, OverloadedLabels, OverloadedLists, OverloadedStrings, PackageImports, ParallelListComp, PartialTypeSignatures, PatternSynonyms, QualifiedDo, QuantifiedConstraints, QuasiQuotes, RebindableSyntax, RecursiveDo, RoleAnnotations, Safe, StandaloneKindSignatures, StaticPointers, Strict, StrictData, TemplateHaskell, TemplateHaskellQuotes, TransformListComp, Trustworthy, TypeFamilyDependencies, TypeInType, UnboxedSums, UnboxedTuples, UndecidableInstances, UndecidableSuperClasses, UnliftedFFITypes, UnliftedNewtypes, Unsafe The most popular of these is (and I don’t even have to look that up) OverloadedStrings. I expect we might have the most discussion around that one. *Main Data.List> mapM_ putStrLn [ printf "%s: %0.2f" ext pop | E{..} <- M.elems exts, votes_total - votes >= 4, let pop = fromIntegral survey_yes / fromIntegral survey_total , then sortOn by Down pop, then take 5] OverloadedStrings: 0.45 MultiWayIf: 0.22 FunctionalDependencies: 0.17 DefaultSignatures: 0.16 PatternSynonyms: 0.14 In terms of process it has become apparent that I should have been more careful about excluding deprecated extensions from the ballots, to avoid confusion. If the final tally on them will look confused, we’ll still apply common sense (e.g. ForeignFunctionInterface is implied by Haskell2010, as Simon Marlow points out, and we won't “accidentially” remove it.) Anyways, that’s just a peek preview; with less than half of the votes in, a few things can still change. Keep it coming! Cheers, Joachim -- Joachim Breitner mail@joachim-breitner.de http://www.joachim-breitner.de/