Traversable instance for ((,) o) ?

Henning Thielemann lemming at henning-thielemann.de
Wed Jan 4 00:24:00 CET 2012


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



More information about the Libraries mailing list