Proposal: Add 'Foldable1' to base

Simon Jakobi simon.jakobi at googlemail.com
Thu Dec 10 11:26:23 UTC 2020


+1

Am Do., 10. Dez. 2020 um 08:20 Uhr schrieb Reed Mullanix
<reedmullanix at gmail.com>:
>
> Seems reasonable to me! I definitely agree that we ought to add a
> strict foldMap1 to the version found in semigroupoids.
>
> On Wed, Dec 9, 2020 at 11:08 PM David Feuer <david.feuer at gmail.com> wrote:
> >
> > That seems rather large to me, and some of those methods don't have much if any historical usage. I'd recommend starting with a slightly smaller class. It's always easier to add more later than to remove. My suggestion:
> >
> >      foldMap1 :: Semigroup m => (a -> m) -> t a -> m
> >
> >      foldMap1' :: Semigroup m => (a -> m) -> t a -> m
> >
> >      toNonEmpty :: t a -> NonEmpty a
> >
> > The rest can be exported as functions, rather than methods, to begin with.
> >
> > On Thu, Dec 10, 2020, 1:38 AM Reed Mullanix <reedmullanix at gmail.com> wrote:
> >>
> >> With the recent discussion around the addition of 'intersection' to containers,
> >> I think it might be a good time to re-open the discussion surrounding adding
> >> 'Foldable1' to base.
> >>
> >> For context, 'Foldable1' would be a subclass of 'Foldable' that abstracts
> >> folds over non-empty containers. Alternatively, it can be seen as a method
> >> of combining together the elements of a container using a semigroup.
> >> The contents of this class have been discussed previously (See [1,2]),
> >> and the version presented in this proposal is taken from [1].
> >>
> >>   class Foldable t => Foldable1 t where
> >>      {-# MINIMAL foldMap1 | foldr1map #-}
> >>
> >>      fold1 :: Semigroup m => t m -> m
> >>
> >>      -- the defining member, like foldMap but only asking for Semigroup
> >>      foldMap1 :: Semigroup m => (a -> m) -> t a -> m
> >>
> >>      -- strict foldMap1, cf foldMap'
> >>      foldMap1' :: Semigroup m => (a -> m) -> t a -> m
> >>
> >>      -- analogue of toList
> >>      toNonEmpty :: t a -> NonEmpty a
> >>
> >>      -- left&right, strict&non-strict folds
> >>      foldr1  :: (a -> a -> a) -> t a -> a
> >>      foldr1' :: (a -> a -> a) -> t a -> a
> >>      foldl1  :: (a -> a -> a) -> t a -> a
> >>      foldl1' :: (a -> a -> a) -> t a -> a
> >>
> >>      -- these can have efficient implementation for NonEmptySet
> >>      maximum1 :: Ord a => t a -> a
> >>      minimum1 :: Ord a => t a -> a
> >>
> >>      -- head1 have efficient implementation for NonEmpty and Tree
> >>      -- last1 for symmetry
> >>      head1 :: t a -> a
> >>      last1 :: t a -> a
> >>
> >>      -- fold variants with premap.
> >>      -- Without this map, we cannot implement foldl using foldr etc.
> >>      foldrMap1  :: (a -> b) -> (b -> b -> b) -> t a -> b
> >>      foldlMap1' :: (a -> b) -> (b -> b -> b) -> t a -> b
> >>      foldlMap1  :: (a -> b) -> (b -> b -> b) -> t a -> b
> >>      foldrMap1' :: (a -> b) -> (b -> b -> b) -> t a -> b
> >>
> >>
> >> This has a couple of benefits. On the practical side, we can provide
> >> total alternatives
> >> to existing partial functions (IE: 'foldr1' and friends). It also
> >> enables us to fold
> >> over containers using a semigroup instance, which comes up suprisingly often.
> >>
> >> Naming:
> >> --------------------------------------------------------------------------------
> >> Historically, the biggest source of controversy with this proposal has
> >> been over the
> >> name. The class currently exists in semigroupoids [3] under the name
> >> 'Foldable1', though
> >> there was some discussion around renaming it to 'SemiFoldable' [4].
> >> However, if we keep
> >> the name unchanged, it makes the migration path nice and
> >> straightforward, and the possible
> >> name conflict with Data.Functor.Classes seems unlikely.
> >>
> >> Migration:
> >> --------------------------------------------------------------------------------
> >> If we decide to go with 'Foldable1' as the name, we should be able to
> >> perform this change with
> >> 0 breakage.
> >>
> >> References:
> >> [1] https://mail.haskell.org/pipermail/libraries/2019-November/030059.html
> >> [2] https://gitlab.haskell.org/ghc/ghc/-/issues/13573
> >> [3] https://hackage.haskell.org/package/semigroupoids-5.3.4/docs/Data-Semigroup-Foldable.html#t:Foldable1
> >> [4] https://github.com/ekmett/semigroupoids/issues/26
> >> _______________________________________________
> >> Libraries mailing list
> >> Libraries at haskell.org
> >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries


More information about the Libraries mailing list