Haskell Platform Proposal: add transformers and revise the mtl package to depend on it

Ross Paterson ross at soi.city.ac.uk
Thu Sep 16 04:23:49 EDT 2010


The proposal is that version 2 of the mtl package be the current contents
of the monads-fd package, which depends on the transformers package:

    http://hackage.haskell.org/package/monads-fd
    http://hackage.haskell.org/package/transformers

An up to date copy of this text is kept at:

    http://trac.haskell.org/haskell-platform/wiki/Proposals/transformers

Everyone is invited to review this proposal, following the standard
procedure for proposing and reviewing packages.

    http://trac.haskell.org/haskell-platform/wiki/AddingPackages

Review comments should be sent to the libraries mailing list by
October 15 so that we have time to discuss and resolve issues
before the final deadline on November 1.

    http://trac.haskell.org/haskell-platform/wiki/ReleaseTimetable

== Proposer ==

 * Ross Paterson (maintainer of transformers and monads-fd)

If this proposal is accepted, monads-fd would be obsoleted and
transformers would be turned over to community control (like the current
mtl package).

== Rationale ==

Monad transformers are widely used, but the MTL interface is tied to
functional dependencies, whose future is in doubt.  Many people want to
try out interfaces based on type functions, or without using experimental
type class features, but their interfaces will then be incompatible with
libraries using mtl.

The idea is to factor out the monad transformers as the Haskell 98
package.  The objectives for this package are:

 1. that it be as useful as possible by itself, so that it can replace
    many uses of mtl.

 2. that it serve as a base for other packages adding type classes based
    on either functional dependencies (e.g. mtl) or type functions,
    with interfaces referring to the monad transformers being compatible
    across the different libraries.

The transformers and monads-fd packages have been in use for over 18
months, and are used by 112 and 23 packages respectively.  The split
structure has been shown to be viable, but its existence in parallel
with mtl has meant extra effort for authors of client packages.  It is
time to complete the transition.

== Structure ==

The current mtl is to be split in two:

 * transformers is a Haskell 98 package containing
    * base functors (Data.Functor.Constant and Data.Functor.Identity),
    * operations on functors (Data.Functor.Compose and Data.Functor.Product),
    * transformer classes (Control.Monad.Trans.Class and
      Control.Monad.IO.Class) and
    * concrete monad transformers with code to lift operators
      (Control.Monad.Trans.*).
   The package can be used on its own (see the Control.Monad.Trans.Class
   documentation for examples), or with packages adding type classes.

 * mtl-2 (the current monads-fd) depends on transformers and adds type
   classes using functional dependencies.  It has the same modules as
   mtl-1 and usage is very close, except for the differences listed below.

== Incompatibilities ==

The proposed interface of mtl-2 is close to that of mtl-1, but with the
following differences (illustrated with Reader):

 * instances of Applicative and Alternative have been added as appropriate,
   e.g.
   
        instance (Applicative m) => Applicative (ReaderT r m) where ...
        instance (Alternative m) => Alternative (ReaderT r m) where ...


   Rationale: These classes postdate the MTL, and such instances have
   been repeatedly defined in various packages.  They belong together
   with the type constructors.

 * Functor instances for monad transformers no longer require Monad
   where Functor is sufficient.  Unfortunately this is incompatible
   because Functor is not a superclass of Monad, e.g.
   
        instance (Monad m) => Functor (ReaderT r m) where ...

   is replaced by
   
        instance (Functor m) => Functor (ReaderT r m) where ...

   Rationale: These instances are more general, and are consistent with
   the instances of other classes.

 * simple monads are now aliases for monad trasformers applied to Identity,
   e.g.
   
        newtype Reader r a = Reader { runReader :: r -> a }

   is replaced by
   
        type Reader r = ReaderT r Identity
 
        reader :: (r -> a) -> Reader r a
        reader f = ReaderT (Identity . f)

        runReader :: Reader r a -> r -> a
        runReader m = runIdentity . runReaderT m

   Rationale: This avoids repetition in the interfaces of both
   transformers and the proposed mtl-2.  It makes transformers more useful
   on its own, and also saves clients of mtl from defining instances
   for both Reader r and ReaderT r and ensuring that they are consistent.

 * The instance Error String is restructured to avoid a type synonym instance:

        instance Error String where
            noMsg  = ""
            strMsg = id

   is replaced by

        instance ErrorList a => Error [a] where
            strMsg = listMsg
         
        class ErrorList a where
            listMsg :: String -> [a]
         
        instance ErrorList Char where
            listMsg = id

   Rationale: This makes the instance Haskell 98, so it can be included
   in the transformers package.

== Transition issues ==

In early September 2010, of the 510 buildable packages in hackage that
directly depended on mtl,
 * 312 built unchanged with the proposed mtl-2
 * 102 had a bounded mtl dependency (or a dependent package had) that
   excluded mtl-2
 * 2 failed because of the recent move of the Monad (Either e) instance
   from mtl to base
 * 41 failed with the new mtl:
    * 11 because they defined their own Applicative instances (which can
      now be deleted)
    * 11 because of the changed constraint on Functor instances
    * 15 that used the constructors of base monads (which can be trivially
      replaced)
    * 3 that defined instances for base monads
    * 1 that defined an overlapping Error instance
 * 53 failed because they depended on one of the other failures
The attached test report lists the packages involved.

== Other issues ==

Some other issues have been raised with mtl over the years, but they
are orthogonal to this proposal:
 * The MonadCont instance for StateT is not compatible with the monad
   transformer.  The transformers package provides the correct lifting
   (in which callcc causes the state to rollback on entering the saved
   continuation), but also provides the MTL lifting for compatibility,
   and this is used by monads-fd.  It could be switched to the correct
   lifting later.
 * The ErrorT monad transformer has an Error constraint, so that errors
   can be passed to the fail method of the Monad class.
 * ListT only works on commutative monads.

Attachments

 * mtl-2.0.0.0.tar.gz (13.4 kB) -"proposed mtl-2.0.0.0.tar.gz", added by ross on 09/14/10 19:01:21.
 * test-Sep-2010 (21.3 kB) -"test of mtl-using packages in Sep 2010", added by ross on 09/15/10 20:05:56.



More information about the Libraries mailing list