Data.Functor.{Product,Sum} functions

Let's see if any of these are useful (a lot more at https://ghc.haskell.org/trac/ghc/ticket/13026) (||||) :: (f a -> b) -> (g a -> b) -> ((Sum f g) a -> b) f |||| g = \case InL fa -> f fa InR ga -> g ga (&&&&) :: (a -> f b) -> (a -> g b) -> (a -> (Product f g) b) (f &&&& g) a = f a `Pair` g a I couldn't think of any for Data.Functor.Compose, names are up for bikeshedding

Baldur Blöndal
Let's see if any of these are useful (a lot more at https://ghc.haskell.org/trac/ghc/ticket/13026)
(||||) :: (f a -> b) -> (g a -> b) -> ((Sum f g) a -> b) f |||| g = \case InL fa -> f fa InR ga -> g ga
(&&&&) :: (a -> f b) -> (a -> g b) -> (a -> (Product f g) b) (f &&&& g) a = f a `Pair` g a
I couldn't think of any for Data.Functor.Compose, names are up for bikeshedding
I don’t have any particular preference for names, but I’d say that any name consisting of more than three consecutive identical symbols is going to be too hard to read (particularly if the symbol is “|”). There’s a whole unicode alphabet out there. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

This |||| is the sum eliminator. We can't call it `sum`, but maybe
`sumE`? I do think it should be included with some name. Another
option might be to drag Data.Bifoldable into base from bifunctors;
(||||) = bifoldMap, but I think the case for a specialized name is
still pretty good.
&&&& is definitely a nice thing to have. However, (&&&&) = liftA2
Pair, so I'm not convinced we need to give it its own name.
On Fri, Dec 23, 2016 at 7:02 PM, Baldur Blöndal
Let's see if any of these are useful (a lot more at https://ghc.haskell.org/trac/ghc/ticket/13026)
(||||) :: (f a -> b) -> (g a -> b) -> ((Sum f g) a -> b) f |||| g = \case InL fa -> f fa InR ga -> g ga
(&&&&) :: (a -> f b) -> (a -> g b) -> (a -> (Product f g) b) (f &&&& g) a = f a `Pair` g a
I couldn't think of any for Data.Functor.Compose, names are up for bikeshedding
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Data.Bifoldable has already been dragged into base: https://ghc.haskell.org/trac/ghc/ticket/9682 On 12/24/2016 03:43 PM, David Feuer wrote:
This |||| is the sum eliminator. We can't call it `sum`, but maybe `sumE`? I do think it should be included with some name. Another option might be to drag Data.Bifoldable into base from bifunctors; (||||) = bifoldMap, but I think the case for a specialized name is still pretty good.
&&&& is definitely a nice thing to have. However, (&&&&) = liftA2 Pair, so I'm not convinced we need to give it its own name.
On Fri, Dec 23, 2016 at 7:02 PM, Baldur Blöndal
wrote: Let's see if any of these are useful (a lot more at https://ghc.haskell.org/trac/ghc/ticket/13026)
(||||) :: (f a -> b) -> (g a -> b) -> ((Sum f g) a -> b) f |||| g = \case InL fa -> f fa InR ga -> g ga
(&&&&) :: (a -> f b) -> (a -> g b) -> (a -> (Product f g) b) (f &&&& g) a = f a `Pair` g a
I couldn't think of any for Data.Functor.Compose, names are up for bikeshedding
_______________________________________________ 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

Er ... that was silly. I guess bifoldMap isn't really (||||), exactly.
It's pretty much `either`, but needs to have a Monoid wrapper. The
generalization I was roughly imagining would be a sort of
higher-kinded Bifoldable1:
class Bifoldable1' p where
bifoldMap1' :: Semigroup m => (f a -> m) -> (g a -> m) -> p f g a -> m
which would then get the job done with Data.Semigroup.First.
But that's getting pretty far from the point, so, we need `||||` or
`sum` or whatever.
On Sat, Dec 24, 2016 at 7:43 AM, David Feuer
This |||| is the sum eliminator. We can't call it `sum`, but maybe `sumE`? I do think it should be included with some name. Another option might be to drag Data.Bifoldable into base from bifunctors; (||||) = bifoldMap, but I think the case for a specialized name is still pretty good.
&&&& is definitely a nice thing to have. However, (&&&&) = liftA2 Pair, so I'm not convinced we need to give it its own name.
On Fri, Dec 23, 2016 at 7:02 PM, Baldur Blöndal
wrote: Let's see if any of these are useful (a lot more at https://ghc.haskell.org/trac/ghc/ticket/13026)
(||||) :: (f a -> b) -> (g a -> b) -> ((Sum f g) a -> b) f |||| g = \case InL fa -> f fa InR ga -> g ga
(&&&&) :: (a -> f b) -> (a -> g b) -> (a -> (Product f g) b) (f &&&& g) a = f a `Pair` g a
I couldn't think of any for Data.Functor.Compose, names are up for bikeshedding
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

I updated the proposal with (again more information in https://ghc.haskell.org/trac/ghc/ticket/13026#comment:5) runSum :: Sum f g a -> Either (f a) (g a)runSum = Left |||| Right runProduct :: Product f g a -> (f a, g a)runProduct (Pair fa ga) = (fa, ga) I found one for ‘Data.Functor.Compose’ o :: Functor m => (b -> n c) -> (a -> m b) -> (a -> Compose m n c)o f g = Compose . fmap f . g

On 2016-12-23 07:02 PM, Baldur Blöndal wrote:
Let's see if any of these are useful (a lot more at https://ghc.haskell.org/trac/ghc/ticket/13026)
(||||) :: (f a -> b) -> (g a -> b) -> ((Sum f g) a -> b) f |||| g = \case InL fa -> f fa InR ga -> g ga
The corresponding destructor function in Data.Either is called either: either :: (a -> c) -> (b -> c) -> Either http://hackage.haskell.org/package/base-4.9.0.0/docs/Data-Either.html#t:Eith... a b -> c Thus the most logical name for the Sum destructor would be sum. You can always import Data.Functor.Product qualified as Product to avoid clashes. In the same vein, I propose adding uncurry :: (f a -> g a -> b) -> Product f g a -> b uncurry f (Pair a b) = f a b
(&&&&) :: (a -> f b) -> (a -> g b) -> (a -> (Product f g) b) (f &&&& g) a = f a `Pair` g a
I'm not fond of that name. Also, f &&&& g == uncurry Pair . (f &&& g)

I do not like using infix operators as names. Similar to others, I like the
Sum eliminator and am skeptical of the value that the &&&& operator
provides.
On Fri, Dec 23, 2016 at 7:02 PM, Baldur Blöndal
Let's see if any of these are useful (a lot more at https://ghc.haskell.org/trac/ghc/ticket/13026)
(||||) :: (f a -> b) -> (g a -> b) -> ((Sum f g) a -> b) f |||| g = \case InL fa -> f fa InR ga -> g ga
(&&&&) :: (a -> f b) -> (a -> g b) -> (a -> (Product f g) b) (f &&&& g) a = f a `Pair` g a
I couldn't think of any for Data.Functor.Compose, names are up for bikeshedding
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
-- -Andrew Thaddeus Martin
participants (6)
-
Andrew Martin
-
Artyom
-
Baldur Blöndal
-
David Feuer
-
Jon Fairbairn
-
Mario Blažević