Add Data.Foldable1 to base

I propose adding `Foldable1` type-class into `base1`. Add Foldable1 ============= Motivation ---------- It's regularly asked whether `Foldable1` could be added to `base` (e.g. on reddit[^ref1], there're also GHC issue[^ref2] and old phabricator diff[^ref3]) Also there's work towards non-empty maps and sets[^ref4], which would benefit from `Foldable1`. As commented on reddit, `Foldable1` could be added without any pain to the `base` as it's pure addition - no modifications needed in existing modules. [^ref1]: https://www.reddit.com/r/haskell/comments/6d0vgt/could_we_have_foldable1_and... [^ref2]: https://gitlab.haskell.org/ghc/ghc/issues/13573 [^ref3]: https://phabricator.haskell.org/D4812 [^ref4]: https://github.com/haskell/containers/pull/616 Change ------ The change exist as merge request[^ref4] on gitlab.haskell.org. Importantly, this change **doesn't change** anything in other modules of `base`, except of adding a `Foldable` instance to `Data.Complex`. In particular, `foldl1` and `foldr1` in `Data.Foldable` remain partial, etc. My version of `Foldable1` class is big, so I'll comment the motivation for each member ```haskell class Foldable t => Foldable1 t where {-# MINIMAL foldMap1 | toNonEmpty | foldr1map #-} -- the defining member, like foldMap but only asking for Semigroup foldMap1 :: Semigroup m => (a -> m) -> t a -> m fold1 :: Semigroup m => t m -> 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 :: forall a. Ord a => t a -> a minimum1 :: forall a. 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. foldr1map :: (a -> b) -> (b -> b -> b) -> t a -> b foldl1'map :: (a -> b) -> (b -> b -> b) -> t a -> b foldl1map :: (a -> b) -> (b -> b -> b) -> t a -> b foldr1'map :: (a -> b) -> (b -> b -> b) -> t a -> b ``` The merge request also adds instances for everything non-empty in `base`. I propose the `Data.Foldable1` as the module name. `semigroupoids`[^ref6] uses `Data.Semigroup.Foldable`, but it's confusing; and using different name could help migration. The module contains five top-level functions, which should be self-explanatory: ```haskell intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a ``` This is less than in `Data.Semigroup.Foldable`[^ref9], as without `Apply` they don't make sense. For example: ```haskell -- needs Apply, not in Data.Foldable1 traverse1_ :: (Foldable1 t, Apply f) => (a -> f b) -> t a -> f () ``` And if we relax `Apply` to `Applicative`, we get `traverse_`. [^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 [^ref9]: https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-... [^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 Compatibility & migration ------------------------- I drafted a compatibility package `foldable1` (github[^ref6], haddocks[^ref7]), which I hope could be maintained under github.com/haskell organization. I can act as a maintainer, with a hope that there won't be a lot of changes happening in `Data.Foldable1`. To my surprise, there's already a package with this name on Hackage[^ref8] by M Farkas-Dyck (cc'd). I hope they would donate the name to Haskell.org / CLC; the package won't have any other good use when `Data.Foldable1` is in `base`, then act as a compat package. `Data.Foldable1` contains also instances for `Lift`, `Backwards` and `Reverse` data types from `transformers`. Perfectly, the `transformers` bundled with GHC with this change would implement the instances as well. This change should propage to `transformers-compat` too. Similarly, `containers` would have an instance for `Tree` (and non-empty `Set` and `Map` when they are added). `semigroupoids` would need a bit of work, to depend on `foldable1`, yet the public changes can be kept quite minimal. I don't think that anything in reverse dependencies of `lens` will be broken by this change, if "new" `Foldable1` is re-exported from `semigroupoids`' `Data.Semigroup.Foldable`[^ref9] Other "compat" packages -- like `tagged`, `bifunctors` -- have to be dealt with case by case. For example whether they should depend on `foldable1` or other way around. [^ref6]: https://github.com/phadej/foldable1 [^ref7]: https://oleg.fi/haddocks/foldable1/ [^ref8]: https://hackage.haskell.org/package/foldable1 [^ref9]: https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-... Unresolved questions -------------------- - Should we add `Bifoldable1` too. That should be trivial. - GHC-8.10 freeze is quite soon, is targeting GHC-8.12/base-4.15 more realistic?

I support this change and I would love to have `Foldable1` in the `base` as
well. I find it so useful that we even have it in our alternative prelude
called `relude`:
*
https://github.com/kowainik/relude/blob/45e112677c6e23759e4742cb695eed20a2cb...
I would love to reexport this typeclass by default from `base` instead of
maintaining one more `Extra.*` module in `relude`. However, at this point,
I like the implementation in `relude` more because:
1. It has usage examples tested with `doctest`.
2. Implements (almost) each function manually and uses {-# INLINE #-}
pragmas for better performance.
3. In the next release, we're also going to add custom type errors of
`Foldable1` instances for data types like ordinary lists to improve UX.
These improvements don't rely on anything `relude`-specific and can be done
in `base` as well.
On Thu, Oct 17, 2019 at 5:43 PM Oleg Grenrus
I propose adding `Foldable1` type-class into `base1`.
Add Foldable1 =============
Motivation ----------
It's regularly asked whether `Foldable1` could be added to `base` (e.g. on reddit[^ref1], there're also GHC issue[^ref2] and old phabricator diff[^ref3]) Also there's work towards non-empty maps and sets[^ref4], which would benefit from `Foldable1`.
As commented on reddit, `Foldable1` could be added without any pain to the `base` as it's pure addition - no modifications needed in existing modules.
[^ref1]:
https://www.reddit.com/r/haskell/comments/6d0vgt/could_we_have_foldable1_and... [^ref2]: https://gitlab.haskell.org/ghc/ghc/issues/13573 [^ref3]: https://phabricator.haskell.org/D4812 [^ref4]: https://github.com/haskell/containers/pull/616
Change ------
The change exist as merge request[^ref4] on gitlab.haskell.org.
Importantly, this change **doesn't change** anything in other modules of `base`, except of adding a `Foldable` instance to `Data.Complex`. In particular, `foldl1` and `foldr1` in `Data.Foldable` remain partial, etc.
My version of `Foldable1` class is big, so I'll comment the motivation for each member
```haskell class Foldable t => Foldable1 t where {-# MINIMAL foldMap1 | toNonEmpty | foldr1map #-}
-- the defining member, like foldMap but only asking for Semigroup foldMap1 :: Semigroup m => (a -> m) -> t a -> m
fold1 :: Semigroup m => t m -> 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 :: forall a. Ord a => t a -> a minimum1 :: forall a. 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. foldr1map :: (a -> b) -> (b -> b -> b) -> t a -> b foldl1'map :: (a -> b) -> (b -> b -> b) -> t a -> b foldl1map :: (a -> b) -> (b -> b -> b) -> t a -> b foldr1'map :: (a -> b) -> (b -> b -> b) -> t a -> b ```
The merge request also adds instances for everything non-empty in `base`.
I propose the `Data.Foldable1` as the module name. `semigroupoids`[^ref6] uses `Data.Semigroup.Foldable`, but it's confusing; and using different name could help migration.
The module contains five top-level functions, which should be self-explanatory:
```haskell intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m
foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a
maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a ```
This is less than in `Data.Semigroup.Foldable`[^ref9], as without `Apply` they don't make sense. For example:
```haskell -- needs Apply, not in Data.Foldable1 traverse1_ :: (Foldable1 t, Apply f) => (a -> f b) -> t a -> f () ```
And if we relax `Apply` to `Applicative`, we get `traverse_`.
[^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 [^ref9]:
https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-...
[^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973
Compatibility & migration -------------------------
I drafted a compatibility package `foldable1` (github[^ref6], haddocks[^ref7]), which I hope could be maintained under github.com/haskell organization. I can act as a maintainer, with a hope that there won't be a lot of changes happening in `Data.Foldable1`.
To my surprise, there's already a package with this name on Hackage[^ref8] by M Farkas-Dyck (cc'd). I hope they would donate the name to Haskell.org / CLC; the package won't have any other good use when `Data.Foldable1` is in `base`, then act as a compat package.
`Data.Foldable1` contains also instances for `Lift`, `Backwards` and `Reverse` data types from `transformers`. Perfectly, the `transformers` bundled with GHC with this change would implement the instances as well. This change should propage to `transformers-compat` too.
Similarly, `containers` would have an instance for `Tree` (and non-empty `Set` and `Map` when they are added).
`semigroupoids` would need a bit of work, to depend on `foldable1`, yet the public changes can be kept quite minimal. I don't think that anything in reverse dependencies of `lens` will be broken by this change, if "new" `Foldable1` is re-exported from `semigroupoids`' `Data.Semigroup.Foldable`[^ref9]
Other "compat" packages -- like `tagged`, `bifunctors` -- have to be dealt with case by case. For example whether they should depend on `foldable1` or other way around.
[^ref6]: https://github.com/phadej/foldable1 [^ref7]: https://oleg.fi/haddocks/foldable1/ [^ref8]: https://hackage.haskell.org/package/foldable1 [^ref9]:
https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-...
Unresolved questions --------------------
- Should we add `Bifoldable1` too. That should be trivial. - GHC-8.10 freeze is quite soon, is targeting GHC-8.12/base-4.15 more realistic?
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Thanks for the support and comments Dmitrii. 1. I can add usage examples, that's no brainer. 2. Yes, implementing selected members manually can help, that's the point of having a lot of members, and not bare foldMap1. - Yet I hope that is not a blocker - This may be motivated by GHC.Generics, but I don't see instances in `relude`? - Non trivial manual implementations should be backed up by some benchmark that shows it's worth having more code (which one have test, that it's coherent!). - That said, I'll add more manual members when I have test setup ready. E.g. `head1 :: Compose f g a -> a`, and for `Product` (and Generics variants). - {-# INLINE #-} everywhere doesn't imply more performance. - The `foldable1` package is simple enough playground to add benchmarks, there are some already. 3. There is no prior art of disallowing instances with TypeErrors in `base`, so I'm wont consider it here either. - That's worth an own separate library proposal - Oleg On 17.10.2019 19.26, Dmitrii Kovanikov wrote:
I support this change and I would love to have `Foldable1` in the `base` as well. I find it so useful that we even have it in our alternative prelude called `relude`:
* https://github.com/kowainik/relude/blob/45e112677c6e23759e4742cb695eed20a2cb...
I would love to reexport this typeclass by default from `base` instead of maintaining one more `Extra.*` module in `relude`. However, at this point, I like the implementation in `relude` more because:
1. It has usage examples tested with `doctest`. 2. Implements (almost) each function manually and uses {-# INLINE #-} pragmas for better performance. 3. In the next release, we're also going to add custom type errors of `Foldable1` instances for data types like ordinary lists to improve UX.
These improvements don't rely on anything `relude`-specific and can be done in `base` as well.
On Thu, Oct 17, 2019 at 5:43 PM Oleg Grenrus
mailto:oleg.grenrus@iki.fi> wrote: I propose adding `Foldable1` type-class into `base1`.
Add Foldable1 =============
Motivation ----------
It's regularly asked whether `Foldable1` could be added to `base` (e.g. on reddit[^ref1], there're also GHC issue[^ref2] and old phabricator diff[^ref3]) Also there's work towards non-empty maps and sets[^ref4], which would benefit from `Foldable1`.
As commented on reddit, `Foldable1` could be added without any pain to the `base` as it's pure addition - no modifications needed in existing modules.
[^ref1]: https://www.reddit.com/r/haskell/comments/6d0vgt/could_we_have_foldable1_and... [^ref2]: https://gitlab.haskell.org/ghc/ghc/issues/13573 [^ref3]: https://phabricator.haskell.org/D4812 [^ref4]: https://github.com/haskell/containers/pull/616
Change ------
The change exist as merge request[^ref4] on gitlab.haskell.org http://gitlab.haskell.org.
Importantly, this change **doesn't change** anything in other modules of `base`, except of adding a `Foldable` instance to `Data.Complex`. In particular, `foldl1` and `foldr1` in `Data.Foldable` remain partial, etc.
My version of `Foldable1` class is big, so I'll comment the motivation for each member
```haskell class Foldable t => Foldable1 t where {-# MINIMAL foldMap1 | toNonEmpty | foldr1map #-}
-- the defining member, like foldMap but only asking for Semigroup foldMap1 :: Semigroup m => (a -> m) -> t a -> m
fold1 :: Semigroup m => t m -> 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 :: forall a. Ord a => t a -> a minimum1 :: forall a. 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. foldr1map :: (a -> b) -> (b -> b -> b) -> t a -> b foldl1'map :: (a -> b) -> (b -> b -> b) -> t a -> b foldl1map :: (a -> b) -> (b -> b -> b) -> t a -> b foldr1'map :: (a -> b) -> (b -> b -> b) -> t a -> b ```
The merge request also adds instances for everything non-empty in `base`.
I propose the `Data.Foldable1` as the module name. `semigroupoids`[^ref6] uses `Data.Semigroup.Foldable`, but it's confusing; and using different name could help migration.
The module contains five top-level functions, which should be self-explanatory:
```haskell intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m
foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a
maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a ```
This is less than in `Data.Semigroup.Foldable`[^ref9], as without `Apply` they don't make sense. For example:
```haskell -- needs Apply, not in Data.Foldable1 traverse1_ :: (Foldable1 t, Apply f) => (a -> f b) -> t a -> f () ```
And if we relax `Apply` to `Applicative`, we get `traverse_`.
[^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 [^ref9]: https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-...
[^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973
Compatibility & migration -------------------------
I drafted a compatibility package `foldable1` (github[^ref6], haddocks[^ref7]), which I hope could be maintained under github.com/haskell http://github.com/haskell organization. I can act as a maintainer, with a hope that there won't be a lot of changes happening in `Data.Foldable1`.
To my surprise, there's already a package with this name on Hackage[^ref8] by M Farkas-Dyck (cc'd). I hope they would donate the name to Haskell.org / CLC; the package won't have any other good use when `Data.Foldable1` is in `base`, then act as a compat package.
`Data.Foldable1` contains also instances for `Lift`, `Backwards` and `Reverse` data types from `transformers`. Perfectly, the `transformers` bundled with GHC with this change would implement the instances as well. This change should propage to `transformers-compat` too.
Similarly, `containers` would have an instance for `Tree` (and non-empty `Set` and `Map` when they are added).
`semigroupoids` would need a bit of work, to depend on `foldable1`, yet the public changes can be kept quite minimal. I don't think that anything in reverse dependencies of `lens` will be broken by this change, if "new" `Foldable1` is re-exported from `semigroupoids`' `Data.Semigroup.Foldable`[^ref9]
Other "compat" packages -- like `tagged`, `bifunctors` -- have to be dealt with case by case. For example whether they should depend on `foldable1` or other way around.
[^ref6]: https://github.com/phadej/foldable1 [^ref7]: https://oleg.fi/haddocks/foldable1/ [^ref8]: https://hackage.haskell.org/package/foldable1 [^ref9]: https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-...
Unresolved questions --------------------
- Should we add `Bifoldable1` too. That should be trivial. - GHC-8.10 freeze is quite soon, is targeting GHC-8.12/base-4.15 more realistic?
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

While I want this abstraction in base, I don’t want it there yet. There is an open issue on semigroupoids about renaming everything: https://github.com/ekmett/semigroupoids/issues/26 This needs to be handled before the abstraction is brought into base. Also, foldr1 is awful in common situations. See https://github.com/ekmett/semigroupoids/issues/77 The problem is that refinements of this abstraction seem to have stalled in semigroupoids, but these are desperately needed before the abstraction is brought into base. Sent from my iPhone
On Oct 17, 2019, at 10:42 AM, Oleg Grenrus
wrote: I propose adding `Foldable1` type-class into `base1`.
Add Foldable1 =============
Motivation ----------
It's regularly asked whether `Foldable1` could be added to `base` (e.g. on reddit[^ref1], there're also GHC issue[^ref2] and old phabricator diff[^ref3]) Also there's work towards non-empty maps and sets[^ref4], which would benefit from `Foldable1`.
As commented on reddit, `Foldable1` could be added without any pain to the `base` as it's pure addition - no modifications needed in existing modules.
[^ref1]: https://www.reddit.com/r/haskell/comments/6d0vgt/could_we_have_foldable1_and... [^ref2]: https://gitlab.haskell.org/ghc/ghc/issues/13573 [^ref3]: https://phabricator.haskell.org/D4812 [^ref4]: https://github.com/haskell/containers/pull/616
Change ------
The change exist as merge request[^ref4] on gitlab.haskell.org.
Importantly, this change **doesn't change** anything in other modules of `base`, except of adding a `Foldable` instance to `Data.Complex`. In particular, `foldl1` and `foldr1` in `Data.Foldable` remain partial, etc.
My version of `Foldable1` class is big, so I'll comment the motivation for each member
```haskell class Foldable t => Foldable1 t where {-# MINIMAL foldMap1 | toNonEmpty | foldr1map #-}
-- the defining member, like foldMap but only asking for Semigroup foldMap1 :: Semigroup m => (a -> m) -> t a -> m
fold1 :: Semigroup m => t m -> 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 :: forall a. Ord a => t a -> a minimum1 :: forall a. 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. foldr1map :: (a -> b) -> (b -> b -> b) -> t a -> b foldl1'map :: (a -> b) -> (b -> b -> b) -> t a -> b foldl1map :: (a -> b) -> (b -> b -> b) -> t a -> b foldr1'map :: (a -> b) -> (b -> b -> b) -> t a -> b ```
The merge request also adds instances for everything non-empty in `base`.
I propose the `Data.Foldable1` as the module name. `semigroupoids`[^ref6] uses `Data.Semigroup.Foldable`, but it's confusing; and using different name could help migration.
The module contains five top-level functions, which should be self-explanatory:
```haskell intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m
foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a
maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a ```
This is less than in `Data.Semigroup.Foldable`[^ref9], as without `Apply` they don't make sense. For example:
```haskell -- needs Apply, not in Data.Foldable1 traverse1_ :: (Foldable1 t, Apply f) => (a -> f b) -> t a -> f () ```
And if we relax `Apply` to `Applicative`, we get `traverse_`.
[^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 [^ref9]: https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-...
[^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973
Compatibility & migration -------------------------
I drafted a compatibility package `foldable1` (github[^ref6], haddocks[^ref7]), which I hope could be maintained under github.com/haskell organization. I can act as a maintainer, with a hope that there won't be a lot of changes happening in `Data.Foldable1`.
To my surprise, there's already a package with this name on Hackage[^ref8] by M Farkas-Dyck (cc'd). I hope they would donate the name to Haskell.org / CLC; the package won't have any other good use when `Data.Foldable1` is in `base`, then act as a compat package.
`Data.Foldable1` contains also instances for `Lift`, `Backwards` and `Reverse` data types from `transformers`. Perfectly, the `transformers` bundled with GHC with this change would implement the instances as well. This change should propage to `transformers-compat` too.
Similarly, `containers` would have an instance for `Tree` (and non-empty `Set` and `Map` when they are added).
`semigroupoids` would need a bit of work, to depend on `foldable1`, yet the public changes can be kept quite minimal. I don't think that anything in reverse dependencies of `lens` will be broken by this change, if "new" `Foldable1` is re-exported from `semigroupoids`' `Data.Semigroup.Foldable`[^ref9]
Other "compat" packages -- like `tagged`, `bifunctors` -- have to be dealt with case by case. For example whether they should depend on `foldable1` or other way around.
[^ref6]: https://github.com/phadej/foldable1 [^ref7]: https://oleg.fi/haddocks/foldable1/ [^ref8]: https://hackage.haskell.org/package/foldable1 [^ref9]: https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-...
Unresolved questions --------------------
- Should we add `Bifoldable1` too. That should be trivial. - GHC-8.10 freeze is quite soon, is targeting GHC-8.12/base-4.15 more realistic?
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

I’m happy to take patches to move things along in semigroupoids. My focus has been elsewhere, I admit. -Edward
On Oct 17, 2019, at 5:03 PM, Andrew Martin
wrote: While I want this abstraction in base, I don’t want it there yet. There is an open issue on semigroupoids about renaming everything: https://github.com/ekmett/semigroupoids/issues/26
This needs to be handled before the abstraction is brought into base. Also, foldr1 is awful in common situations. See https://github.com/ekmett/semigroupoids/issues/77
The problem is that refinements of this abstraction seem to have stalled in semigroupoids, but these are desperately needed before the abstraction is brought into base.
Sent from my iPhone
On Oct 17, 2019, at 10:42 AM, Oleg Grenrus
wrote: I propose adding `Foldable1` type-class into `base1`.
Add Foldable1 =============
Motivation ----------
It's regularly asked whether `Foldable1` could be added to `base` (e.g. on reddit[^ref1], there're also GHC issue[^ref2] and old phabricator diff[^ref3]) Also there's work towards non-empty maps and sets[^ref4], which would benefit from `Foldable1`.
As commented on reddit, `Foldable1` could be added without any pain to the `base` as it's pure addition - no modifications needed in existing modules.
[^ref1]: https://www.reddit.com/r/haskell/comments/6d0vgt/could_we_have_foldable1_and... [^ref2]: https://gitlab.haskell.org/ghc/ghc/issues/13573 [^ref3]: https://phabricator.haskell.org/D4812 [^ref4]: https://github.com/haskell/containers/pull/616
Change ------
The change exist as merge request[^ref4] on gitlab.haskell.org.
Importantly, this change **doesn't change** anything in other modules of `base`, except of adding a `Foldable` instance to `Data.Complex`. In particular, `foldl1` and `foldr1` in `Data.Foldable` remain partial, etc.
My version of `Foldable1` class is big, so I'll comment the motivation for each member
```haskell class Foldable t => Foldable1 t where {-# MINIMAL foldMap1 | toNonEmpty | foldr1map #-}
-- the defining member, like foldMap but only asking for Semigroup foldMap1 :: Semigroup m => (a -> m) -> t a -> m
fold1 :: Semigroup m => t m -> 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 :: forall a. Ord a => t a -> a minimum1 :: forall a. 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. foldr1map :: (a -> b) -> (b -> b -> b) -> t a -> b foldl1'map :: (a -> b) -> (b -> b -> b) -> t a -> b foldl1map :: (a -> b) -> (b -> b -> b) -> t a -> b foldr1'map :: (a -> b) -> (b -> b -> b) -> t a -> b ```
The merge request also adds instances for everything non-empty in `base`.
I propose the `Data.Foldable1` as the module name. `semigroupoids`[^ref6] uses `Data.Semigroup.Foldable`, but it's confusing; and using different name could help migration.
The module contains five top-level functions, which should be self-explanatory:
```haskell intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m
foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a
maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a ```
This is less than in `Data.Semigroup.Foldable`[^ref9], as without `Apply` they don't make sense. For example:
```haskell -- needs Apply, not in Data.Foldable1 traverse1_ :: (Foldable1 t, Apply f) => (a -> f b) -> t a -> f () ```
And if we relax `Apply` to `Applicative`, we get `traverse_`.
[^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 [^ref9]: https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-...
[^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973
Compatibility & migration -------------------------
I drafted a compatibility package `foldable1` (github[^ref6], haddocks[^ref7]), which I hope could be maintained under github.com/haskell organization. I can act as a maintainer, with a hope that there won't be a lot of changes happening in `Data.Foldable1`.
To my surprise, there's already a package with this name on Hackage[^ref8] by M Farkas-Dyck (cc'd). I hope they would donate the name to Haskell.org / CLC; the package won't have any other good use when `Data.Foldable1` is in `base`, then act as a compat package.
`Data.Foldable1` contains also instances for `Lift`, `Backwards` and `Reverse` data types from `transformers`. Perfectly, the `transformers` bundled with GHC with this change would implement the instances as well. This change should propage to `transformers-compat` too.
Similarly, `containers` would have an instance for `Tree` (and non-empty `Set` and `Map` when they are added).
`semigroupoids` would need a bit of work, to depend on `foldable1`, yet the public changes can be kept quite minimal. I don't think that anything in reverse dependencies of `lens` will be broken by this change, if "new" `Foldable1` is re-exported from `semigroupoids`' `Data.Semigroup.Foldable`[^ref9]
Other "compat" packages -- like `tagged`, `bifunctors` -- have to be dealt with case by case. For example whether they should depend on `foldable1` or other way around.
[^ref6]: https://github.com/phadej/foldable1 [^ref7]: https://oleg.fi/haddocks/foldable1/ [^ref8]: https://hackage.haskell.org/package/foldable1 [^ref9]: https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-...
Unresolved questions --------------------
- Should we add `Bifoldable1` too. That should be trivial. - GHC-8.10 freeze is quite soon, is targeting GHC-8.12/base-4.15 more realistic?
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

What is the proposed change in semigroupoids, I don't see any decisive conclusion comment. To get this going, I suggest limiting discussion to the Foldable1 only and if after this proposal is accepted, extrapolate for the rest of `semigroupoids`. So if someone can propose a concrete list how to rename symbols in https://oleg.fi/haddocks/foldable1/Data-Foldable1.html http://oleg.fi/haddocks/foldable1/Data-Foldable1.html, I'll make a separate branch & haddock page. Is the wanted renaming s/1//; s/^/semi/: - Foldable1 -> Semifoldable - fold1 -> semifold - foldMap1 -> semifoldMap - foldr1 -> semifoldr - foldr1map -> semifoldr1map - toNonEmpty -> toNonEmpty - ... - head1 -> semihead - last1 -> semilast - minimum1 -> semiminimum - maximum1 -> semimaximum - intercalate1 -> semiintercalate - foldl1M -> semifoldl - ... - maximum1By -> semimaximumBy - ... I'm fine with this. The head1/semihead are both silly, but the suffix was there to avoid name clash, so prefix is fine for that purpose too. --- The synopsis of current state of proposed Data.Foldable1 module Data.Foldable1where class Foldable t => Foldable1 t fold1 :: (Foldable1 t, Semigroup m) => t m -> m foldMap1 :: (Foldable1 t, Semigroup m) => (a -> m) -> t a -> m foldMap1' :: (Foldable1 t, Semigroup m) => (a -> m) -> t a -> m foldr1 :: Foldable1 t => (a -> a -> a) -> t a -> a foldr1' :: Foldable1 t => (a -> a -> a) -> t a -> a foldl1 :: Foldable1 t => (a -> a -> a) -> t a -> a foldl1' :: Foldable1 t => (a -> a -> a) -> t a -> a toNonEmpty :: Foldable1 t => t a -> NonEmpty a maximum1 :: forall a. (Foldable1 t, Ord a) => t a -> a minimum1 :: forall a. (Foldable1 t, Ord a) => t a -> a head1 :: Foldable1 t => t a -> a last1 :: Foldable1 t => t a -> a foldr1map :: Foldable1 t => (a -> b) -> (b -> b -> b) -> t a -> b foldl1'map :: Foldable1 t => (a -> b) -> (b -> b -> b) -> t a -> b foldl1map :: Foldable1 t => (a -> b) -> (b -> b -> b) -> t a -> b foldr1'map :: Foldable1 t => (a -> b) -> (b -> b -> b) -> t a -> b intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a - Oleg On 18.10.2019 3.06, Edward Kmett wrote:
I’m happy to take patches to move things along in semigroupoids. My focus has been elsewhere, I admit.
-Edward
On Oct 17, 2019, at 5:03 PM, Andrew Martin
wrote: While I want this abstraction in base, I don’t want it there yet. There is an open issue on semigroupoids about renaming everything: https://github.com/ekmett/semigroupoids/issues/26
This needs to be handled before the abstraction is brought into base. Also, foldr1 is awful in common situations. See https://github.com/ekmett/semigroupoids/issues/77
The problem is that refinements of this abstraction seem to have stalled in semigroupoids, but these are desperately needed before the abstraction is brought into base.
Sent from my iPhone
On Oct 17, 2019, at 10:42 AM, Oleg Grenrus
mailto:oleg.grenrus@iki.fi> wrote: I propose adding `Foldable1` type-class into `base1`.
Add Foldable1 =============
Motivation ----------
It's regularly asked whether `Foldable1` could be added to `base` (e.g. on reddit[^ref1], there're also GHC issue[^ref2] and old phabricator diff[^ref3]) Also there's work towards non-empty maps and sets[^ref4], which would benefit from `Foldable1`.
As commented on reddit, `Foldable1` could be added without any pain to the `base` as it's pure addition - no modifications needed in existing modules.
[^ref1]: https://www.reddit.com/r/haskell/comments/6d0vgt/could_we_have_foldable1_and... [^ref2]: https://gitlab.haskell.org/ghc/ghc/issues/13573 [^ref3]: https://phabricator.haskell.org/D4812 [^ref4]: https://github.com/haskell/containers/pull/616
Change ------
The change exist as merge request[^ref4] on gitlab.haskell.org http://gitlab.haskell.org.
Importantly, this change **doesn't change** anything in other modules of `base`, except of adding a `Foldable` instance to `Data.Complex`. In particular, `foldl1` and `foldr1` in `Data.Foldable` remain partial, etc.
My version of `Foldable1` class is big, so I'll comment the motivation for each member
```haskell class Foldable t => Foldable1 t where {-# MINIMAL foldMap1 | toNonEmpty | foldr1map #-}
-- the defining member, like foldMap but only asking for Semigroup foldMap1 :: Semigroup m => (a -> m) -> t a -> m
fold1 :: Semigroup m => t m -> 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 :: forall a. Ord a => t a -> a minimum1 :: forall a. 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. foldr1map :: (a -> b) -> (b -> b -> b) -> t a -> b foldl1'map :: (a -> b) -> (b -> b -> b) -> t a -> b foldl1map :: (a -> b) -> (b -> b -> b) -> t a -> b foldr1'map :: (a -> b) -> (b -> b -> b) -> t a -> b ```
The merge request also adds instances for everything non-empty in `base`.
I propose the `Data.Foldable1` as the module name. `semigroupoids`[^ref6] uses `Data.Semigroup.Foldable`, but it's confusing; and using different name could help migration.
The module contains five top-level functions, which should be self-explanatory:
```haskell intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m
foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a
maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a ```
This is less than in `Data.Semigroup.Foldable`[^ref9], as without `Apply` they don't make sense. For example:
```haskell -- needs Apply, not in Data.Foldable1 traverse1_ :: (Foldable1 t, Apply f) => (a -> f b) -> t a -> f () ```
And if we relax `Apply` to `Applicative`, we get `traverse_`.
[^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 [^ref9]: https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-...
[^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973
Compatibility & migration -------------------------
I drafted a compatibility package `foldable1` (github[^ref6], haddocks[^ref7]), which I hope could be maintained under github.com/haskell http://github.com/haskell organization. I can act as a maintainer, with a hope that there won't be a lot of changes happening in `Data.Foldable1`.
To my surprise, there's already a package with this name on Hackage[^ref8] by M Farkas-Dyck (cc'd). I hope they would donate the name to Haskell.org http://Haskell.org / CLC; the package won't have any other good use when `Data.Foldable1` is in `base`, then act as a compat package.
`Data.Foldable1` contains also instances for `Lift`, `Backwards` and `Reverse` data types from `transformers`. Perfectly, the `transformers` bundled with GHC with this change would implement the instances as well. This change should propage to `transformers-compat` too.
Similarly, `containers` would have an instance for `Tree` (and non-empty `Set` and `Map` when they are added).
`semigroupoids` would need a bit of work, to depend on `foldable1`, yet the public changes can be kept quite minimal. I don't think that anything in reverse dependencies of `lens` will be broken by this change, if "new" `Foldable1` is re-exported from `semigroupoids`' `Data.Semigroup.Foldable`[^ref9]
Other "compat" packages -- like `tagged`, `bifunctors` -- have to be dealt with case by case. For example whether they should depend on `foldable1` or other way around.
[^ref6]: https://github.com/phadej/foldable1 [^ref7]: https://oleg.fi/haddocks/foldable1/ [^ref8]: https://hackage.haskell.org/package/foldable1 [^ref9]: https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-...
Unresolved questions --------------------
- Should we add `Bifoldable1` too. That should be trivial. - GHC-8.10 freeze is quite soon, is targeting GHC-8.12/base-4.15 more realistic?
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

I agree Foldable1 in base would be great, but I think the most bang for
buck would be to include several others; at least also Traversable1 and
possibly even Apply,Bind,Alt
I second the comment about the issue related to addressing the names, etc
in semigroupoids, in preparation for inclusion to base.
On Fri, Oct 18, 2019 at 11:12 AM Oleg Grenrus
What is the proposed change in semigroupoids, I don't see any decisive conclusion comment. To get this going, I suggest limiting discussion to the Foldable1 only and if after this proposal is accepted, extrapolate for the rest of `semigroupoids`.
So if someone can propose a concrete list how to rename symbols in https://oleg.fi/haddocks/foldable1/Data-Foldable1.html http://oleg.fi/haddocks/foldable1/Data-Foldable1.html, I'll make a separate branch & haddock page.
Is the wanted renaming s/1//; s/^/semi/:
- Foldable1 -> Semifoldable - fold1 -> semifold - foldMap1 -> semifoldMap - foldr1 -> semifoldr - foldr1map -> semifoldr1map - toNonEmpty -> toNonEmpty - ... - head1 -> semihead - last1 -> semilast - minimum1 -> semiminimum - maximum1 -> semimaximum
- intercalate1 -> semiintercalate - foldl1M -> semifoldl - ... - maximum1By -> semimaximumBy - ...
I'm fine with this. The head1/semihead are both silly, but the suffix was there to avoid name clash, so prefix is fine for that purpose too.
---
The synopsis of current state of proposed Data.Foldable1
module Data.Foldable1 where
class Foldable t => Foldable1 t fold1 :: (Foldable1 t, Semigroup m) => t m -> m foldMap1 :: (Foldable1 t, Semigroup m) => (a -> m) -> t a -> m foldMap1' :: (Foldable1 t, Semigroup m) => (a -> m) -> t a -> m foldr1 :: Foldable1 t => (a -> a -> a) -> t a -> a foldr1' :: Foldable1 t => (a -> a -> a) -> t a -> a foldl1 :: Foldable1 t => (a -> a -> a) -> t a -> a foldl1' :: Foldable1 t => (a -> a -> a) -> t a -> a toNonEmpty :: Foldable1 t => t a -> NonEmpty a maximum1 :: forall a. (Foldable1 t, Ord a) => t a -> a minimum1 :: forall a. (Foldable1 t, Ord a) => t a -> a head1 :: Foldable1 t => t a -> a last1 :: Foldable1 t => t a -> a foldr1map :: Foldable1 t => (a -> b) -> (b -> b -> b) -> t a -> b foldl1'map :: Foldable1 t => (a -> b) -> (b -> b -> b) -> t a -> b foldl1map :: Foldable1 t => (a -> b) -> (b -> b -> b) -> t a -> b foldr1'map :: Foldable1 t => (a -> b) -> (b -> b -> b) -> t a -> b
intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a
- Oleg On 18.10.2019 3.06, Edward Kmett wrote:
I’m happy to take patches to move things along in semigroupoids. My focus has been elsewhere, I admit.
-Edward
On Oct 17, 2019, at 5:03 PM, Andrew Martin
wrote: While I want this abstraction in base, I don’t want it there yet. There is an open issue on semigroupoids about renaming everything: https://github.com/ekmett/semigroupoids/issues/26
This needs to be handled before the abstraction is brought into base. Also, foldr1 is awful in common situations. See https://github.com/ekmett/semigroupoids/issues/77
The problem is that refinements of this abstraction seem to have stalled in semigroupoids, but these are desperately needed before the abstraction is brought into base.
Sent from my iPhone
On Oct 17, 2019, at 10:42 AM, Oleg Grenrus
wrote: I propose adding `Foldable1` type-class into `base1`.
Add Foldable1 =============
Motivation ----------
It's regularly asked whether `Foldable1` could be added to `base` (e.g. on reddit[^ref1], there're also GHC issue[^ref2] and old phabricator diff[^ref3]) Also there's work towards non-empty maps and sets[^ref4], which would benefit from `Foldable1`.
As commented on reddit, `Foldable1` could be added without any pain to the `base` as it's pure addition - no modifications needed in existing modules.
[^ref1]:
https://www.reddit.com/r/haskell/comments/6d0vgt/could_we_have_foldable1_and... [^ref2]: https://gitlab.haskell.org/ghc/ghc/issues/13573 [^ref3]: https://phabricator.haskell.org/D4812 [^ref4]: https://github.com/haskell/containers/pull/616
Change ------
The change exist as merge request[^ref4] on gitlab.haskell.org.
Importantly, this change **doesn't change** anything in other modules of `base`, except of adding a `Foldable` instance to `Data.Complex`. In particular, `foldl1` and `foldr1` in `Data.Foldable` remain partial, etc.
My version of `Foldable1` class is big, so I'll comment the motivation for each member
```haskell class Foldable t => Foldable1 t where {-# MINIMAL foldMap1 | toNonEmpty | foldr1map #-}
-- the defining member, like foldMap but only asking for Semigroup foldMap1 :: Semigroup m => (a -> m) -> t a -> m
fold1 :: Semigroup m => t m -> 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 :: forall a. Ord a => t a -> a minimum1 :: forall a. 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. foldr1map :: (a -> b) -> (b -> b -> b) -> t a -> b foldl1'map :: (a -> b) -> (b -> b -> b) -> t a -> b foldl1map :: (a -> b) -> (b -> b -> b) -> t a -> b foldr1'map :: (a -> b) -> (b -> b -> b) -> t a -> b ```
The merge request also adds instances for everything non-empty in `base`.
I propose the `Data.Foldable1` as the module name. `semigroupoids`[^ref6] uses `Data.Semigroup.Foldable`, but it's confusing; and using different name could help migration.
The module contains five top-level functions, which should be self-explanatory:
```haskell intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m
foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a
maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a ```
This is less than in `Data.Semigroup.Foldable`[^ref9], as without `Apply` they don't make sense. For example:
```haskell -- needs Apply, not in Data.Foldable1 traverse1_ :: (Foldable1 t, Apply f) => (a -> f b) -> t a -> f () ```
And if we relax `Apply` to `Applicative`, we get `traverse_`.
[^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 [^ref9]:
https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-...
[^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973
Compatibility & migration -------------------------
I drafted a compatibility package `foldable1` (github[^ref6], haddocks[^ref7]), which I hope could be maintained under github.com/haskell organization. I can act as a maintainer, with a hope that there won't be a lot of changes happening in `Data.Foldable1`.
To my surprise, there's already a package with this name on Hackage[^ref8] by M Farkas-Dyck (cc'd). I hope they would donate the name to Haskell.org / CLC; the package won't have any other good use when `Data.Foldable1` is in `base`, then act as a compat package.
`Data.Foldable1` contains also instances for `Lift`, `Backwards` and `Reverse` data types from `transformers`. Perfectly, the `transformers` bundled with GHC with this change would implement the instances as well. This change should propage to `transformers-compat` too.
Similarly, `containers` would have an instance for `Tree` (and non-empty `Set` and `Map` when they are added).
`semigroupoids` would need a bit of work, to depend on `foldable1`, yet the public changes can be kept quite minimal. I don't think that anything in reverse dependencies of `lens` will be broken by this change, if "new" `Foldable1` is re-exported from `semigroupoids`' `Data.Semigroup.Foldable`[^ref9]
Other "compat" packages -- like `tagged`, `bifunctors` -- have to be dealt with case by case. For example whether they should depend on `foldable1` or other way around.
[^ref6]: https://github.com/phadej/foldable1 [^ref7]: https://oleg.fi/haddocks/foldable1/ [^ref8]: https://hackage.haskell.org/package/foldable1 [^ref9]:
https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-...
Unresolved questions --------------------
- Should we add `Bifoldable1` too. That should be trivial. - GHC-8.10 freeze is quite soon, is targeting GHC-8.12/base-4.15 more realistic?
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

I won't try to include Traversable1, nor Apply, Bind, Alt; not yet. It would extend the scope of a patch way too much, and rise AMP-like questions, which I don't have answers to. Foldable1 is something which "could move into base without pain" [1], so let's do that first. - Oleg [1]: https://www.reddit.com/r/haskell/comments/6d0vgt/could_we_have_foldable1_and... On 18.10.2019 10.26, Tony Morris wrote:
I agree Foldable1 in base would be great, but I think the most bang for buck would be to include several others; at least also Traversable1 and possibly even Apply,Bind,Alt
I second the comment about the issue related to addressing the names, etc in semigroupoids, in preparation for inclusion to base.
On Fri, Oct 18, 2019 at 11:12 AM Oleg Grenrus
mailto:oleg.grenrus@iki.fi> wrote: What is the proposed change in semigroupoids, I don't see any decisive conclusion comment. To get this going, I suggest limiting discussion to the Foldable1 only and if after this proposal is accepted, extrapolate for the rest of `semigroupoids`.
So if someone can propose a concrete list how to rename symbols in https://oleg.fi/haddocks/foldable1/Data-Foldable1.html http://oleg.fi/haddocks/foldable1/Data-Foldable1.html, I'll make a separate branch & haddock page.
Is the wanted renaming s/1//; s/^/semi/:
- Foldable1 -> Semifoldable - fold1 -> semifold - foldMap1 -> semifoldMap - foldr1 -> semifoldr - foldr1map -> semifoldr1map - toNonEmpty -> toNonEmpty - ... - head1 -> semihead - last1 -> semilast - minimum1 -> semiminimum - maximum1 -> semimaximum
- intercalate1 -> semiintercalate - foldl1M -> semifoldl - ... - maximum1By -> semimaximumBy - ...
I'm fine with this. The head1/semihead are both silly, but the suffix was there to avoid name clash, so prefix is fine for that purpose too.
---
The synopsis of current state of proposed Data.Foldable1
module Data.Foldable1where
class Foldable t => Foldable1 t fold1 :: (Foldable1 t, Semigroup m) => t m -> m foldMap1 :: (Foldable1 t, Semigroup m) => (a -> m) -> t a -> m foldMap1' :: (Foldable1 t, Semigroup m) => (a -> m) -> t a -> m foldr1 :: Foldable1 t => (a -> a -> a) -> t a -> a foldr1' :: Foldable1 t => (a -> a -> a) -> t a -> a foldl1 :: Foldable1 t => (a -> a -> a) -> t a -> a foldl1' :: Foldable1 t => (a -> a -> a) -> t a -> a toNonEmpty :: Foldable1 t => t a -> NonEmpty a maximum1 :: forall a. (Foldable1 t, Ord a) => t a -> a minimum1 :: forall a. (Foldable1 t, Ord a) => t a -> a head1 :: Foldable1 t => t a -> a last1 :: Foldable1 t => t a -> a foldr1map :: Foldable1 t => (a -> b) -> (b -> b -> b) -> t a -> b foldl1'map :: Foldable1 t => (a -> b) -> (b -> b -> b) -> t a -> b foldl1map :: Foldable1 t => (a -> b) -> (b -> b -> b) -> t a -> b foldr1'map :: Foldable1 t => (a -> b) -> (b -> b -> b) -> t a -> b
intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a
- Oleg
On 18.10.2019 3.06, Edward Kmett wrote:
I’m happy to take patches to move things along in semigroupoids. My focus has been elsewhere, I admit.
-Edward
On Oct 17, 2019, at 5:03 PM, Andrew Martin
mailto:andrew.thaddeus@gmail.com wrote: While I want this abstraction in base, I don’t want it there yet. There is an open issue on semigroupoids about renaming everything: https://github.com/ekmett/semigroupoids/issues/26
This needs to be handled before the abstraction is brought into base. Also, foldr1 is awful in common situations. See https://github.com/ekmett/semigroupoids/issues/77
The problem is that refinements of this abstraction seem to have stalled in semigroupoids, but these are desperately needed before the abstraction is brought into base.
Sent from my iPhone
On Oct 17, 2019, at 10:42 AM, Oleg Grenrus
mailto:oleg.grenrus@iki.fi> wrote: I propose adding `Foldable1` type-class into `base1`.
Add Foldable1 =============
Motivation ----------
It's regularly asked whether `Foldable1` could be added to `base` (e.g. on reddit[^ref1], there're also GHC issue[^ref2] and old phabricator diff[^ref3]) Also there's work towards non-empty maps and sets[^ref4], which would benefit from `Foldable1`.
As commented on reddit, `Foldable1` could be added without any pain to the `base` as it's pure addition - no modifications needed in existing modules.
[^ref1]: https://www.reddit.com/r/haskell/comments/6d0vgt/could_we_have_foldable1_and... [^ref2]: https://gitlab.haskell.org/ghc/ghc/issues/13573 [^ref3]: https://phabricator.haskell.org/D4812 [^ref4]: https://github.com/haskell/containers/pull/616
Change ------
The change exist as merge request[^ref4] on gitlab.haskell.org http://gitlab.haskell.org.
Importantly, this change **doesn't change** anything in other modules of `base`, except of adding a `Foldable` instance to `Data.Complex`. In particular, `foldl1` and `foldr1` in `Data.Foldable` remain partial, etc.
My version of `Foldable1` class is big, so I'll comment the motivation for each member
```haskell class Foldable t => Foldable1 t where {-# MINIMAL foldMap1 | toNonEmpty | foldr1map #-}
-- the defining member, like foldMap but only asking for Semigroup foldMap1 :: Semigroup m => (a -> m) -> t a -> m
fold1 :: Semigroup m => t m -> 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 :: forall a. Ord a => t a -> a minimum1 :: forall a. 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. foldr1map :: (a -> b) -> (b -> b -> b) -> t a -> b foldl1'map :: (a -> b) -> (b -> b -> b) -> t a -> b foldl1map :: (a -> b) -> (b -> b -> b) -> t a -> b foldr1'map :: (a -> b) -> (b -> b -> b) -> t a -> b ```
The merge request also adds instances for everything non-empty in `base`.
I propose the `Data.Foldable1` as the module name. `semigroupoids`[^ref6] uses `Data.Semigroup.Foldable`, but it's confusing; and using different name could help migration.
The module contains five top-level functions, which should be self-explanatory:
```haskell intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m
foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a
maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a ```
This is less than in `Data.Semigroup.Foldable`[^ref9], as without `Apply` they don't make sense. For example:
```haskell -- needs Apply, not in Data.Foldable1 traverse1_ :: (Foldable1 t, Apply f) => (a -> f b) -> t a -> f () ```
And if we relax `Apply` to `Applicative`, we get `traverse_`.
[^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 [^ref9]: https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-...
[^ref5]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973
Compatibility & migration -------------------------
I drafted a compatibility package `foldable1` (github[^ref6], haddocks[^ref7]), which I hope could be maintained under github.com/haskell http://github.com/haskell organization. I can act as a maintainer, with a hope that there won't be a lot of changes happening in `Data.Foldable1`.
To my surprise, there's already a package with this name on Hackage[^ref8] by M Farkas-Dyck (cc'd). I hope they would donate the name to Haskell.org http://Haskell.org / CLC; the package won't have any other good use when `Data.Foldable1` is in `base`, then act as a compat package.
`Data.Foldable1` contains also instances for `Lift`, `Backwards` and `Reverse` data types from `transformers`. Perfectly, the `transformers` bundled with GHC with this change would implement the instances as well. This change should propage to `transformers-compat` too.
Similarly, `containers` would have an instance for `Tree` (and non-empty `Set` and `Map` when they are added).
`semigroupoids` would need a bit of work, to depend on `foldable1`, yet the public changes can be kept quite minimal. I don't think that anything in reverse dependencies of `lens` will be broken by this change, if "new" `Foldable1` is re-exported from `semigroupoids`' `Data.Semigroup.Foldable`[^ref9]
Other "compat" packages -- like `tagged`, `bifunctors` -- have to be dealt with case by case. For example whether they should depend on `foldable1` or other way around.
[^ref6]: https://github.com/phadej/foldable1 [^ref7]: https://oleg.fi/haddocks/foldable1/ [^ref8]: https://hackage.haskell.org/package/foldable1 [^ref9]: https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-...
Unresolved questions --------------------
- Should we add `Bifoldable1` too. That should be trivial. - GHC-8.10 freeze is quite soon, is targeting GHC-8.12/base-4.15 more realistic?
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

This is second revision of proposal. Thanks to all commented so far. The changes from the first revision are - Remove `toNonEmpty` from MINIMAL pragma (implementation driven, it seems to be a bad idea to go via toNonEmpty) - Add `Semifoldable` naming-scheme alternative (see sections at the end) - Discuss `Bifoldable1` - Discuss `foldr1` inefficiency - Migration plan for `tagged` and `bifunctors` - PoC patch to `semigroupoids` - `foldable1` package has doctest examples, and a test-suite - more members are manually implemented (and tested) - haddocks regenerated to reflect current state of `foldable1`-package I set the deadline for discussion in two weeks, ending Monday 2019-11-04. - Oleg Add Foldable1 to base ===================== Motivation ---------- It's regularly asked whether `Foldable1` could be added to `base` (e.g. on reddit[^ref1], there're also GHC issue[^ref2] and old phabricator diff[^ref3]) Also there's work towards non-empty maps and sets[^ref4], which would benefit from `Foldable1`. Recently `nonempty-vector` was upload to Hackage as well[^refV]. As commented on reddit, `Foldable1` could be added without any pain to the `base` as it's pure addition - no modifications needed in existing modules. [^ref1]: https://www.reddit.com/r/haskell/comments/6d0vgt/could_we_have_foldable1_and... [^ref2]: https://gitlab.haskell.org/ghc/ghc/issues/13573 [^ref3]: https://phabricator.haskell.org/D4812 [^ref4]: https://github.com/haskell/containers/pull/616 [^refV]: https://hackage.haskell.org/package/nonempty-vector Changelog --------- - Remove `toNonEmpty` from MINIMAL pragma - Add `Semifoldable` naming-scheme alternative (see sections at the end) - Discuss `Bifoldable1` - Discuss `foldr1` inefficiency - Migration plan for `tagged` and `bifunctors` - PoC patch to `semigroupoids` - `foldable1` package has doctest examples, and a test-suite - more members are manually implemented (and tested) - haddocks regenerated to reflect current state of `foldable1`-package Change: Foldable1 ----------------- The change exist as merge request[^ghcMR] on gitlab.haskell.org. However the more up to date version of a proposed module is visible from haddocks on https://oleg.fi/haddocks/foldable1/Data-Foldable1.html or http://oleg.fi/haddocks/semifoldable/Data-Semifoldable.html Importantly, this change **doesn't change** anything in other modules of `base`, except of adding a `Foldable` instance to `Data.Complex`. In particular, `foldl1` and `foldr1` in `Data.Foldable` remain partial, etc. My version of `Foldable1` class is big, so I'll comment the motivation for each member ```haskell 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 :: forall a. Ord a => t a -> a minimum1 :: forall a. 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. -- These will probably change, see foldr1 inefficiency section foldr1Map :: (a -> b) -> (b -> b -> b) -> t a -> b foldl1'Map :: (a -> b) -> (b -> b -> b) -> t a -> b foldl1Map :: (a -> b) -> (b -> b -> b) -> t a -> b foldr1'Map :: (a -> b) -> (b -> b -> b) -> t a -> b ``` The merge request also adds instances for everything non-empty in `base`. I propose the `Data.Foldable1` as the module name (an alternative `Data.Semifoldable`). `semigroupoids`[^semigroupoids] uses `Data.Semigroup.Foldable`, but it's confusing; and using different name could help migration. Additionally, the `Data.Foldable1` module contains five top-level functions, which should be self-explanatory: ```haskell intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a ``` This is less than in `Data.Semigroup.Foldable`[^d.s.foldable], as other top-level definitions doesn't make sense without bringing in the `Apply` type-class. For example: ```haskell -- needs Apply, not in Data.Foldable1 traverse1_ :: (Foldable1 t, Apply f) => (a -> f b) -> t a -> f () ``` And if we relax `Apply` to `Applicative`, we get `traverse_`. Bringing `Apply` into `base` is out-of-scope of this proposal. [^ghcMR]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 [^semigroupoids]: https://hackage.haskell.org/package/semigroupoids [^d.s.foldable]: https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-... Bifoldable1 ----------- `Bifoldable` class have `Bifoldable1` subclass in `semigroupoids`. We could move that class into `base` as well, but it's not strictly necessary, as it can be done later too. However, `Bifoldable1` should migrate to `bifunctors` package. This is discussed in "Compatibility & migration" section. Name controversy ---------------- Adding `Foldable1` is considered controversial. Library submissions guidelines say:
Adding a new, useful function under a clear name is probably not controversial
Yet in this case, there doesn't seem to be clear names. The alternative naming scheme is discussed on `semigroupoids` issue tracker[^naming-issue]. In a comment nickname chessai list a table of possible renamings, essentially dropping `1`-suffix and adding `semi`- prefix.[^refComment1] Following comments brainstorm more ideas like: - all the functions that aren't actual typeclass methods could possibly just keep the `1` suffix - i'm struggling against consistency here, because some functions sound great with `semi`- as their prefix, and some sound bad The bad sounding names are `semihead`, `semilast`, `semimaximum` and `semiminimum`. In theory they could be prefixless and suffixless, i.e. plain `head`, `last`, `maximum`, and `minimum`. However, I consider that naming more controversial, as it clashes with `Prelude` names, even one can argue that `Semifoldable` members should eventually replace them. Luckily, the names can be changed, if they are on the way into `Prelude`. A variation of this, is to use bare `s` as prefix to the members, i.e. `sfoldMap`, `sfoldr`. It's shorter, but maybe too subtle? One justification to not use 1-suffix name is[^refComment2]
The 1 is still in conflict, but requires more Eq1, etc like classes to define. e.g. Monoid1 for taking a monoid to a monoid, then Foldable1 consistently in that nomenclature would let you reduce through a Monoid1.
The haddocks for Semi.Monad being a superclass of Monad someday in
Also using qualified imports would prevent `Foldable1` class to be ever imported unqualified[^refComment3]: the far
flung future would be frankly pretty awful to read, and would ensure that they could never move into Prelude, forever dooming them to a second class existence.
And finally, trying to unify `Foldable` with `Foldable1` into single class using type families / some hackery requires `QuantifiedConstraints` at the very least. That's not a realistic option to current, essentially a Haskell98 formulation. [^naming-issue]: https://github.com/ekmett/semigroupoids/issues/26 [^refComment1]: https://github.com/ekmett/semigroupoids/issues/26#issuecomment-395565772 [^refComment2]: https://github.com/ekmett/semigroupoids/issues/26#issuecomment-395950042 [^refComment3]: https://github.com/ekmett/semigroupoids/issues/26#issuecomment-398117218 Inefficiency of foldr1 ---------------------- In another `semigroupoids` issue[^foldr1-issue], the inefficiency of `foldr1` is highlighted. My original proposal included functions of the type: ```haskell foldr1Map :: (a -> b) -> (b -> b -> b) -> t a -> b ``` Yet, Andrew Martin points out, another better type: ```haskell foldr1Map :: (a -> b) -> (a -> b -> b) -> t a -> b ``` This helps differentiate between foldr and foldl variants, and also simplifies some implementation bits (to my surprise). I'm in favour of this change. The order of function arguments is chosen so: ```haskell foldr1 = foldr1Map id ``` This variant is implemented in a PR in my repository[^foldrPR]. But not yet incorporated into this proposal. [^foldr1-issue]: https://github.com/ekmett/semigroupoids/issues/77 [^foldrPR]: https://github.com/phadej/foldable1/pull/7 Compatibility & migration ------------------------- I drafted a compatibility package `foldable1`: - GitHub repository: https://github.com/phadej/foldable1 - haddocks: https://oleg.fi/haddocks/foldable1/ - Semifoldable variant: https://github.com/phadej/foldable1/pull/5 - its haddocks: https://oleg.fi/haddocks/semifoldable/ which I hope could be maintained under github.com/haskell organization. I can act as a maintainer, with a hope that there won't be a lot of changes happening in `Data.Foldable1`. To my surprise, there's already a package with this name on Hackage[^hackageFoldable] by M Farkas-Dyck (cc'd). He kindly offered to donate the name if this proposal is accepted (with foldable1 name).[^refDonate] `Data.Foldable1` contains also instances for `Lift`, `Backwards` and `Reverse`, and other data types from `transformers`. Perfectly, the `transformers` bundled with GHC with this change would implement the instances as well. This change should propage to `transformers-compat` too. Similarly, `containers` would have an instance for `Tree` (and non-empty `Set` and `Map` when they are added). Other packages would be compat'd as follows: - `foldable1` would provide instances for `Tagged` from `tagged` - `Bifoldable1` class would migrate to `bifunctors` This is because current dependencies are: ``` semigroups <- tagged <- bifunctors <- semigroupoids ``` and `foldable1` would be more natural between `tagged` and `bifunctors`: ``` semigroups <- tagged <- foldable1 <- bifunctors <- semigroupoids ``` `foldable` have to be before `bifunctors` in the dependency tree, as `Bifoldable1` instances of some `Bifunctor`s need `Foldable1` class. I also drafted a PR for compatibility patch to `semigroupoids`[^semigroupoidsPatch] including `Foldable1` part; but doesn't include migrating `Bifoldable, nor other proposed renaming. The rest of renamings is straight-forward should be straight-forward to do. Migration `Bifoldable` would be a lot easier, when the `foldable1` package interface is stabilized. [^hackageFoldable]: https://hackage.haskell.org/package/foldable1 [^refDonate]: https://mail.haskell.org/pipermail/libraries/2019-October/030029.html [^semigroupoidsPatch]: https://github.com/ekmett/semigroupoids/pull/87 Unresolved questions -------------------- - The names? Foldable1 or Semifoldable, members? - Bifoldable1 or Bisemifoldable (or Semibifoldable)? - Members: `semifoldMap` or just `sfoldMap`? See following Foldable1 and Semifoldable sections for synopsis - Which type signature `foldr1Map` / `semifoldr1Map` should have (`a -> b -> b` is IMO better) - GHC-8.10 freeze is quite soon, is targeting GHC-8.12/base-4.15 more realistic. Note: this technically is a non-breaking change in `base`, so could be bundled with GHC-8.10.2, but I think sticking to major would be preferable by GHC HQ. Appendix: Foldable1 synopsis ---------------------------- https://oleg.fi/haddocks/foldable1/Data-Foldable1.html ```haskell class Foldable t => Foldable1 t where fold1 :: Semigroup m => t m -> m foldMap1 :: Semigroup m => (a -> m) -> t a -> m foldMap1' :: Semigroup m => (a -> m) -> t a -> m 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 toNonEmpty :: t a -> NonEmpty a maximum1 :: forall a. Ord a => t a -> a minimum1 :: forall a. Ord a => t a -> a head1 :: t a -> a last1 :: t a -> a foldr1Map :: (a -> b) -> (b -> b -> b) -> t a -> b foldl1'Map :: (a -> b) -> (b -> b -> b) -> t a -> b foldl1Map :: (a -> b) -> (b -> b -> b) -> t a -> b foldr1'Map :: (a -> b) -> (b -> b -> b) -> t a -> b intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a ``` Appendix: Semifoldable synopsis ------------------------------- https://oleg.fi/haddocks/semifoldable/ ```haskell class Foldable t => Semifoldable t where semifold :: Semigroup m => t m -> m semifoldMap :: Semigroup m => (a -> m) -> t a -> m semifoldMap' :: Semigroup m => (a -> m) -> t a -> m semifoldr :: (a -> a -> a) -> t a -> a semifoldr' :: (a -> a -> a) -> t a -> a semifoldl :: (a -> a -> a) -> t a -> a semifoldl' :: (a -> a -> a) -> t a -> a toNonEmpty :: t a -> NonEmpty a semimaximum :: forall a. Ord a => t a -> a semiminimum :: forall a. Ord a => t a -> a semihead :: t a -> a semilast :: t a -> a semifoldrMap :: (a -> b) -> (b -> b -> b) -> t a -> b semifoldl'Map :: (a -> b) -> (b -> b -> b) -> t a -> b semifoldlMap :: (a -> b) -> (b -> b -> b) -> t a -> b semifoldr'Map :: (a -> b) -> (b -> b -> b) -> t a -> b intercalate1 :: (Semifoldable t, Semigroup m) => m -> t m -> m foldrM1 :: (Semifoldable t, Monad m) => (a -> a -> m a) -> t a -> m a foldlM1 :: (Semifoldable t, Monad m) => (a -> a -> m a) -> t a -> m a semimaximumBy :: Semifoldable t => (a -> a -> Ordering) -> t a -> a semiminimumBy :: Semifoldable t => (a -> a -> Ordering) -> t a -> a -- or alternatively semiintercalate semifoldrM semifoldlM ``` Appendix: Alternative foldr1Map ------------------------------- ```haskell class Foldable t => Foldable1 t where fold1 :: Semigroup m => t m -> m foldMap1 :: Semigroup m => (a -> m) -> t a -> m foldMap1' :: Semigroup m => (a -> m) -> t a -> m 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 toNonEmpty :: t a -> NonEmpty a maximum1 :: forall a. Ord a => t a -> a minimum1 :: forall a. Ord a => t a -> a head1 :: t a -> a last1 :: t a -> a -- These four are changed compared to Foldable1 synopsis foldr1Map :: (a -> b) -> (a -> b -> b) -> t a -> b foldl1'Map :: (a -> b) -> (b -> a -> b) -> t a -> b foldl1Map :: (a -> b) -> (b -> a -> b) -> t a -> b foldr1'Map :: (a -> b) -> (a -> b -> b) -> t a -> b intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a ```
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

To keep committee well equipped to make final decision - Show support or disapproval for both proposed naming schemes (Foldable1 and Semifoldable) - If you don't like either, propose new ones Otherwise these proposal will linger forever "because naming is hard". We can do better. To be explicit, I myself is fine with both naming schemes, and either using semi- or just single s- prefix (e.g. sfoldMap). I encourage everyone to brainstorm the names. The proposal mentions some reasons why Foldable1 is not considered good choice. So if you think Semifoldable is not optimal either, now is good opportunity to make history, by inventing a "contravariant" variant of Semi- prefix. - Oleg On 22.10.2019 17.51, John Cotton Ericson wrote:
Echoing Keith's point, "semi" to me means a weaker algebra; i.e. a super-class. Foldable => Semifoldable is thus totally wrong, "Semifoldable" is the sub-class. In particular. The Monoid and Semigroup constraints on their respective methods further show that the fold class hierarchy is *contravariant* with respect to the binary operator class hierarchy. Putting semi-* with semi-* only makes sense for something covariant (e.g. the if methods *returned* `Dict (Semigroup a)` etc).
Semimonad and Semiapplicative are fine with me (I don't really care, not worth fighting one way or the other) but strong -1 on Semifoldable.
John
On 21.10.2019 0.31, Oleg Grenrus wrote:
This is second revision of proposal. Thanks to all commented so far.
The changes from the first revision are
- Remove `toNonEmpty` from MINIMAL pragma (implementation driven, it seems to be a bad idea to go via toNonEmpty) - Add `Semifoldable` naming-scheme alternative (see sections at the end) - Discuss `Bifoldable1` - Discuss `foldr1` inefficiency - Migration plan for `tagged` and `bifunctors` - PoC patch to `semigroupoids` - `foldable1` package has doctest examples, and a test-suite - more members are manually implemented (and tested) - haddocks regenerated to reflect current state of `foldable1`-package
I set the deadline for discussion in two weeks, ending Monday 2019-11-04.
- Oleg
Add Foldable1 to base =====================
Motivation ----------
It's regularly asked whether `Foldable1` could be added to `base` (e.g. on reddit[^ref1], there're also GHC issue[^ref2] and old phabricator diff[^ref3]) Also there's work towards non-empty maps and sets[^ref4], which would benefit from `Foldable1`. Recently `nonempty-vector` was upload to Hackage as well[^refV].
As commented on reddit, `Foldable1` could be added without any pain to the `base` as it's pure addition - no modifications needed in existing modules.
[^ref1]: https://www.reddit.com/r/haskell/comments/6d0vgt/could_we_have_foldable1_and... [^ref2]: https://gitlab.haskell.org/ghc/ghc/issues/13573 [^ref3]: https://phabricator.haskell.org/D4812 [^ref4]: https://github.com/haskell/containers/pull/616 [^refV]: https://hackage.haskell.org/package/nonempty-vector
Changelog ---------
- Remove `toNonEmpty` from MINIMAL pragma - Add `Semifoldable` naming-scheme alternative (see sections at the end) - Discuss `Bifoldable1` - Discuss `foldr1` inefficiency - Migration plan for `tagged` and `bifunctors` - PoC patch to `semigroupoids` - `foldable1` package has doctest examples, and a test-suite - more members are manually implemented (and tested) - haddocks regenerated to reflect current state of `foldable1`-package
Change: Foldable1 -----------------
The change exist as merge request[^ghcMR] on gitlab.haskell.org. However the more up to date version of a proposed module is visible from haddocks on
https://oleg.fi/haddocks/foldable1/Data-Foldable1.html
or
http://oleg.fi/haddocks/semifoldable/Data-Semifoldable.html
Importantly, this change **doesn't change** anything in other modules of `base`, except of adding a `Foldable` instance to `Data.Complex`. In particular, `foldl1` and `foldr1` in `Data.Foldable` remain partial, etc.
My version of `Foldable1` class is big, so I'll comment the motivation for each member
```haskell 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 :: forall a. Ord a => t a -> a minimum1 :: forall a. 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. -- These will probably change, see foldr1 inefficiency section foldr1Map :: (a -> b) -> (b -> b -> b) -> t a -> b foldl1'Map :: (a -> b) -> (b -> b -> b) -> t a -> b foldl1Map :: (a -> b) -> (b -> b -> b) -> t a -> b foldr1'Map :: (a -> b) -> (b -> b -> b) -> t a -> b ```
The merge request also adds instances for everything non-empty in `base`.
I propose the `Data.Foldable1` as the module name (an alternative `Data.Semifoldable`). `semigroupoids`[^semigroupoids] uses `Data.Semigroup.Foldable`, but it's confusing; and using different name could help migration.
Additionally, the `Data.Foldable1` module contains five top-level functions, which should be self-explanatory:
```haskell intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m
foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a
maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a ```
This is less than in `Data.Semigroup.Foldable`[^d.s.foldable], as other top-level definitions doesn't make sense without bringing in the `Apply` type-class. For example:
```haskell -- needs Apply, not in Data.Foldable1 traverse1_ :: (Foldable1 t, Apply f) => (a -> f b) -> t a -> f () ```
And if we relax `Apply` to `Applicative`, we get `traverse_`. Bringing `Apply` into `base` is out-of-scope of this proposal.
[^ghcMR]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 [^semigroupoids]: https://hackage.haskell.org/package/semigroupoids [^d.s.foldable]: https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-...
Bifoldable1 -----------
`Bifoldable` class have `Bifoldable1` subclass in `semigroupoids`. We could move that class into `base` as well, but it's not strictly necessary, as it can be done later too.
However, `Bifoldable1` should migrate to `bifunctors` package. This is discussed in "Compatibility & migration" section.
Name controversy ----------------
Adding `Foldable1` is considered controversial. Library submissions guidelines say:
Adding a new, useful function under a clear name is probably not controversial
Yet in this case, there doesn't seem to be clear names. The alternative naming scheme is discussed on `semigroupoids` issue tracker[^naming-issue].
In a comment nickname chessai list a table of possible renamings, essentially dropping `1`-suffix and adding `semi`- prefix.[^refComment1] Following comments brainstorm more ideas like:
- all the functions that aren't actual typeclass methods could possibly just keep the `1` suffix - i'm struggling against consistency here, because some functions sound great with `semi`- as their prefix, and some sound bad
The bad sounding names are `semihead`, `semilast`, `semimaximum` and `semiminimum`. In theory they could be prefixless and suffixless, i.e. plain `head`, `last`, `maximum`, and `minimum`. However, I consider that naming more controversial, as it clashes with `Prelude` names, even one can argue that `Semifoldable` members should eventually replace them. Luckily, the names can be changed, if they are on the way into `Prelude`.
A variation of this, is to use bare `s` as prefix to the members, i.e. `sfoldMap`, `sfoldr`. It's shorter, but maybe too subtle?
One justification to not use 1-suffix name is[^refComment2]
The 1 is still in conflict, but requires more Eq1, etc like classes to define. e.g. Monoid1 for taking a monoid to a monoid, then Foldable1 consistently in that nomenclature would let you reduce through a Monoid1.
Also using qualified imports would prevent `Foldable1` class to be ever imported unqualified[^refComment3]:
The haddocks for Semi.Monad being a superclass of Monad someday in the far flung future would be frankly pretty awful to read, and would ensure that they could never move into Prelude, forever dooming them to a second class existence.
And finally, trying to unify `Foldable` with `Foldable1` into single class using type families / some hackery requires `QuantifiedConstraints` at the very least. That's not a realistic option to current, essentially a Haskell98 formulation.
[^naming-issue]: https://github.com/ekmett/semigroupoids/issues/26 [^refComment1]: https://github.com/ekmett/semigroupoids/issues/26#issuecomment-395565772 [^refComment2]: https://github.com/ekmett/semigroupoids/issues/26#issuecomment-395950042 [^refComment3]: https://github.com/ekmett/semigroupoids/issues/26#issuecomment-398117218
Inefficiency of foldr1 ----------------------
In another `semigroupoids` issue[^foldr1-issue], the inefficiency of `foldr1` is highlighted.
My original proposal included functions of the type:
```haskell foldr1Map :: (a -> b) -> (b -> b -> b) -> t a -> b ```
Yet, Andrew Martin points out, another better type:
```haskell foldr1Map :: (a -> b) -> (a -> b -> b) -> t a -> b ```
This helps differentiate between foldr and foldl variants, and also simplifies some implementation bits (to my surprise). I'm in favour of this change.
The order of function arguments is chosen so:
```haskell foldr1 = foldr1Map id ```
This variant is implemented in a PR in my repository[^foldrPR]. But not yet incorporated into this proposal.
[^foldr1-issue]: https://github.com/ekmett/semigroupoids/issues/77 [^foldrPR]: https://github.com/phadej/foldable1/pull/7
Compatibility & migration -------------------------
I drafted a compatibility package `foldable1`:
- GitHub repository: https://github.com/phadej/foldable1 - haddocks: https://oleg.fi/haddocks/foldable1/ - Semifoldable variant: https://github.com/phadej/foldable1/pull/5 - its haddocks: https://oleg.fi/haddocks/semifoldable/
which I hope could be maintained under github.com/haskell organization. I can act as a maintainer, with a hope that there won't be a lot of changes happening in `Data.Foldable1`.
To my surprise, there's already a package with this name on Hackage[^hackageFoldable] by M Farkas-Dyck (cc'd). He kindly offered to donate the name if this proposal is accepted (with foldable1 name).[^refDonate]
`Data.Foldable1` contains also instances for `Lift`, `Backwards` and `Reverse`, and other data types from `transformers`. Perfectly, the `transformers` bundled with GHC with this change would implement the instances as well. This change should propage to `transformers-compat` too.
Similarly, `containers` would have an instance for `Tree` (and non-empty `Set` and `Map` when they are added).
Other packages would be compat'd as follows: - `foldable1` would provide instances for `Tagged` from `tagged` - `Bifoldable1` class would migrate to `bifunctors`
This is because current dependencies are:
``` semigroups <- tagged <- bifunctors <- semigroupoids ```
and `foldable1` would be more natural between `tagged` and `bifunctors`:
``` semigroups <- tagged <- foldable1 <- bifunctors <- semigroupoids ```
`foldable` have to be before `bifunctors` in the dependency tree, as `Bifoldable1` instances of some `Bifunctor`s need `Foldable1` class.
I also drafted a PR for compatibility patch to `semigroupoids`[^semigroupoidsPatch] including `Foldable1` part; but doesn't include migrating `Bifoldable, nor other proposed renaming.
The rest of renamings is straight-forward should be straight-forward to do. Migration `Bifoldable` would be a lot easier, when the `foldable1` package interface is stabilized.
[^hackageFoldable]: https://hackage.haskell.org/package/foldable1 [^refDonate]: https://mail.haskell.org/pipermail/libraries/2019-October/030029.html [^semigroupoidsPatch]: https://github.com/ekmett/semigroupoids/pull/87
Unresolved questions --------------------
- The names? Foldable1 or Semifoldable, members? - Bifoldable1 or Bisemifoldable (or Semibifoldable)? - Members: `semifoldMap` or just `sfoldMap`? See following Foldable1 and Semifoldable sections for synopsis - Which type signature `foldr1Map` / `semifoldr1Map` should have (`a -> b -> b` is IMO better) - GHC-8.10 freeze is quite soon, is targeting GHC-8.12/base-4.15 more realistic. Note: this technically is a non-breaking change in `base`, so could be bundled with GHC-8.10.2, but I think sticking to major would be preferable by GHC HQ.
Appendix: Foldable1 synopsis ----------------------------
https://oleg.fi/haddocks/foldable1/Data-Foldable1.html
```haskell class Foldable t => Foldable1 t where fold1 :: Semigroup m => t m -> m foldMap1 :: Semigroup m => (a -> m) -> t a -> m foldMap1' :: Semigroup m => (a -> m) -> t a -> m
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
toNonEmpty :: t a -> NonEmpty a
maximum1 :: forall a. Ord a => t a -> a minimum1 :: forall a. Ord a => t a -> a head1 :: t a -> a last1 :: t a -> a
foldr1Map :: (a -> b) -> (b -> b -> b) -> t a -> b foldl1'Map :: (a -> b) -> (b -> b -> b) -> t a -> b foldl1Map :: (a -> b) -> (b -> b -> b) -> t a -> b foldr1'Map :: (a -> b) -> (b -> b -> b) -> t a -> b
intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a ```
Appendix: Semifoldable synopsis -------------------------------
https://oleg.fi/haddocks/semifoldable/
```haskell class Foldable t => Semifoldable t where semifold :: Semigroup m => t m -> m semifoldMap :: Semigroup m => (a -> m) -> t a -> m semifoldMap' :: Semigroup m => (a -> m) -> t a -> m
semifoldr :: (a -> a -> a) -> t a -> a semifoldr' :: (a -> a -> a) -> t a -> a semifoldl :: (a -> a -> a) -> t a -> a semifoldl' :: (a -> a -> a) -> t a -> a
toNonEmpty :: t a -> NonEmpty a
semimaximum :: forall a. Ord a => t a -> a semiminimum :: forall a. Ord a => t a -> a semihead :: t a -> a semilast :: t a -> a
semifoldrMap :: (a -> b) -> (b -> b -> b) -> t a -> b semifoldl'Map :: (a -> b) -> (b -> b -> b) -> t a -> b semifoldlMap :: (a -> b) -> (b -> b -> b) -> t a -> b semifoldr'Map :: (a -> b) -> (b -> b -> b) -> t a -> b
intercalate1 :: (Semifoldable t, Semigroup m) => m -> t m -> m foldrM1 :: (Semifoldable t, Monad m) => (a -> a -> m a) -> t a -> m a foldlM1 :: (Semifoldable t, Monad m) => (a -> a -> m a) -> t a -> m a semimaximumBy :: Semifoldable t => (a -> a -> Ordering) -> t a -> a semiminimumBy :: Semifoldable t => (a -> a -> Ordering) -> t a -> a
-- or alternatively semiintercalate semifoldrM semifoldlM ```
Appendix: Alternative foldr1Map -------------------------------
```haskell class Foldable t => Foldable1 t where fold1 :: Semigroup m => t m -> m foldMap1 :: Semigroup m => (a -> m) -> t a -> m foldMap1' :: Semigroup m => (a -> m) -> t a -> m
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
toNonEmpty :: t a -> NonEmpty a
maximum1 :: forall a. Ord a => t a -> a minimum1 :: forall a. Ord a => t a -> a head1 :: t a -> a last1 :: t a -> a
-- These four are changed compared to Foldable1 synopsis foldr1Map :: (a -> b) -> (a -> b -> b) -> t a -> b foldl1'Map :: (a -> b) -> (b -> a -> b) -> t a -> b foldl1Map :: (a -> b) -> (b -> a -> b) -> t a -> b foldr1'Map :: (a -> b) -> (a -> b -> b) -> t a -> b
intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a ```
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

This is the third revision of the proposal. The rendered version is available at https://oleg.fi/foldable1-proposal3.html I'm submitting this to CLC for decision making. Best regards, Oleg Grenrus Add Foldable1 and Bifoldable1 to base ===================================== Motivation ---------- It's regularly asked whether `Foldable1` could be added to `base` (e.g. on reddit[^ref1], there're also GHC issue[^ref2] and old phabricator diff[^ref3]) Also there's work towards non-empty maps and sets[^ref4], which would benefit from `Foldable1`. Recently `nonempty-vector` was uploaded to Hackage as well[^refV]. As commented on reddit, `Foldable1` could be added without any pain to the `base` as it's pure addition - no modifications needed in existing modules. The most difficult question is the names: `Foldable1`, `Semifoldable`, `NonEmptyFoldable`, or something else? [^ref1]: https://www.reddit.com/r/haskell/comments/6d0vgt/could_we_have_foldable1_and... [^ref2]: https://gitlab.haskell.org/ghc/ghc/issues/13573 [^ref3]: https://phabricator.haskell.org/D4812 [^ref4]: https://github.com/haskell/containers/pull/616 [^refV]: https://hackage.haskell.org/package/nonempty-vector Changelog --------- <h3>Revision 3</h3> - Propose moving `Bifoldable1` (`Semibifoldable`) to `base` as well. Move compat `Bifoldable1` to `bifunctors`. - Changed the type of `foldrMap1` to be `(a -> b) -> (a -> b -> b) -> t a -> b` - Add `foldrMapM1` and `foldlMapM1`. These methods could use just `Bind` (`Semimonad`), but as that's not available in base, they don't. `semigroupoids` could provide such variants. - Third naming variant: `NonEmptyFoldable` with `foldMapNE`; and few other variations mentioned. - Patches: https://github.com/ekmett/bifunctors/pull/78 https://github.com/ekmett/semigroupoids/pull/87 <h3>Revision 2</h3> - Remove `toNonEmpty` from MINIMAL pragma - Add `Semifoldable` naming-scheme alternative (see sections at the end) - Discuss `Bifoldable1` - Discuss `foldr1` inefficiency - Migration plan for `tagged` and `bifunctors` - PoC patch to `semigroupoids` - `foldable1` package has doctest examples, and a test-suite - more members are manually implemented (and tested) Change: Foldable1 ----------------- The change exist as merge request[^ghcMR] on gitlab.haskell.org. However the more up to date version of a proposed module is visible from haddocks on
or
Importantly, this change **doesn't change** anything in other modules of `base`, except of adding a `Foldable` instance to `Data.Complex`. In particular, `foldl1` and `foldr1` in `Data.Foldable` remain partial, etc. My version of `Foldable1` class is big, so I'll comment the motivation for each member ```haskell 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 foldl'Map1 :: (a -> b) -> (b -> b -> b) -> t a -> b foldlMap1 :: (a -> b) -> (b -> b -> b) -> t a -> b foldr'Map1 :: (a -> b) -> (b -> b -> b) -> t a -> b ``` The merge request also adds instances for everything non-empty in `base`. I propose the `Data.Foldable1` as the module name (an alternative `Data.Semifoldable`). `semigroupoids`[^semigroupoids] uses `Data.Semigroup.Foldable`, but it's confusing; and using different name could help migration. Additionally, the `Data.Foldable1` module contains seven top-level functions, which should be self-explanatory: ```haskell intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a foldrMapM1 :: (Foldable1 t, Monad m) => (a -> m b) -> (a -> b -> m b) -> t a -> m b foldlMapM1 :: (Foldable1 t, Monad m) => (a -> m b) -> (b -> a -> m b) -> t a -> m b maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a ``` This is less than in `Data.Semigroup.Foldable`[^d.s.foldable], as other top-level definitions doesn't make sense without bringing in the `Apply` type-class. For example: ```haskell -- needs Apply, not in Data.Foldable1 traverse1_ :: (Foldable1 t, Apply f) => (a -> f b) -> t a -> f () ``` And if we relax `Apply` to `Applicative`, we get `traverse_`. Bringing `Apply` into `base` is out-of-scope of this proposal. [^ghcMR]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 [^semigroupoids]: https://hackage.haskell.org/package/semigroupoids [^d.s.foldable]: https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-... Bifoldable1 ----------- `Bifoldable` class have `Bifoldable1` subclass in `semigroupoids`. We propose moving that class to `base` as well. The propose module would be very tiny and simple. ```haskell class Bifoldable t => Bifoldable1 t where bifold1 :: Semigroup m => t m m -> m bifold1 = bifoldMap1 id id {-# INLINE bifold1 #-} bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> t a b -> m bifoldMap1 f g = maybe (error "bifoldMap1") id . getOption . bifoldMap (Option . Just . f) (Option . Just . g) {-# INLINE bifoldMap1 #-} ``` or using `Semi` prefix: ```haskell class Bifoldable t => Semibifoldable t where semibifold :: Semigroup m => t m m -> m semibifold = semibifoldMap id id {-# INLINE semibifold #-} semibifoldMap :: Semigroup m => (a -> m) -> (b -> m) -> t a b -> m semibifoldMap f g = maybe (error "semibifoldMap") id . getOption . bifoldMap (Option . Just . f) (Option . Just . g) {-# INLINE semibifoldMap #-} ``` There is a pull-request to `bifunctors`[^bifunctorPR], as a proof-of-concept, using `Semibifoldable` naming scheme. `Bisemifoldable` is also a variant, yet `Semibifoldable` sounds more correct: take `Bifoldable` and remove empty things resulting into `Semibifoldable`. [^bifunctorPR]: https://github.com/ekmett/bifunctors/pull/78 Name controversy ---------------- Adding `Foldable1` is considered controversial. Library submissions guidelines say:
Adding a new, useful function under a clear name is probably not controversial
Yet in this case, there doesn't seem to be clear names. The alternative naming scheme is discussed on `semigroupoids` issue tracker[^naming-issue]. In a comment nickname chessai list a table of possible renamings, essentially dropping `1`-suffix and adding `semi`- prefix.[^refComment1] Following comments brainstorm more ideas like: - all the functions that aren't actual typeclass methods could possibly just keep the `1` suffix - I'm struggling against consistency here, because some functions sound great with `semi`- as their prefix, and some sound bad The bad sounding names are `semihead`, `semilast`, `semimaximum` and `semiminimum`. In theory they could be prefixless and suffixless, i.e. plain `head`, `last`, `maximum`, and `minimum`. However, I consider that naming more controversial, as it clashes with `Prelude` names, even one can argue that `Semifoldable` members should eventually replace them. Luckily, the names can be changed, if they are on the way into `Prelude`. A variation of this, is to use bare `s` as prefix to the members, i.e. `sfoldMap`, `sfoldr`. It's shorter, but maybe too subtle? One justification to not use 1-suffix name is[^refComment2]
The 1 is still in conflict, but requires more Eq1, etc like classes to define. e.g. Monoid1 for taking a monoid to a monoid, then Foldable1 consistently in that nomenclature would let you reduce through a Monoid1.
The haddocks for Semi.Monad being a superclass of Monad someday in
Also using qualified imports would prevent `Foldable1` class to be ever imported unqualified[^refComment3]: the far
flung future would be frankly pretty awful to read, and would ensure that they could never move into Prelude, forever dooming them to a second class existence.
And finally, trying to unify `Foldable` with `Foldable1` into single class using type families / some hackery requires `QuantifiedConstraints` at the very least. That's not a realistic option to current, essentially a Haskell98 formulation. On the other hand few people noted[^bikeshedding] that where `Semiapplicative` and `Semimonad` would be good names for what's currently called `Apply` and `Bind`, `Semifoldable` feels like a superclass of `Foldable`, i.e. ```haskell -- feels like class Semifoldable f => Foldable f where ``` ```haskell class Foldable f => Semifoldable f where ``` Alternatives mentioned are ```haskell -- class prefix NonEmpty, -- method prefix bare s class Foldable f => NonEmptyFoldable f where sfoldMap :: Semigroup s => (a -> s) -> f a -> s sminimum :: Ord a => f a -> a shead :: f a -> a class Bifoldable p => NonEmptyBifoldable p where sbifoldMap :: Semigroup s => (a -> s) -> (b -> s) -> p a b -> s -- or alternatively: method prefix `ne` (for nonempty): nefoldMap neminimum nehead nebifoldMap -- or suffix `NE` foldMapNE minimumNE headNE bifoldMapNE ``` The last function naming scheme is used in `containers` patch[^containersNEpatch], which adds `NonEmptyMap`. Using this scheme `Traversable1` will become ```haskell class Traversable t => NonEmptyTraversable t where traverseNE :: SemiApplicative f => (a -> f b) -> t a -> f (t b) ``` [^naming-issue]: https://github.com/ekmett/semigroupoids/issues/26 [^refComment1]: https://github.com/ekmett/semigroupoids/issues/26#issuecomment-395565772 [^refComment2]: https://github.com/ekmett/semigroupoids/issues/26#issuecomment-395950042 [^refComment3]: https://github.com/ekmett/semigroupoids/issues/26#issuecomment-398117218 [^bikeshedding]: https://mail.haskell.org/pipermail/libraries/2019-October/030036.html [^containersNEpatch]: https://github.com/haskell/containers/pull/616 Inefficiency of foldr1 ---------------------- In another `semigroupoids` issue[^foldr1-issue], the inefficiency of `foldr1` is highlighted. The proposal includes functions like: ```haskell foldrMap1 :: (a -> b) -> (a -> b -> b) -> t a -> b foldlMap1 :: (a -> b) -> (b -> a -> b) -> t a -> b ``` And in fact the minimal pragma is `{-# MINIMAL foldMap1 | foldrMap1 #-}` The order of function arguments is chosen so: ```haskell foldr1 = foldr1Map id ``` Another option is to have function arguments flipped: ```haskell foldrMap1 :: (a -> b -> b) -> (a -> b) -> t a -> b foldlMap1 :: (b -> a -> b) -> (a -> b) -> t a -> b ``` which more closely resembles `foldr` and `foldl`. The start element of a fold is `seed` with the right or the left element. [^foldr1-issue]: https://github.com/ekmett/semigroupoids/issues/77 Compatibility & migration ------------------------- I drafted a compatibility package `foldable1`: - GitHub repository: https://github.com/phadej/foldable1 - haddocks: https://oleg.fi/haddocks/foldable1/ - Semifoldable variant: https://github.com/phadej/foldable1/pull/5 - its haddocks: https://oleg.fi/haddocks/semifoldable/ which I hope could be maintained under github.com/haskell organization. I can act as a maintainer, with a hope that there won't be a lot of changes happening in `Data.Foldable1`. To my surprise, there's already a package with this name on Hackage[^hackageFoldable] by M Farkas-Dyck (cc'd). He kindly offered to donate the name if this proposal is accepted (with foldable1 name).[^refDonate] `Data.Foldable1` contains also instances for `Lift`, `Backwards` and `Reverse`, and other data types from `transformers`. Perfectly, the `transformers` bundled with GHC with this change would implement the instances as well. This change should propagate to `transformers-compat` too. Similarly, `containers` would have an instance for `Tree` (and non-empty `Set` and `Map` when they are added). Other packages would be compat'd as follows: - `foldable1` would provide instances for `Tagged` from `tagged` - `Bifoldable1` class would migrate to `bifunctors` This is because current dependencies are: ``` semigroups <- tagged <- bifunctors <- semigroupoids ``` and `foldable1` would be more natural between `tagged` and `bifunctors`: ``` semigroups <- tagged <- foldable1 <- bifunctors <- semigroupoids ``` `foldable` have to be before `bifunctors` in the dependency tree, as `Bifoldable1` instances of some bifunctors need `Foldable1` class. I also drafted a pull requests for compatibility patches to `bifunctors`[^bifunctorsPatch] and `semigroupoids`[^semigroupoidsPatch] with [^hackageFoldable]: https://hackage.haskell.org/package/foldable1 [^refDonate]: https://mail.haskell.org/pipermail/libraries/2019-October/030029.html [^bifunctorsPatch]: https://github.com/ekmett/bifunctors/pull/78 [^semigroupoidsPatch]: https://github.com/ekmett/semigroupoids/pull/87 Unresolved questions -------------------- - The names? Foldable1 or Semifoldable, members? - Bifoldable1 or Semibifoldable (or Bisemifoldable)? - Members: `semifoldMap` or just `sfoldMap`? See following Foldable1 and Semifoldable sections for synopsis - GHC-8.10 freeze is quite soon, is targeting GHC-8.12/base-4.15 more realistic. Note: this technically is a non-breaking change in `base`, so could be bundled with GHC-8.10.2, but I think sticking to major would be preferable by GHC HQ. Appendix: Foldable1 synopsis ---------------------------- Module name: `Data.Foldable1` and `Data.Bifoldable1` https://oleg.fi/haddocks/foldable1/Data-Foldable1.html ```haskell class Foldable t => Foldable1 t where fold1 :: Semigroup m => t m -> m foldMap1 :: Semigroup m => (a -> m) -> t a -> m foldMap1' :: Semigroup m => (a -> m) -> t a -> m 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 toNonEmpty :: t a -> NonEmpty a maximum1 :: Ord a => t a -> a minimum1 :: Ord a => t a -> a head1 :: t a -> a last1 :: t a -> a foldrMap1 :: (a -> b) -> (b -> b -> b) -> t a -> b foldl'Map1 :: (a -> b) -> (b -> b -> b) -> t a -> b foldlMap1 :: (a -> b) -> (b -> b -> b) -> t a -> b foldr'Map1 :: (a -> b) -> (b -> b -> b) -> t a -> b intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a foldrMapM1 :: (Foldable1 t, Monad m) => (a -> m b) -> (a -> b -> m b) -> t a -> m b foldlMapM1 :: (Foldable1 t, Monad m) => (a -> m b) -> (b -> a -> m b) -> t a -> m b maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a class Bifunctor p => Bifunctor1 p where bifoldMap1 :: Semigroup s => (a -> s) -> (b -> s) -> p a b -> s ``` Appendix: Semifoldable synopsis ------------------------------- Module names`: `Data.Semifoldable` and `Data.Semibifoldable` https://oleg.fi/haddocks/semifoldable/ ```haskell class Foldable t => Semifoldable t where semifold :: Semigroup m => t m -> m semifoldMap :: Semigroup m => (a -> m) -> t a -> m semifoldMap' :: Semigroup m => (a -> m) -> t a -> m semifoldr :: (a -> a -> a) -> t a -> a semifoldr' :: (a -> a -> a) -> t a -> a semifoldl :: (a -> a -> a) -> t a -> a semifoldl' :: (a -> a -> a) -> t a -> a toNonEmpty :: t a -> NonEmpty a semimaximum :: Ord a => t a -> a semiminimum :: Ord a => t a -> a semihead :: t a -> a semilast :: t a -> a semifoldrMap :: (a -> b) -> (b -> b -> b) -> t a -> b semifoldl'Map :: (a -> b) -> (b -> b -> b) -> t a -> b semifoldlMap :: (a -> b) -> (b -> b -> b) -> t a -> b semifoldr'Map :: (a -> b) -> (b -> b -> b) -> t a -> b intercalate1 :: (Semifoldable t, Semigroup m) => m -> t m -> m semifoldrM :: (Semifoldable t, Monad m) => (a -> a -> m a) -> t a -> m a semifoldlM :: (Semifoldable t, Monad m) => (a -> a -> m a) -> t a -> m a semifoldrMapM :: (Foldable1 t, Monad m) => (a -> m b) -> (a -> b -> m b) -> t a -> m b semifoldlMapM :: (Foldable1 t, Monad m) => (a -> m b) -> (b -> a -> m b) -> t a -> m b semimaximumBy :: Semifoldable t => (a -> a -> Ordering) -> t a -> a semiminimumBy :: Semifoldable t => (a -> a -> Ordering) -> t a -> a -- or alternatively semiintercalate class Bifunctor p => NonEmptyBifunctor p where semifoldMap :: Semigroup s => (a -> s) -> (b -> s) -> p a b -> s ``` Appendix: NonEmptyFoldable synopsis ------------------------------- Module name: `Data.Foldable.NonEmpty` and `Data.Bifoldable.NonEmpty` ```haskell class Foldable t => NonEmptyFoldable t where foldNE :: Semigroup m => t m -> m foldMapNE :: Semigroup m => (a -> m) -> t a -> m foldMapNE' :: Semigroup m => (a -> m) -> t a -> m foldrNE :: (a -> a -> a) -> t a -> a foldrNE' :: (a -> a -> a) -> t a -> a foldlNE :: (a -> a -> a) -> t a -> a foldlNE' :: (a -> a -> a) -> t a -> a toNonEmpty :: t a -> NonEmpty a maximumNE :: Ord a => t a -> a minimumNE :: Ord a => t a -> a headNE :: t a -> a lastNE :: t a -> a foldrMapNE :: (a -> b) -> (b -> b -> b) -> t a -> b foldl'MapNE :: (a -> b) -> (b -> b -> b) -> t a -> b foldlMapNE :: (a -> b) -> (b -> b -> b) -> t a -> b foldr'MapNE :: (a -> b) -> (b -> b -> b) -> t a -> b intercalateNE :: (NonEmptyFoldable t, Semigroup m) => m -> t m -> m foldrMNE :: (NonEmptyFoldable t, Monad m) => (a -> a -> m a) -> t a -> m a foldlMNE :: (NonEmptyFoldable t, Monad m) => (a -> a -> m a) -> t a -> m a foldrMapMNE :: (NonEmptyFoldable t, Monad m) => (a -> m b) -> (a -> b -> m b) -> t a -> m b foldlMapMNE :: (NonEmptyFoldable t, Monad m) => (a -> m b) -> (b -> a -> m b) -> t a -> m b maximumNEBy :: NonEmptyFoldable t => (a -> a -> Ordering) -> t a -> a minimumNEBy :: NonEmptyFoldable t => (a -> a -> Ordering) -> t a -> a class Bifunctor p => NonEmptyBifunctor p where bifoldMapNE :: Semigroup s => (a -> s) -> (b -> s) -> p a b -> s ```

Friendly ping, have committee started discussion on this proposal? - Oleg On 4.11.2019 10.15, Oleg Grenrus wrote:
This is the third revision of the proposal.
The rendered version is available at https://oleg.fi/foldable1-proposal3.html
I'm submitting this to CLC for decision making.
Best regards, Oleg Grenrus
Add Foldable1 and Bifoldable1 to base =====================================
Motivation ----------
It's regularly asked whether `Foldable1` could be added to `base` (e.g. on reddit[^ref1], there're also GHC issue[^ref2] and old phabricator diff[^ref3]) Also there's work towards non-empty maps and sets[^ref4], which would benefit from `Foldable1`. Recently `nonempty-vector` was uploaded to Hackage as well[^refV].
As commented on reddit, `Foldable1` could be added without any pain to the `base` as it's pure addition - no modifications needed in existing modules.
The most difficult question is the names: `Foldable1`, `Semifoldable`, `NonEmptyFoldable`, or something else?
[^ref1]: https://www.reddit.com/r/haskell/comments/6d0vgt/could_we_have_foldable1_and... [^ref2]: https://gitlab.haskell.org/ghc/ghc/issues/13573 [^ref3]: https://phabricator.haskell.org/D4812 [^ref4]: https://github.com/haskell/containers/pull/616 [^refV]: https://hackage.haskell.org/package/nonempty-vector
Changelog ---------
<h3>Revision 3</h3>
- Propose moving `Bifoldable1` (`Semibifoldable`) to `base` as well. Move compat `Bifoldable1` to `bifunctors`. - Changed the type of `foldrMap1` to be `(a -> b) -> (a -> b -> b) -> t a -> b` - Add `foldrMapM1` and `foldlMapM1`. These methods could use just `Bind` (`Semimonad`), but as that's not available in base, they don't. `semigroupoids` could provide such variants. - Third naming variant: `NonEmptyFoldable` with `foldMapNE`; and few other variations mentioned. - Patches: https://github.com/ekmett/bifunctors/pull/78 https://github.com/ekmett/semigroupoids/pull/87
<h3>Revision 2</h3>
- Remove `toNonEmpty` from MINIMAL pragma - Add `Semifoldable` naming-scheme alternative (see sections at the end) - Discuss `Bifoldable1` - Discuss `foldr1` inefficiency - Migration plan for `tagged` and `bifunctors` - PoC patch to `semigroupoids` - `foldable1` package has doctest examples, and a test-suite - more members are manually implemented (and tested)
Change: Foldable1 -----------------
The change exist as merge request[^ghcMR] on gitlab.haskell.org. However the more up to date version of a proposed module is visible from haddocks on
or
Importantly, this change **doesn't change** anything in other modules of `base`, except of adding a `Foldable` instance to `Data.Complex`. In particular, `foldl1` and `foldr1` in `Data.Foldable` remain partial, etc.
My version of `Foldable1` class is big, so I'll comment the motivation for each member
```haskell 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 foldl'Map1 :: (a -> b) -> (b -> b -> b) -> t a -> b foldlMap1 :: (a -> b) -> (b -> b -> b) -> t a -> b foldr'Map1 :: (a -> b) -> (b -> b -> b) -> t a -> b ```
The merge request also adds instances for everything non-empty in `base`.
I propose the `Data.Foldable1` as the module name (an alternative `Data.Semifoldable`). `semigroupoids`[^semigroupoids] uses `Data.Semigroup.Foldable`, but it's confusing; and using different name could help migration.
Additionally, the `Data.Foldable1` module contains seven top-level functions, which should be self-explanatory:
```haskell intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m
foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a
foldrMapM1 :: (Foldable1 t, Monad m) => (a -> m b) -> (a -> b -> m b) -> t a -> m b foldlMapM1 :: (Foldable1 t, Monad m) => (a -> m b) -> (b -> a -> m b) -> t a -> m b
maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a ```
This is less than in `Data.Semigroup.Foldable`[^d.s.foldable], as other top-level definitions doesn't make sense without bringing in the `Apply` type-class. For example:
```haskell -- needs Apply, not in Data.Foldable1 traverse1_ :: (Foldable1 t, Apply f) => (a -> f b) -> t a -> f () ```
And if we relax `Apply` to `Applicative`, we get `traverse_`. Bringing `Apply` into `base` is out-of-scope of this proposal.
[^ghcMR]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1973 [^semigroupoids]: https://hackage.haskell.org/package/semigroupoids [^d.s.foldable]: https://hackage.haskell.org/package/semigroupoids-5.3.3/docs/Data-Semigroup-...
Bifoldable1 -----------
`Bifoldable` class have `Bifoldable1` subclass in `semigroupoids`. We propose moving that class to `base` as well.
The propose module would be very tiny and simple.
```haskell class Bifoldable t => Bifoldable1 t where bifold1 :: Semigroup m => t m m -> m bifold1 = bifoldMap1 id id {-# INLINE bifold1 #-}
bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> t a b -> m bifoldMap1 f g = maybe (error "bifoldMap1") id . getOption . bifoldMap (Option . Just . f) (Option . Just . g) {-# INLINE bifoldMap1 #-} ```
or using `Semi` prefix:
```haskell class Bifoldable t => Semibifoldable t where semibifold :: Semigroup m => t m m -> m semibifold = semibifoldMap id id {-# INLINE semibifold #-}
semibifoldMap :: Semigroup m => (a -> m) -> (b -> m) -> t a b -> m semibifoldMap f g = maybe (error "semibifoldMap") id . getOption . bifoldMap (Option . Just . f) (Option . Just . g) {-# INLINE semibifoldMap #-} ```
There is a pull-request to `bifunctors`[^bifunctorPR], as a proof-of-concept, using `Semibifoldable` naming scheme.
`Bisemifoldable` is also a variant, yet `Semibifoldable` sounds more correct: take `Bifoldable` and remove empty things resulting into `Semibifoldable`.
[^bifunctorPR]: https://github.com/ekmett/bifunctors/pull/78
Name controversy ----------------
Adding `Foldable1` is considered controversial. Library submissions guidelines say:
Adding a new, useful function under a clear name is probably not controversial
Yet in this case, there doesn't seem to be clear names. The alternative naming scheme is discussed on `semigroupoids` issue tracker[^naming-issue].
In a comment nickname chessai list a table of possible renamings, essentially dropping `1`-suffix and adding `semi`- prefix.[^refComment1] Following comments brainstorm more ideas like:
- all the functions that aren't actual typeclass methods could possibly just keep the `1` suffix - I'm struggling against consistency here, because some functions sound great with `semi`- as their prefix, and some sound bad
The bad sounding names are `semihead`, `semilast`, `semimaximum` and `semiminimum`. In theory they could be prefixless and suffixless, i.e. plain `head`, `last`, `maximum`, and `minimum`. However, I consider that naming more controversial, as it clashes with `Prelude` names, even one can argue that `Semifoldable` members should eventually replace them. Luckily, the names can be changed, if they are on the way into `Prelude`.
A variation of this, is to use bare `s` as prefix to the members, i.e. `sfoldMap`, `sfoldr`. It's shorter, but maybe too subtle?
One justification to not use 1-suffix name is[^refComment2]
The 1 is still in conflict, but requires more Eq1, etc like classes to define. e.g. Monoid1 for taking a monoid to a monoid, then Foldable1 consistently in that nomenclature would let you reduce through a Monoid1.
Also using qualified imports would prevent `Foldable1` class to be ever imported unqualified[^refComment3]:
The haddocks for Semi.Monad being a superclass of Monad someday in the far flung future would be frankly pretty awful to read, and would ensure that they could never move into Prelude, forever dooming them to a second class existence.
And finally, trying to unify `Foldable` with `Foldable1` into single class using type families / some hackery requires `QuantifiedConstraints` at the very least. That's not a realistic option to current, essentially a Haskell98 formulation.
On the other hand few people noted[^bikeshedding] that where `Semiapplicative` and `Semimonad` would be good names for what's currently called `Apply` and `Bind`, `Semifoldable` feels like a superclass of `Foldable`, i.e.
```haskell -- feels like class Semifoldable f => Foldable f where ```
```haskell class Foldable f => Semifoldable f where ```
Alternatives mentioned are
```haskell -- class prefix NonEmpty, -- method prefix bare s class Foldable f => NonEmptyFoldable f where sfoldMap :: Semigroup s => (a -> s) -> f a -> s
sminimum :: Ord a => f a -> a shead :: f a -> a
class Bifoldable p => NonEmptyBifoldable p where sbifoldMap :: Semigroup s => (a -> s) -> (b -> s) -> p a b -> s
-- or alternatively: method prefix `ne` (for nonempty):
nefoldMap neminimum nehead nebifoldMap
-- or suffix `NE`
foldMapNE minimumNE headNE bifoldMapNE ```
The last function naming scheme is used in `containers` patch[^containersNEpatch], which adds `NonEmptyMap`. Using this scheme `Traversable1` will become
```haskell class Traversable t => NonEmptyTraversable t where traverseNE :: SemiApplicative f => (a -> f b) -> t a -> f (t b) ```
[^naming-issue]: https://github.com/ekmett/semigroupoids/issues/26 [^refComment1]: https://github.com/ekmett/semigroupoids/issues/26#issuecomment-395565772 [^refComment2]: https://github.com/ekmett/semigroupoids/issues/26#issuecomment-395950042 [^refComment3]: https://github.com/ekmett/semigroupoids/issues/26#issuecomment-398117218 [^bikeshedding]: https://mail.haskell.org/pipermail/libraries/2019-October/030036.html [^containersNEpatch]: https://github.com/haskell/containers/pull/616
Inefficiency of foldr1 ----------------------
In another `semigroupoids` issue[^foldr1-issue], the inefficiency of `foldr1` is highlighted.
The proposal includes functions like:
```haskell foldrMap1 :: (a -> b) -> (a -> b -> b) -> t a -> b foldlMap1 :: (a -> b) -> (b -> a -> b) -> t a -> b ```
And in fact the minimal pragma is `{-# MINIMAL foldMap1 | foldrMap1 #-}`
The order of function arguments is chosen so:
```haskell foldr1 = foldr1Map id ```
Another option is to have function arguments flipped:
```haskell foldrMap1 :: (a -> b -> b) -> (a -> b) -> t a -> b foldlMap1 :: (b -> a -> b) -> (a -> b) -> t a -> b ```
which more closely resembles `foldr` and `foldl`. The start element of a fold is `seed` with the right or the left element.
[^foldr1-issue]: https://github.com/ekmett/semigroupoids/issues/77
Compatibility & migration -------------------------
I drafted a compatibility package `foldable1`:
- GitHub repository: https://github.com/phadej/foldable1 - haddocks: https://oleg.fi/haddocks/foldable1/ - Semifoldable variant: https://github.com/phadej/foldable1/pull/5 - its haddocks: https://oleg.fi/haddocks/semifoldable/
which I hope could be maintained under github.com/haskell organization. I can act as a maintainer, with a hope that there won't be a lot of changes happening in `Data.Foldable1`.
To my surprise, there's already a package with this name on Hackage[^hackageFoldable] by M Farkas-Dyck (cc'd). He kindly offered to donate the name if this proposal is accepted (with foldable1 name).[^refDonate]
`Data.Foldable1` contains also instances for `Lift`, `Backwards` and `Reverse`, and other data types from `transformers`. Perfectly, the `transformers` bundled with GHC with this change would implement the instances as well. This change should propagate to `transformers-compat` too.
Similarly, `containers` would have an instance for `Tree` (and non-empty `Set` and `Map` when they are added).
Other packages would be compat'd as follows: - `foldable1` would provide instances for `Tagged` from `tagged` - `Bifoldable1` class would migrate to `bifunctors`
This is because current dependencies are:
``` semigroups <- tagged <- bifunctors <- semigroupoids ```
and `foldable1` would be more natural between `tagged` and `bifunctors`:
``` semigroups <- tagged <- foldable1 <- bifunctors <- semigroupoids ```
`foldable` have to be before `bifunctors` in the dependency tree, as `Bifoldable1` instances of some bifunctors need `Foldable1` class.
I also drafted a pull requests for compatibility patches to `bifunctors`[^bifunctorsPatch] and `semigroupoids`[^semigroupoidsPatch] with
[^hackageFoldable]: https://hackage.haskell.org/package/foldable1 [^refDonate]: https://mail.haskell.org/pipermail/libraries/2019-October/030029.html [^bifunctorsPatch]: https://github.com/ekmett/bifunctors/pull/78 [^semigroupoidsPatch]: https://github.com/ekmett/semigroupoids/pull/87
Unresolved questions --------------------
- The names? Foldable1 or Semifoldable, members? - Bifoldable1 or Semibifoldable (or Bisemifoldable)? - Members: `semifoldMap` or just `sfoldMap`? See following Foldable1 and Semifoldable sections for synopsis
- GHC-8.10 freeze is quite soon, is targeting GHC-8.12/base-4.15 more realistic. Note: this technically is a non-breaking change in `base`, so could be bundled with GHC-8.10.2, but I think sticking to major would be preferable by GHC HQ.
Appendix: Foldable1 synopsis ----------------------------
Module name: `Data.Foldable1` and `Data.Bifoldable1`
https://oleg.fi/haddocks/foldable1/Data-Foldable1.html
```haskell class Foldable t => Foldable1 t where fold1 :: Semigroup m => t m -> m foldMap1 :: Semigroup m => (a -> m) -> t a -> m foldMap1' :: Semigroup m => (a -> m) -> t a -> m
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
toNonEmpty :: t a -> NonEmpty a
maximum1 :: Ord a => t a -> a minimum1 :: Ord a => t a -> a head1 :: t a -> a last1 :: t a -> a
foldrMap1 :: (a -> b) -> (b -> b -> b) -> t a -> b foldl'Map1 :: (a -> b) -> (b -> b -> b) -> t a -> b foldlMap1 :: (a -> b) -> (b -> b -> b) -> t a -> b foldr'Map1 :: (a -> b) -> (b -> b -> b) -> t a -> b
intercalate1 :: (Foldable1 t, Semigroup m) => m -> t m -> m foldrM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a foldlM1 :: (Foldable1 t, Monad m) => (a -> a -> m a) -> t a -> m a foldrMapM1 :: (Foldable1 t, Monad m) => (a -> m b) -> (a -> b -> m b) -> t a -> m b foldlMapM1 :: (Foldable1 t, Monad m) => (a -> m b) -> (b -> a -> m b) -> t a -> m b maximum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a minimum1By :: Foldable1 t => (a -> a -> Ordering) -> t a -> a
class Bifunctor p => Bifunctor1 p where bifoldMap1 :: Semigroup s => (a -> s) -> (b -> s) -> p a b -> s ```
Appendix: Semifoldable synopsis -------------------------------
Module names`: `Data.Semifoldable` and `Data.Semibifoldable`
https://oleg.fi/haddocks/semifoldable/
```haskell class Foldable t => Semifoldable t where semifold :: Semigroup m => t m -> m semifoldMap :: Semigroup m => (a -> m) -> t a -> m semifoldMap' :: Semigroup m => (a -> m) -> t a -> m
semifoldr :: (a -> a -> a) -> t a -> a semifoldr' :: (a -> a -> a) -> t a -> a semifoldl :: (a -> a -> a) -> t a -> a semifoldl' :: (a -> a -> a) -> t a -> a
toNonEmpty :: t a -> NonEmpty a
semimaximum :: Ord a => t a -> a semiminimum :: Ord a => t a -> a semihead :: t a -> a semilast :: t a -> a
semifoldrMap :: (a -> b) -> (b -> b -> b) -> t a -> b semifoldl'Map :: (a -> b) -> (b -> b -> b) -> t a -> b semifoldlMap :: (a -> b) -> (b -> b -> b) -> t a -> b semifoldr'Map :: (a -> b) -> (b -> b -> b) -> t a -> b
intercalate1 :: (Semifoldable t, Semigroup m) => m -> t m -> m semifoldrM :: (Semifoldable t, Monad m) => (a -> a -> m a) -> t a -> m a semifoldlM :: (Semifoldable t, Monad m) => (a -> a -> m a) -> t a -> m a semifoldrMapM :: (Foldable1 t, Monad m) => (a -> m b) -> (a -> b -> m b) -> t a -> m b semifoldlMapM :: (Foldable1 t, Monad m) => (a -> m b) -> (b -> a -> m b) -> t a -> m b semimaximumBy :: Semifoldable t => (a -> a -> Ordering) -> t a -> a semiminimumBy :: Semifoldable t => (a -> a -> Ordering) -> t a -> a
-- or alternatively semiintercalate
class Bifunctor p => NonEmptyBifunctor p where semifoldMap :: Semigroup s => (a -> s) -> (b -> s) -> p a b -> s ```
Appendix: NonEmptyFoldable synopsis -------------------------------
Module name: `Data.Foldable.NonEmpty` and `Data.Bifoldable.NonEmpty`
```haskell class Foldable t => NonEmptyFoldable t where foldNE :: Semigroup m => t m -> m foldMapNE :: Semigroup m => (a -> m) -> t a -> m foldMapNE' :: Semigroup m => (a -> m) -> t a -> m
foldrNE :: (a -> a -> a) -> t a -> a foldrNE' :: (a -> a -> a) -> t a -> a foldlNE :: (a -> a -> a) -> t a -> a foldlNE' :: (a -> a -> a) -> t a -> a
toNonEmpty :: t a -> NonEmpty a
maximumNE :: Ord a => t a -> a minimumNE :: Ord a => t a -> a headNE :: t a -> a lastNE :: t a -> a
foldrMapNE :: (a -> b) -> (b -> b -> b) -> t a -> b foldl'MapNE :: (a -> b) -> (b -> b -> b) -> t a -> b foldlMapNE :: (a -> b) -> (b -> b -> b) -> t a -> b foldr'MapNE :: (a -> b) -> (b -> b -> b) -> t a -> b
intercalateNE :: (NonEmptyFoldable t, Semigroup m) => m -> t m -> m foldrMNE :: (NonEmptyFoldable t, Monad m) => (a -> a -> m a) -> t a -> m a foldlMNE :: (NonEmptyFoldable t, Monad m) => (a -> a -> m a) -> t a -> m a foldrMapMNE :: (NonEmptyFoldable t, Monad m) => (a -> m b) -> (a -> b -> m b) -> t a -> m b foldlMapMNE :: (NonEmptyFoldable t, Monad m) => (a -> m b) -> (b -> a -> m b) -> t a -> m b maximumNEBy :: NonEmptyFoldable t => (a -> a -> Ordering) -> t a -> a minimumNEBy :: NonEmptyFoldable t => (a -> a -> Ordering) -> t a -> a
class Bifunctor p => NonEmptyBifunctor p where bifoldMapNE :: Semigroup s => (a -> s) -> (b -> s) -> p a b -> s ```
participants (6)
-
Andrew Martin
-
Dmitrii Kovanikov
-
Edward Kmett
-
Matthew Farkas-Dyck
-
Oleg Grenrus
-
Tony Morris