[Haskell-cafe] instance Binary UTCTime (Was: Oprhan instances)

David Menendez dave at zednenem.com
Thu Nov 26 16:40:16 EST 2009


On Thu, Nov 26, 2009 at 3:47 PM, Antoine Latter <aslatter at gmail.com> wrote:
>
> Lets say I want to provide an alternate or additional library of monad
> transformer data types. To make these types maximally useful, they
> should implement the typeclasses in the mtl package and in the
> monads-tf package.
>
> The only way to do this in a reasonable way is with multiple packages
> and orphan instances:
>
> mypackage
> mypackage-classes-tf
> mypackage-classes-fd
>
> where the 'classes' packages do nothing but provide class implementations.

This is the method I'm using for my own monad transformer library. I
initially considered using a flag to specify which instances to
provide, but I concluded that providing a consistent API was more
important than avoiding orphan instances.

The problem with this solution is that it doesn't scale. If we have M
packages providing types and N packages providing classes, then we
need M*N additional packages for orphans.

The best long-term solution is probably extending Cabal to handle this
more transparently, perhaps by allowing packages to depend on flagged
versions of other packages (e.g., foomonad >= 4.0 && < 4.1 && HAS_MTL)
or some sort of bundled "intersection" packages.

> But then we're in a tight spot if someone doesn't notice that I have
> the mypackage-classes-tf package released, provides their own
> instances, and ships them in a library.
>
> Am I missing something? And how can we extend the language to make
> this better? Does anything short of class-instance explicit
> import/export make this better?

With FlexibleContexts, GHC will accept code that depends on
not-yet-known instances.

{-# LANGUAGE FlexibleContexts #-}
module Foo where

foo :: (Monad (Either Char)) => Int -> Either Char Bool
foo i = do
    if i < 0 then Left 'a' else Right ()
    return False

If I write another module that imports Foo and has an instance for
Monad (Either Char) in scope, I can call foo. Otherwise, I get a type
error.

-- 
Dave Menendez <dave at zednenem.com>
<http://www.eyrie.org/~zednenem/>


More information about the Haskell-Cafe mailing list