
I found the following data type useful when working with the Foldable class: {- | It holds:
foldMap f . Mapped g = foldMap f . fmap g
but use of 'Mapped' avoids 'Functor' constraint. -} data Mapped f a b = Mapped (a -> b) (f a) instance (Foldable f) => Foldable (Mapped f a) where foldMap g (Mapped f xs) = Fold.foldMap (g . f) xs foldr g x (Mapped f xs) = Fold.foldr (g . f) x xs foldl g x (Mapped f xs) = Fold.foldl (\acc -> g acc . f) x xs Should it be added to Data.Foldable?

Could you provide some examples where you have found it useful? On Sun, Jan 3, 2016 at 9:11 PM Henning Thielemann < lemming@henning-thielemann.de> wrote:
I found the following data type useful when working with the Foldable class:
{- | It holds:
foldMap f . Mapped g = foldMap f . fmap g
but use of 'Mapped' avoids 'Functor' constraint. -} data Mapped f a b = Mapped (a -> b) (f a)
instance (Foldable f) => Foldable (Mapped f a) where foldMap g (Mapped f xs) = Fold.foldMap (g . f) xs foldr g x (Mapped f xs) = Fold.foldr (g . f) x xs foldl g x (Mapped f xs) = Fold.foldl (\acc -> g acc . f) x xs
Should it be added to Data.Foldable? _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

On Mon, 4 Jan 2016, Oliver Charles wrote:
Could you provide some examples where you have found it useful?
E.g. Set has Foldable instance, but not Functor. Using Mapped I can implement argmax in a generic way, such that it also works on Set. argmax :: (Ord b, Foldable f) => (a -> b) -> f a -> a argmax f = snd . Fold.maximumBy (comparing fst) . Mapped (\a -> (f a, a))

It sounds like Coyoneda -- i.e. Mapped with the "a" existential --
might be what you're looking for:
http://hackage.haskell.org/package/kan-extensions-4.2.3/docs/Data-Functor-Co...
Shachaf
On Sun, Jan 3, 2016 at 5:11 PM, Henning Thielemann
On Mon, 4 Jan 2016, Oliver Charles wrote:
Could you provide some examples where you have found it useful?
E.g. Set has Foldable instance, but not Functor. Using Mapped I can implement argmax in a generic way, such that it also works on Set.
argmax :: (Ord b, Foldable f) => (a -> b) -> f a -> a argmax f = snd . Fold.maximumBy (comparing fst) . Mapped (\a -> (f a, a))
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

That's what I was thinking too. While that's not Haskell 98, I believe it
can be justified on Haskell 98 grounds by approximate equivalence with the
representation of a foldable container by a binary tree. I'm no expert, but
I think the hypothetical alternative formulation might look like this:
--Free magma
data Tree a = Leaf a | Bin (Tree a) (Tree a) deriving (Functor, Foldable)
--Adjoin an identity and a phantom.
--The phantom isn't Haskell 98, but
--it would be possible to accomplish the
--same purpose in Haskell 98
data R (f :: * -> *) a = Empty | FM (Tree a) deriving (Functor, Foldable)
--Improper, but probably sane for the purpose
instance Monoid (R f a) where
mempty = Empty
mappend Empty ys = ys
mappend xs Empty = xs
mappend (FM xs) (FM ys) = FM (Bin xs ys)
rep :: Foldable f => f a -> R f a
rep = foldMap (FM . Leaf)
We can apply rep to a foldable container to get a reusable representation
of that container for folding purposes that is also a Functor.
On Jan 3, 2016 8:21 PM, "Shachaf Ben-Kiki"
It sounds like Coyoneda -- i.e. Mapped with the "a" existential -- might be what you're looking for:
http://hackage.haskell.org/package/kan-extensions-4.2.3/docs/Data-Functor-Co...
Shachaf
On Sun, Jan 3, 2016 at 5:11 PM, Henning Thielemann
wrote: On Mon, 4 Jan 2016, Oliver Charles wrote:
Could you provide some examples where you have found it useful?
E.g. Set has Foldable instance, but not Functor. Using Mapped I can implement argmax in a generic way, such that it also works on Set.
argmax :: (Ord b, Foldable f) => (a -> b) -> f a -> a argmax f = snd . Fold.maximumBy (comparing fst) . Mapped (\a -> (f 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
participants (4)
-
David Feuer
-
Henning Thielemann
-
Oliver Charles
-
Shachaf Ben-Kiki