Proposal: Add 'Foldable1' to base

Oleg Grenrus oleg.grenrus at iki.fi
Mon Feb 22 10:31:35 UTC 2021


The conservative class size is not optimal.
One needs at least to have foldrMap-like function.
See https://github.com/ekmett/semigroupoids/issues/77

I think that renaming *and* moving to base is better done in one step,
as then ecosystem would need to adjust once.

A clean approach to migration, which I'd recommend, is to have a (new)
compatibility package, because semigroupoids is too heavy, folks don't
want to depend on it, even semigroups is heavy for some/
Let's tentatively call it foldable1. Then new base would have the exact
same modules as foldable1. And then semigroupoids may at its own pace
migrate to use base/foldable1 and the rest of ecosystem would follow.
Given that Foldable1 isn't terribly spread class (yet), I don't see that
more complicated that what regular major base updates are.

There is another reason to have separate package: Bifoldable1, which I
argue should be moved to base as well.

I think this all is mentioned in my proposal
https://oleg.fi/foldable1-proposal3.html

I (and also Edward, IIUC) call for CLC to make the choice of naming. The
proposal above have three options, I hope one of them fits.

- Oleg

On 3.1.2021 13.01, George Wilson wrote:
> I like David's more conservative class size.
>
> I would prefer to see the semigroupoids classes renamed [1] before
> they get added to base, since it's much harder to rename them once
> they're there. However, it's not clear to me that there's the required
> will to move forward with such a gargantuan renaming effort
> (semigroupoids is depended on directly and transitively by a lot of
> hackage). There was a recent attempt that didn't gain traction [2]. I
> would also prefer that the renaming and the move to base are two
> discrete steps -- not combined, since that would make the migration
> awkward and unpleasant (migrating to a differently-named class from a
> different package).
>
> I want to see the spirit of this happen, but overall I'm -1 on this
> proposal at this time.
>
> [1] https://github.com/ekmett/semigroupoids/issues/26
> [2] https://github.com/ekmett/semigroupoids/pull/90
>
> Cheers,
> George
>
>
> On Fri, 11 Dec 2020 at 22:37, Tony Morris <tonymorris at gmail.com> wrote:
>> Delete head1 and last1 and you'll get my +1.
>>
>> (they are better written as optics, when we also get Apply into base)
>>
>> On 12/10/20 4:37 PM, Reed Mullanix 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
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries


More information about the Libraries mailing list