
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