Foldable, Traversable and choosing an order

Hello again, haskell-cafe. I was trying to implement the Unifiable typeclass from Control.Unification on one of my types, and did so fine, but then realized I needed a Traversable instance. So I thought about it, and concluded: Yes, my type definitely is Traversable, and I implemented Traversable. But then I realized I needed a Foldable instance for that. And then I wasn't so sure anymore. I *can* implement a Foldable instance, but it requires a choice of the order in which my structure is traversed that I don't really want to make? A.k.a: I can think of at least two different ways of implementing Foldable that would give different results if the function passed to foldr was not associative. So I looked online a bit, and it seems this is a topic people have talked about, but maybe not precisely in the context of the order. What I have gathered is that: yes, if a functor is Traversable, then there is at least one way to implement a Foldable in it. And I understand this, but then, I don't really grasp how that works in my specific case. Because my Traversable instance does not make a choice of this order (at least I think so), and I do need to make that choice to implement Foldable (at least I think so), and I don't see how the "default" implementation of foldMap in terms of traverse makes that choice. But the choice must be made somewhere if it is made in the Foldable. So what is going on? Of course, here's the code. My types: data SOTermPF fn p f = ConstF fn | Proj Int | CompF p [f] deriving Eq newtype SOTermF fn f = SOF (SOTermPF fn f f) deriving Eq My Traversable instance (with comments on intermediate types because otherwise it can get pretty obscure): instance Traversable (SOTermF fn) where traverse f (SOF (ConstF c)) = pure (SOF (ConstF c)) traverse f (SOF (Proj idx)) = pure (SOF (Proj idx)) -- f g :: f b -- map f sargs = [f b] -- CompF :: a -> ([a] -> SOTermPF fn p a) -- (\h -> \ts -> SOF (CompF h ts)) :: ([a] -> SOTermF fn a) -- fmap (\h -> \ts -> SOF (CompF h ts)) (f g) :: f ([b] -> SOTermF fn b) -- traverse :: (aa -> ff bb) -> [aa] -> ff [bb] -- traverse :: (f b -> f b) -> [f b] -> f [b] -- ((fmap (\h -> \ts -> SOF (CompF h ts)) (f g)) <*>) :: f [b] -> f (SOTermF fn b) -- traverse id (map f sargs) :: f [b] -- (fmap (\h -> \ts -> SOF (CompF h ts)) (f g)) <*> (traverse id (map f sargs)) :: f (SOTermF fn b) traverse f (SOF (CompF g sargs)) = (fmap (\h -> \ts -> SOF (CompF h ts)) (f g)) <*> (traverse id (map f sargs)) But to implement Foldable I need to choose an order because in the case where I do have elements under the functor (CompF), I have them in two shapes: The "head" and the "arguments" (the p and the [f] in CompF p [f]). So, of course, the arguments are traversed in the order of the list, but the order that I need to choose is: Do I apply the head first and the arguments later or do I apply the arguments first and the head later? But my traverse seems so natural. Am I making that choice there? Maybe if I made the fmap over the arguments (while traversing the list) instead of over the head, and then did a flipped application of <*>? Does that mean my traverse instance has implicitly assumed that the head will be done first? All of this is really out of curiosity and making sure I know what I'm doing: I will not use foldr on my structure and I'm pretty sure that the traversal that Control.Unification needs is associative. But I don't like seeing arbitrary choices appear out of nowhere in my code, I want to make sure of why I made them. :P Thanks in advance, Juan. -- The University of Edinburgh is a charitable body, registered in Scotland, with registration number SC005336.

Hi,
Your choice of Traversable must already give you an answer to that
question. In fact, if you could implement `Traversable` you can get
`Foldable` for free by using `foldMapDefault` [
http://hackage.haskell.org/package/base-4.12.0.0/docs/Data-Traversable.html#...].
Then you know that both instances "agree" on their behavior.
Regards,
Alejandro
El lun., 23 sept. 2019 a las 21:06, Juan Casanova (
Hello again, haskell-cafe.
I was trying to implement the Unifiable typeclass from Control.Unification on one of my types, and did so fine, but then realized I needed a Traversable instance.
So I thought about it, and concluded: Yes, my type definitely is Traversable, and I implemented Traversable. But then I realized I needed a Foldable instance for that.
And then I wasn't so sure anymore. I *can* implement a Foldable instance, but it requires a choice of the order in which my structure is traversed that I don't really want to make? A.k.a: I can think of at least two different ways of implementing Foldable that would give different results if the function passed to foldr was not associative.
So I looked online a bit, and it seems this is a topic people have talked about, but maybe not precisely in the context of the order. What I have gathered is that: yes, if a functor is Traversable, then there is at least one way to implement a Foldable in it. And I understand this, but then, I don't really grasp how that works in my specific case. Because my Traversable instance does not make a choice of this order (at least I think so), and I do need to make that choice to implement Foldable (at least I think so), and I don't see how the "default" implementation of foldMap in terms of traverse makes that choice. But the choice must be made somewhere if it is made in the Foldable. So what is going on?
Of course, here's the code. My types:
data SOTermPF fn p f = ConstF fn | Proj Int | CompF p [f] deriving Eq newtype SOTermF fn f = SOF (SOTermPF fn f f) deriving Eq
My Traversable instance (with comments on intermediate types because otherwise it can get pretty obscure):
instance Traversable (SOTermF fn) where traverse f (SOF (ConstF c)) = pure (SOF (ConstF c)) traverse f (SOF (Proj idx)) = pure (SOF (Proj idx)) -- f g :: f b -- map f sargs = [f b] -- CompF :: a -> ([a] -> SOTermPF fn p a) -- (\h -> \ts -> SOF (CompF h ts)) :: ([a] -> SOTermF fn a) -- fmap (\h -> \ts -> SOF (CompF h ts)) (f g) :: f ([b] -> SOTermF fn b) -- traverse :: (aa -> ff bb) -> [aa] -> ff [bb] -- traverse :: (f b -> f b) -> [f b] -> f [b] -- ((fmap (\h -> \ts -> SOF (CompF h ts)) (f g)) <*>) :: f [b] -> f (SOTermF fn b) -- traverse id (map f sargs) :: f [b] -- (fmap (\h -> \ts -> SOF (CompF h ts)) (f g)) <*> (traverse id (map f sargs)) :: f (SOTermF fn b) traverse f (SOF (CompF g sargs)) = (fmap (\h -> \ts -> SOF (CompF h ts)) (f g)) <*> (traverse id (map f sargs))
But to implement Foldable I need to choose an order because in the case where I do have elements under the functor (CompF), I have them in two shapes: The "head" and the "arguments" (the p and the [f] in CompF p [f]). So, of course, the arguments are traversed in the order of the list, but the order that I need to choose is: Do I apply the head first and the arguments later or do I apply the arguments first and the head later? But my traverse seems so natural. Am I making that choice there? Maybe if I made the fmap over the arguments (while traversing the list) instead of over the head, and then did a flipped application of <*>? Does that mean my traverse instance has implicitly assumed that the head will be done first?
All of this is really out of curiosity and making sure I know what I'm doing: I will not use foldr on my structure and I'm pretty sure that the traversal that Control.Unification needs is associative. But I don't like seeing arbitrary choices appear out of nowhere in my code, I want to make sure of why I made them. :P
Thanks in advance, Juan.
-- The University of Edinburgh is a charitable body, registered in Scotland, with registration number SC005336.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Your implementation of traverse DOES make a choice of order (any
implementation must). In particular f <*> x does the effects of f first,
and then x.
-Brent
On Mon, Sep 23, 2019, 2:06 PM Juan Casanova
Hello again, haskell-cafe.
I was trying to implement the Unifiable typeclass from Control.Unification on one of my types, and did so fine, but then realized I needed a Traversable instance.
So I thought about it, and concluded: Yes, my type definitely is Traversable, and I implemented Traversable. But then I realized I needed a Foldable instance for that.
And then I wasn't so sure anymore. I *can* implement a Foldable instance, but it requires a choice of the order in which my structure is traversed that I don't really want to make? A.k.a: I can think of at least two different ways of implementing Foldable that would give different results if the function passed to foldr was not associative.
So I looked online a bit, and it seems this is a topic people have talked about, but maybe not precisely in the context of the order. What I have gathered is that: yes, if a functor is Traversable, then there is at least one way to implement a Foldable in it. And I understand this, but then, I don't really grasp how that works in my specific case. Because my Traversable instance does not make a choice of this order (at least I think so), and I do need to make that choice to implement Foldable (at least I think so), and I don't see how the "default" implementation of foldMap in terms of traverse makes that choice. But the choice must be made somewhere if it is made in the Foldable. So what is going on?
Of course, here's the code. My types:
data SOTermPF fn p f = ConstF fn | Proj Int | CompF p [f] deriving Eq newtype SOTermF fn f = SOF (SOTermPF fn f f) deriving Eq
My Traversable instance (with comments on intermediate types because otherwise it can get pretty obscure):
instance Traversable (SOTermF fn) where traverse f (SOF (ConstF c)) = pure (SOF (ConstF c)) traverse f (SOF (Proj idx)) = pure (SOF (Proj idx)) -- f g :: f b -- map f sargs = [f b] -- CompF :: a -> ([a] -> SOTermPF fn p a) -- (\h -> \ts -> SOF (CompF h ts)) :: ([a] -> SOTermF fn a) -- fmap (\h -> \ts -> SOF (CompF h ts)) (f g) :: f ([b] -> SOTermF fn b) -- traverse :: (aa -> ff bb) -> [aa] -> ff [bb] -- traverse :: (f b -> f b) -> [f b] -> f [b] -- ((fmap (\h -> \ts -> SOF (CompF h ts)) (f g)) <*>) :: f [b] -> f (SOTermF fn b) -- traverse id (map f sargs) :: f [b] -- (fmap (\h -> \ts -> SOF (CompF h ts)) (f g)) <*> (traverse id (map f sargs)) :: f (SOTermF fn b) traverse f (SOF (CompF g sargs)) = (fmap (\h -> \ts -> SOF (CompF h ts)) (f g)) <*> (traverse id (map f sargs))
But to implement Foldable I need to choose an order because in the case where I do have elements under the functor (CompF), I have them in two shapes: The "head" and the "arguments" (the p and the [f] in CompF p [f]). So, of course, the arguments are traversed in the order of the list, but the order that I need to choose is: Do I apply the head first and the arguments later or do I apply the arguments first and the head later? But my traverse seems so natural. Am I making that choice there? Maybe if I made the fmap over the arguments (while traversing the list) instead of over the head, and then did a flipped application of <*>? Does that mean my traverse instance has implicitly assumed that the head will be done first?
All of this is really out of curiosity and making sure I know what I'm doing: I will not use foldr on my structure and I'm pretty sure that the traversal that Control.Unification needs is associative. But I don't like seeing arbitrary choices appear out of nowhere in my code, I want to make sure of why I made them. :P
Thanks in advance, Juan.
-- The University of Edinburgh is a charitable body, registered in Scotland, with registration number SC005336.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Quoting Brent Yorgey
Your implementation of traverse DOES make a choice of order (any implementation must). In particular f <*> x does the effects of f first, and then x.
Ahhh, so it's in the applicative that the order choice happens! And I could change it by essentially flipping the function application and so on. That makes sense. Thanks! -- The University of Edinburgh is a charitable body, registered in Scotland, with registration number SC005336.

On Mon, Sep 23, 2019 at 08:05:38PM +0100, Juan Casanova wrote:
data SOTermPF fn p f = ConstF fn | Proj Int | CompF p [f] deriving Eq newtype SOTermF fn f = SOF (SOTermPF fn f f) deriving Eq
My Traversable instance (with comments on intermediate types because otherwise it can get pretty obscure):
Everyone else has made good comments, but to add a little and to be a little more explicit: your data type uses [] so it makes sense to directly inherit the Traversable (and hence Foldable) instance from that. Your instance was a little convoluted. Here's what I would suggest: instance Foldable (SOTermF fn) where foldMap = foldMapDefault instance Traversable (SOTermF fn) where traverse f (SOF (ConstF c)) = pure (SOF (ConstF c)) traverse f (SOF (Proj idx)) = pure (SOF (Proj idx)) traverse f (SOF (CompF g sargs)) = SOF <$> (CompF <$> f g <*> traverse f sargs)

Thanks Tom,
Looking at your suggested solution, it looks very similar to mine
albeit two differences.
One is "just" (as if it were not important) code clarity in that you
use <$> instead of fmap which enables you to avoid lambda abstraction,
but that part is operationally the same as mine.
The other is that you do (traverse f sargs), whereas I did (traverse
id (map f sargs)). This made me think. Is this always the same? Is it
the same only for [] or for any Traversable? If it is, then,
considering map is just fmap for lists, and that all Traversables must
be Functors, why isn't traverse just defined as
traverse_alt :: (Traversable t, Applicative f) => t (f a) -> f (t a)
traverse_alt = traverse id
and let fmap deal with the mapping of the function? Of course this
wouldn't be the implementation, it would be the other way around.
Instances of Traversable would implement traverse_alt, and then
whenever I wanted to do what traverse currently does, I would just do:
traverse_alt (fmap f inputs). What is there to gain by including the
mapping into the traversal *in the implementation of traverse itself*?
Thanks again,
Juan.
Quoting Tom Ellis
On Mon, Sep 23, 2019 at 08:05:38PM +0100, Juan Casanova wrote:
data SOTermPF fn p f = ConstF fn | Proj Int | CompF p [f] deriving Eq newtype SOTermF fn f = SOF (SOTermPF fn f f) deriving Eq
My Traversable instance (with comments on intermediate types because otherwise it can get pretty obscure):
Everyone else has made good comments, but to add a little and to be a little more explicit: your data type uses [] so it makes sense to directly inherit the Traversable (and hence Foldable) instance from that. Your instance was a little convoluted. Here's what I would suggest:
instance Foldable (SOTermF fn) where foldMap = foldMapDefault
instance Traversable (SOTermF fn) where traverse f (SOF (ConstF c)) = pure (SOF (ConstF c)) traverse f (SOF (Proj idx)) = pure (SOF (Proj idx)) traverse f (SOF (CompF g sargs)) = SOF <$> (CompF <$> f g <*> traverse f sargs) _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
-- The University of Edinburgh is a charitable body, registered in Scotland, with registration number SC005336.

On Sep 25, 2019, at 1:03 PM, Juan Casanova
wrote: Considering map is just fmap for lists, and that all Traversables must be Functors, why isn't traverse just defined as
traverse_alt :: (Traversable t, Applicative f) => t (f a) -> f (t a) traverse_alt = traverse id
and let fmap deal with the mapping of the function? Of course this wouldn't be the implementation, it would be the other way around. Instances of Traversable would implement traverse_alt, and then whenever I wanted to do what traverse currently does, I would just do: traverse_alt (fmap f inputs). What is there to gain by including the mapping into the traversal *in the implementation of traverse itself*?
It seems you're reinventing 'sequenceA': λ> import Data.Traversable λ> :t traverse id traverse id :: (Applicative f, Traversable t) => t (f b) -> f (t b) λ> :t sequenceA sequenceA :: (Applicative f, Traversable t) => t (f a) -> f (t a) λ> :t traverse traverse :: (Applicative f, Traversable t) => (a -> f b) -> t a -> f (t b) λ> :t ((sequenceA .) . fmap) ((sequenceA .) . fmap) :: (Applicative f, Traversable t) => (a1 -> f a) -> t a1 -> f (t a) Each of 'traverse' and 'sequenceA' can be defined in terms of the other. The choice of one vs. the other is a matter of convenience: sequenceA = traverse id traverse f = sequenceA . fmap f -- Viktor.

On Wed, Sep 25, 2019 at 06:03:20PM +0100, Juan Casanova wrote:
why isn't traverse just defined as
traverse_alt :: (Traversable t, Applicative f) => t (f a) -> f (t a) traverse_alt = traverse id
and let fmap deal with the mapping of the function? Of course this wouldn't be the implementation, it would be the other way around. Instances of Traversable would implement traverse_alt, and then whenever I wanted to do what traverse currently does, I would just do: traverse_alt (fmap f inputs). What is there to gain by including the mapping into the traversal *in the implementation of traverse itself*?
Your `traverse_alt` is called `sequence`: https://hackage.haskell.org/package/base-4.12.0.0/docs/src/Data.Traversable.... They're both useful and you can define each in terms of the other. I'd say I use traverse about ten times more than sequence. It's basically equivalent to `mapM`, i.e. "map with an effect". `fmap` followed by `sequence` tends to read a bit clumsily. Tom

On Mon, Sep 23, 2019, 3:05 PM Juan Casanova
data SOTermPF fn p f = ConstF fn | Proj Int | CompF p [f] deriving Eq
newtype SOTermF fn f = SOF (SOTermPF fn f f) deriving Eq
Here's a more modular option for the Traversable instance. import Data.Bitraversable import Data.Bifoldable import Control.Applicative import Data.Traversable instance Bifoldable (SOTermPF fn) where bifoldMap = bifoldMapDefault instance Bitraversable (SOTermPF fn) where bitraverse _f _g (ConstF fn) = pure (ConstF fn) bitraverse _f _g (Proj i) = pure (Proj i) bitraverse f g (CompF p fs) = liftA2 CompF (f p) (traverse g fs) instance Foldable (SOTermF fn) where foldMap = foldMapDefault instance Traversable (SOTermF fn) where traverse f (SOF q) = SOF <$> bitraverse f f q

That is lovely. Makes it super clear. Hadn't thought about
Bitraversable and Bifoldable. Thanks a lot.
Juan.
Quoting David Feuer
On Mon, Sep 23, 2019, 3:05 PM Juan Casanova
wrote: My types:
data SOTermPF fn p f = ConstF fn | Proj Int | CompF p [f] deriving Eq
newtype SOTermF fn f = SOF (SOTermPF fn f f) deriving Eq
Here's a more modular option for the Traversable instance.
import Data.Bitraversable import Data.Bifoldable import Control.Applicative import Data.Traversable
instance Bifoldable (SOTermPF fn) where bifoldMap = bifoldMapDefault
instance Bitraversable (SOTermPF fn) where bitraverse _f _g (ConstF fn) = pure (ConstF fn) bitraverse _f _g (Proj i) = pure (Proj i) bitraverse f g (CompF p fs) = liftA2 CompF (f p) (traverse g fs)
instance Foldable (SOTermF fn) where foldMap = foldMapDefault
instance Traversable (SOTermF fn) where traverse f (SOF q) = SOF <$> bitraverse f f q
-- The University of Edinburgh is a charitable body, registered in Scotland, with registration number SC005336.
participants (6)
-
Alejandro Serrano Mena
-
Brent Yorgey
-
David Feuer
-
Juan Casanova
-
Tom Ellis
-
Viktor Dukhovni