[nhc-users] Disappearing instances?

Martin Sjögren msjogren at gmail.com
Wed Jul 28 11:47:08 EDT 2004


Hello list.

Since NHC doesn't distribute Control.Monad.Error that, among other
things, defines the Monad  (Either e) instance, I wrote the following
module for Cabal:

http://cvs.haskell.org/darcs/cabal/Compat/H98.hs

However, when I compile it, the Monad instance seems to disappear!

With a small test program

> module Main where
> import Monad
> import Compat.H98
> foo :: Either Char [()]
> foo = sequence [Right (), Left 'a', Right (), Left 'b']
> main = print foo

nhc complains:

Fail: The class Prelude.Monad has no instance for the type Prelude.Either.

and indeed if I look at Compat/H98.hi, it mentions

instance Error Prelude.Char;
instance (Error a) => Error [a];

but nothing about Error e => Monad (Either e)


What should I do? Is this a bug?


/Martin


More information about the Nhc-users mailing list