class declaration in boot file

Gaal Yahas gaal at forum2.org
Fri Aug 11 16:05:35 EDT 2006


(I forgot to say, this was with 6.4.2.)

Another problem I'm having is that when I consume a datatype, its
derived instances aren't available; and even in an hs-boot file, a
'deriving' clause is illegal on a type with no constructors. So I can't
compile B in this case:

    module A where

    import B
    data DT1 = X | Y deriving Show

    module B where

    import {-# SOURCE #-} A

    data DT2 = MkDT2 { Q :: DT1 } deriving Show

Because of missing Show instances for DT1. (In practise, I think it
might work if I spell out the full declaration of DT1 with the deriving
clause, but I don't want the creep: X and Y are really records entailing
additional types B need not concern itself with.)

I'm hoping 6.6 will allow me to say this in the hs-boot file:

    data DT1 deriving Show

On Fri, Aug 11, 2006 at 10:59:29AM +0100, Simon Peyton-Jones wrote:
> Well this is odd.  The manual (for 6.6 anyway) says that class decls are
> allowed in hs-boot files, but instance decls are not, whereas the code
> seems to say that class decls aren't but instance decls are!
> 
> I will look into this.  Meanwhile, I'm afraid you just can't put a class
> decl in the hs-boot file with the version of the compiler you have.
> 
> Simon
> 
> | -----Original Message-----
> | From: glasgow-haskell-users-bounces at haskell.org
> [mailto:glasgow-haskell-users-bounces at haskell.org]
> | On Behalf Of Gaal Yahas
> | Sent: 09 August 2006 18:25
> | To: GHC Users Mailing List
> | Subject: class declaration in boot file
> | 
> | I'm trying to solve a circularity problem with .hs-boot, but am
> getting
> | the error: "Illegal class declaration in hs-boot file".
> | 
> | The offending declaration is:
> | 
> | class (Monad m, Functor m, Eq a, Data a, Typeable a) => ICoercible m a
> | a -> m
> | 
> | I've tried with and without the fundeps. Data and Typeable are in
> scope,
> | and -fglasgow-exts is set. Any ideas on what else I should be doing?
> | 
> | --
> | Gaal Yahas <gaal at forum2.org>
> | http://gaal.livejournal.com/
> | _______________________________________________
> | Glasgow-haskell-users mailing list
> | Glasgow-haskell-users at haskell.org
> | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

-- 
Gaal Yahas <gaal at forum2.org>
http://gaal.livejournal.com/


More information about the Glasgow-haskell-users mailing list