Fair enough. 

These are the observations I have about 'transformers'.

1.) Data.Functor.Product admits a useful monad instance.

Monads do not always have coproducts, but their products are well defined. I rather need this instance for my 'graphs' package, and it can't be defined outside of transformers without orphans. 

instance (Monad m, Monad n) => Monad (Product f g) where
  return a = Pair a a
  Pair m n >>= f = Pair (m >>= fstP . f) (n >>= sndP . f) where
     fstP (Pair a _) = a
     sndP (Pair _ b) = b

However, despite the kind signature, this is not an actual MonadTrans instance.

2.) The instance for Applicative for MaybeT doesn't really follow the other instances for Applicative in transformers.

instance Applicative m => Applicative (MaybeT m) where
   pure = MaybeT . pure . Just
   f <*> a = MaybeT $ (<*>) <$> runMaybeT f <*> runMaybeT a

would instead follow the convention that Applicatives depend only on Applicatives where possible, as opposed to the current default instance. This convention is followed everywhere in transformers except this module.

3.) Data.Functor.Constant is rather redundant given the existence of the identical Const functor in Control.Applicative (which is a module that Data.Functor.Constant depends upon!) The main thing that would need to be fixed is the addition of Traversable and Foldable to Control.Applicative.Const, which shouldn't be all that controversial. I'll propose that more formally separately, as that does directly fall under the libraries processes.

4.) For completeness, I'm including this here, although I sent it in a separate email to Ross the other day. A large number of the monad transformers admit reasonable definitions for Foldable/Traversable. This is particularly important for IdentityT, but also quite useful for MaybeT and ListT, etc. and follows logically from my earlier proposal to add the missing Traversable instances for many of the corresponding Prelude data types and the fact that other data types in the transformers package provide Foldable/Traversable instances.

instance Foldable f => Foldable (IdentityT f) where
  foldMap f (IdentityT a) = foldMap f a

instance Traversable f => Traversable (IdentityT f) where
  traverse f (IdentityT a) = IdentityT <$> traverse f a

instance Foldable f => Foldable (Strict.WriterT w f) where
  foldMap f (Strict.WriterT a) = foldMap (f . fst) a

instance Traversable f => Traversable (Strict.WriterT w f) where
  traverse f (Strict.WriterT a) = Strict.WriterT <$> traverse f' a where
    f' (a, b) = fmap (\c -> (c, b)) (f a)

instance Foldable f => Foldable (Lazy.WriterT w f) where
  foldMap f (Lazy.WriterT a) = foldMap (f . fst) a

instance Traversable f => Traversable (Lazy.WriterT w f) where
  traverse f (Lazy.WriterT a) = Lazy.WriterT <$> traverse f' a where
    f' (a, b) = fmap (\c -> (c, b)) (f a)

instance Foldable f => Foldable (ErrorT e f) where
  foldMap f (ErrorT a) = foldMap (foldMap f) a

instance Traversable f => Traversable (ErrorT e f) where
  traverse f (ErrorT a) = ErrorT <$> traverse (traverse f) a

instance Foldable f => Foldable (MaybeT f) where
  foldMap f (MaybeT a) = foldMap (foldMap f) a

instance Traversable f => Traversable (MaybeT f) where
  traverse f (MaybeT a) = MaybeT <$> traverse (traverse f) a

instance Foldable f => Foldable (ListT f) where
  foldMap f (ListT a) = foldMap (foldMap f) a

instance Traversable f => Traversable (ListT f) where
  traverse f (ListT a) = ListT <$> traverse (traverse f) a

-Edward Kmett

On Wed, Jan 26, 2011 at 3:28 PM, Antoine Latter <aslatter@gmail.com> wrote:
On Wed, Jan 26, 2011 at 2:20 PM, Edward Kmett <ekmett@gmail.com> wrote:
> Do changes to the 'transformers' package fall under the purview of the libraries change control process?

From what I understand, no. The package has a maintainer.

As it is a widely used package, and an integral part of the Platform,
it wouldn't be a bad idea to put out a request for comments on an idea
you have.

Antoine