Traversable instance for ((,) o) ?

I wanted a Traversable instance for pairing, so I defined one:
{-# LANGUAGE TupleSections #-} {-# OPTIONS_GHC -Wall -fno-warn-orphans #-}
import Data.Traversable (Traversable(..)) import Data.Foldable (Foldable(..)) import Control.Applicative ((<$>))
instance Traversable ((,) o) where sequenceA (o,fa) = (o,) <$> fa
However, Foldable is a superclass of Traversable, so I get an error message: Could not deduce (Foldable ((,) o)) from the context () arising from the superclasses of an instance declaration The best I've thought of is the following:
instance Foldable ((,) o) where fold (_,m) = m
However, I don't like how it discards information. Some questions: * Why is Foldable a superclass of Traversable? * Is there a good choice of a Foldable instance of ((,) o)? * Are there any other problems with the Traversable instance above (besides foldability)? - Conal

On Tue, 3 Jan 2012, Conal Elliott wrote:
I wanted a Traversable instance for pairing, so I defined one:
{-# LANGUAGE TupleSections #-} {-# OPTIONS_GHC -Wall -fno-warn-orphans #-}
import Data.Traversable (Traversable(..)) import Data.Foldable (Foldable(..)) import Control.Applicative ((<$>))
instance Traversable ((,) o) where sequenceA (o,fa) = (o,) <$> fa
What about using the Writer Monad/Functor?
The best I've thought of is the following:
instance Foldable ((,) o) where fold (_,m) = m
However, I don't like how it discards information.
I also didn't like that and thus asked the same question in the past. The answer is, that you can implement a 'fold' using 'traverse' and thus every Traversable type has also a natural Foldable instance. http://www.haskell.org/pipermail/haskell-cafe/2009-October/067535.html

On 3 Jan 2012, at 23:12, Conal Elliott wrote:
I wanted a Traversable instance for pairing, so I defined one:
instance Traversable ((,) o) where sequenceA (o,fa) = (o,) <$> fa
That looks right. Of course, we should really have a BiTraversable class of which (,) is an instance.
However, Foldable is a superclass of Traversable, so I get an error message:
Could not deduce (Foldable ((,) o)) from the context () arising from the superclasses of an instance declaration
The best I've thought of is the following:
instance Foldable ((,) o) where fold (_,m) = m
The best (upto efficiency considerations) is always instance Foldable ((,) o) where foldMap = foldMapDefault which amounts to what you chose. SHE makes this a default superclass instance.
However, I don't like how it discards information.
But these folds always do discard information, discarding the shape information and accumulating over the contents. For ((,) o), seen as a functor, the first component is shape information and the second is the content.
Some questions:
* Why is Foldable a superclass of Traversable?
Because the constant-monoid Applicative makes every Traversable Foldable in a uniform way.
* Is there a good choice of a Foldable instance of ((,) o)?
Yes, the one you chose.
* Are there any other problems with the Traversable instance above (besides foldability)?
Nope. It's the Traversable instance which picks out exactly the contents that correspond to the elements abstracted by the Functor. All the best Conor

Thanks much for the answers, Conor. They all make sense to me, particularly
about the typical information discarding in Foldable.
Regards, - Conal
On Tue, Jan 3, 2012 at 3:30 PM, Conor McBride
On 3 Jan 2012, at 23:12, Conal Elliott wrote:
I wanted a Traversable instance for pairing, so I defined one:
instance Traversable ((,) o) where sequenceA (o,fa) = (o,) <$> fa
That looks right. Of course, we should really have a BiTraversable class of which (,) is an instance.
However, Foldable is a superclass of Traversable, so I get an error message:
Could not deduce (Foldable ((,) o)) from the context () arising from the superclasses of an instance declaration
The best I've thought of is the following:
instance Foldable ((,) o) where fold (_,m) = m
The best (upto efficiency considerations) is always
instance Foldable ((,) o) where foldMap = foldMapDefault
which amounts to what you chose.
SHE makes this a default superclass instance.
However, I don't like how it discards information.
But these folds always do discard information, discarding the shape information and accumulating over the contents. For ((,) o), seen as a functor, the first component is shape information and the second is the content.
Some questions:
* Why is Foldable a superclass of Traversable?
Because the constant-monoid Applicative makes every Traversable Foldable in a uniform way.
* Is there a good choice of a Foldable instance of ((,) o)?
Yes, the one you chose.
* Are there any other problems with the Traversable instance above
(besides foldability)?
Nope. It's the Traversable instance which picks out exactly the contents that correspond to the elements abstracted by the Functor.
All the best
Conor

Yeah, I noticed this the other day, and a couple of other instances
which aren't defined, but could be:
http://hpaste.org/56005
I won't pretend I have much use for the Const instance, but it seems
like it should be there anyway, just for completeness (I think it's
possible to define Traversable instances for compositions of functors,
possibly sums and products as well, so Const could be useful in that
context). I think the Either one makes sense, though, as a natural
analogue of the Maybe instance.
On Tue, Jan 3, 2012 at 11:41 PM, Conal Elliott
Thanks much for the answers, Conor. They all make sense to me, particularly about the typical information discarding in Foldable.
Regards, - Conal
On Tue, Jan 3, 2012 at 3:30 PM, Conor McBride
wrote: On 3 Jan 2012, at 23:12, Conal Elliott wrote:
I wanted a Traversable instance for pairing, so I defined one:
instance Traversable ((,) o) where sequenceA (o,fa) = (o,) <$> fa
That looks right. Of course, we should really have a BiTraversable class of which (,) is an instance.
However, Foldable is a superclass of Traversable, so I get an error message:
Could not deduce (Foldable ((,) o)) from the context () arising from the superclasses of an instance declaration
The best I've thought of is the following:
instance Foldable ((,) o) where fold (_,m) = m
The best (upto efficiency considerations) is always
instance Foldable ((,) o) where foldMap = foldMapDefault
which amounts to what you chose.
SHE makes this a default superclass instance.
However, I don't like how it discards information.
But these folds always do discard information, discarding the shape information and accumulating over the contents. For ((,) o), seen as a functor, the first component is shape information and the second is the content.
Some questions:
* Why is Foldable a superclass of Traversable?
Because the constant-monoid Applicative makes every Traversable Foldable in a uniform way.
* Is there a good choice of a Foldable instance of ((,) o)?
Yes, the one you chose.
* Are there any other problems with the Traversable instance above (besides foldability)?
Nope. It's the Traversable instance which picks out exactly the contents that correspond to the elements abstracted by the Functor.
All the best
Conor
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Bitraversable and Bifoldable are already in the bifunctors package. I needed them. ;)
Sent from my iPad
On Jan 3, 2012, at 6:30 PM, Conor McBride
On 3 Jan 2012, at 23:12, Conal Elliott wrote:
I wanted a Traversable instance for pairing, so I defined one:
instance Traversable ((,) o) where sequenceA (o,fa) = (o,) <$> fa
That looks right. Of course, we should really have a BiTraversable class of which (,) is an instance.
However, Foldable is a superclass of Traversable, so I get an error message:
Could not deduce (Foldable ((,) o)) from the context () arising from the superclasses of an instance declaration
The best I've thought of is the following:
instance Foldable ((,) o) where fold (_,m) = m
The best (upto efficiency considerations) is always
instance Foldable ((,) o) where foldMap = foldMapDefault
which amounts to what you chose.
SHE makes this a default superclass instance.
However, I don't like how it discards information.
But these folds always do discard information, discarding the shape information and accumulating over the contents. For ((,) o), seen as a functor, the first component is shape information and the second is the content.
Some questions:
* Why is Foldable a superclass of Traversable?
Because the constant-monoid Applicative makes every Traversable Foldable in a uniform way.
* Is there a good choice of a Foldable instance of ((,) o)?
Yes, the one you chose.
* Are there any other problems with the Traversable instance above (besides foldability)?
Nope. It's the Traversable instance which picks out exactly the contents that correspond to the elements abstracted by the Functor.
All the best
Conor
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
participants (5)
-
Ben Millwood
-
Conal Elliott
-
Conor McBride
-
Edward Kmett
-
Henning Thielemann