Foldable/Traversable and Applicative/Monoid?

Hi all, I don't understand why Foldable is a necessary super-class of Traversable, and I suspect that the Applicative/Monoid duality, which I've just begun discovering in the literature, has something to do with why that is so. Can anyone give me a hint, without giving me the answer? Thanks! -db

It's not so much that it's *necessary* as that it's *possible*. The
existence of two functions in Data.Traversable explains both of the
superclasses of Traversable:
fmapDefault :: Traversable t => (a -> b) -> t a -> t b
foldMapDefault :: (Traversable t, Monoid m) => (a -> m) -> t a -> m
Each of these is written using only traverse, and they can be used to
define fmap and foldMap for types when you've written traverse.
Hint: Consider traversing using the following applicative functors:
newtype Const a b = Const a
instance Monoid a => Applicative (Const a)
newtype Identity a = Identity a
instance Applicative Identity
On Feb 5, 2016 1:45 PM, "David Banas"
Hi all,
I don't understand why Foldable is a necessary super-class of Traversable, and I suspect that the Applicative/Monoid duality, which I've just begun discovering in the literature, has something to do with why that is so.
Can anyone give me a hint, without giving me the answer?
Thanks! -db
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Hi David,
Thanks for your reply!
That’s really interesting; I never would have thought to try and implement super-class member functions, in terms of sub-class member functions.
I was trying to go the other way: implement sequenceA, in terms of foldMap, which seemed to require a completely generic way of turning an Applicative (guaranteed by the type signature of sequenceA) into a Monoid (required by foldMap). I came up with this:
{-# LANGUAGE Rank2Types
FlexibleContexts
UndecidableInstances
AllowAmbiguousTypes
#-}
newtype MonApp = MonApp {getApp :: (Applicative f, Monoid a) => f a}
instance Monoid MonApp where
mempty = MonApp $ pure mempty
mappend ma1 ma2 = MonApp $ mappend <$> (getApp ma1) <*> (getApp ma2)
instance (Monoid a) => Monoid (Tree a) where
mempty = Empty
mappend Empty t = t
mappend t Empty = t
mappend (Leaf x) (Leaf y) = Leaf (x `mappend` y)
mappend (Leaf x) (Node t1 y t2) = Node t1 (x `mappend` y) t2
mappend (Node t1 y t2) (Leaf x) = Node t1 (y `mappend` x) t2
mappend (Node t1 x t2) (Node t3 y t4) = Node (t1 `mappend` t3) (x `mappend` y) (t2 `mappend` t4)
instance Monoid (Tree a) => Traversable Tree where
sequenceA = getApp . foldMap (MonApp . (fmap Leaf))
to which the compiler responded:
Couldn't match type ‘f (Tree a1)’ with ‘forall (f1 :: * -> *) a2. (Applicative f1, Monoid a2) => f1 a2’
Expected type: f (Tree a1) -> interactive:IHaskell161.MonApp
Actual type: (forall (f :: * -> *) a. (Applicative f, Monoid a) => f a) -> interactive:IHaskell161.MonApp
Relevant bindings include sequenceA :: Tree (f a1) -> f (Tree a1) (bound at :14:3)
In the first argument of ‘(.)’, namely ‘IHaskell161.MonApp’
In the first argument of ‘foldMap’, namely ‘(interactive:IHaskell161.MonApp . (fmap Leaf))’
-db
On Feb 5, 2016, at 11:20 AM, David Feuer
It's not so much that it's *necessary* as that it's *possible*. The existence of two functions in Data.Traversable explains both of the superclasses of Traversable:
fmapDefault :: Traversable t => (a -> b) -> t a -> t b
foldMapDefault :: (Traversable t, Monoid m) => (a -> m) -> t a -> m
Each of these is written using only traverse, and they can be used to define fmap and foldMap for types when you've written traverse.
Hint: Consider traversing using the following applicative functors:
newtype Const a b = Const a instance Monoid a => Applicative (Const a)
newtype Identity a = Identity a instance Applicative Identity
On Feb 5, 2016 1:45 PM, "David Banas"
wrote: Hi all, I don't understand why Foldable is a necessary super-class of Traversable, and I suspect that the Applicative/Monoid duality, which I've just begun discovering in the literature, has something to do with why that is so.
Can anyone give me a hint, without giving me the answer?
Thanks! -db
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

It's not terribly unusual. Functor can be a superclass of Applicative
because
fmap f xs = pure f <*> xs
Applicative can be a superclass of Monad because
pure = return
(<*>) = ap
Distributive can be a superclass of Representable because
distribute wf = tabulate (\k -> fmap (`index` k) wf)
Obviously, it often *doesn't* work like this. The class structure may be
arranged as it is because the subclass conceptually or practically
represents a refinement of the superclass. But when the methods of a given
class can be implemented using the methods of another, that suggests that
it *might* make sense for it to be a superclass.
On Feb 6, 2016 10:10 AM, "David Banas"
Hi David,
Thanks for your reply!
That’s really interesting; I never would have thought to try and implement super-class member functions, in terms of sub-class member functions. I was trying to go the other way: implement sequenceA, in terms of foldMap, which seemed to require a completely generic way of turning an Applicative (guaranteed by the type signature of sequenceA) into a Monoid (required by foldMap). I came up with this:
{-# LANGUAGE Rank2Types FlexibleContexts UndecidableInstances AllowAmbiguousTypes #-}
newtype MonApp = MonApp {getApp :: (Applicative f, Monoid a) => f a}
instance Monoid MonApp where mempty = MonApp $ pure mempty mappend ma1 ma2 = MonApp $ mappend <$> (getApp ma1) <*> (getApp ma2)
instance (Monoid a) => Monoid (Tree a) where mempty = Empty mappend Empty t = t mappend t Empty = t mappend (Leaf x) (Leaf y) = Leaf (x `mappend` y) mappend (Leaf x) (Node t1 y t2) = Node t1 (x `mappend` y) t2 mappend (Node t1 y t2) (Leaf x) = Node t1 (y `mappend` x) t2 mappend (Node t1 x t2) (Node t3 y t4) = Node (t1 `mappend` t3) (x `mappend` y) (t2 `mappend` t4)
instance Monoid (Tree a) => Traversable Tree where sequenceA = getApp . foldMap (MonApp . (fmap Leaf))
to which the compiler responded:
Couldn't match type ‘f (Tree a1)’ with ‘forall (f1 :: * -> *) a2. (Applicative f1, Monoid a2) => f1 a2’ Expected type: f (Tree a1) -> interactive:IHaskell161.MonApp Actual type: (forall (f :: * -> *) a. (Applicative f, Monoid a) => f a) -> interactive:IHaskell161.MonApp Relevant bindings include sequenceA :: Tree (f a1) -> f (Tree a1) (bound at :14:3) In the first argument of ‘(.)’, namely ‘IHaskell161.MonApp’ In the first argument of ‘foldMap’, namely ‘(interactive:IHaskell161.MonApp . (fmap Leaf))’
-db
On Feb 5, 2016, at 11:20 AM, David Feuer
wrote: It's not so much that it's *necessary* as that it's *possible*. The existence of two functions in Data.Traversable explains both of the superclasses of Traversable:
fmapDefault :: Traversable t => (a -> b) -> t a -> t b
foldMapDefault :: (Traversable t, Monoid m) => (a -> m) -> t a -> m
Each of these is written using only traverse, and they can be used to define fmap and foldMap for types when you've written traverse.
Hint: Consider traversing using the following applicative functors:
newtype Const a b = Const a instance Monoid a => Applicative (Const a)
newtype Identity a = Identity a instance Applicative Identity On Feb 5, 2016 1:45 PM, "David Banas"
wrote: Hi all,
I don't understand why Foldable is a necessary super-class of Traversable, and I suspect that the Applicative/Monoid duality, which I've just begun discovering in the literature, has something to do with why that is so.
Can anyone give me a hint, without giving me the answer?
Thanks! -db
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Hi David,
Thanks so much for the two proposed exercises, and very sorry to have taken so long to respond to them.
I’ve constructed my responses in the form of an IHaskell notebook, and made that notebook available, here:
https://htmlpreview.github.io/?https://github.com/capn-freako/Haskell_Misc/b...
Thanks,
-db
On Feb 5, 2016, at 11:20 AM, David Feuer
It's not so much that it's *necessary* as that it's *possible*. The existence of two functions in Data.Traversable explains both of the superclasses of Traversable:
fmapDefault :: Traversable t => (a -> b) -> t a -> t b
foldMapDefault :: (Traversable t, Monoid m) => (a -> m) -> t a -> m
Each of these is written using only traverse, and they can be used to define fmap and foldMap for types when you've written traverse.
Hint: Consider traversing using the following applicative functors:
newtype Const a b = Const a instance Monoid a => Applicative (Const a)
newtype Identity a = Identity a instance Applicative Identity
On Feb 5, 2016 1:45 PM, "David Banas"
wrote: Hi all, I don't understand why Foldable is a necessary super-class of Traversable, and I suspect that the Applicative/Monoid duality, which I've just begun discovering in the literature, has something to do with why that is so.
Can anyone give me a hint, without giving me the answer?
Thanks! -db
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
participants (2)
-
David Banas
-
David Feuer