
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

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@haskell.org
[mailto:glasgow-haskell-users-bounces@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

(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@haskell.org [mailto:glasgow-haskell-users-bounces@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
| http://gaal.livejournal.com/ | _______________________________________________ | Glasgow-haskell-users mailing list | Glasgow-haskell-users@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
--
Gaal Yahas

You can't use 'deriving' in hs-boot files, nor instance declarations.
In the HEAD (and hence in 6.6) you can put instance declarations in
though, thus:
data DT2
instance Show DT2
Simon
| -----Original Message-----
| From: Gaal Yahas [mailto:gaal@forum2.org]
| Sent: 11 August 2006 21:06
| To: Simon Peyton-Jones
| Cc: GHC Users Mailing List
| Subject: Re: class declaration in boot file
|
| (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@haskell.org
| > [mailto:glasgow-haskell-users-bounces@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

Prodded by your mail, I've gotten back to hs-boot files. I've fixed the
HEAD so that both class and instance declarations are allowed in hs-boot
files. But not 'deriving'!
Simon
| -----Original Message-----
| From: Gaal Yahas [mailto:gaal@forum2.org]
| Sent: 11 August 2006 21:06
| To: Simon Peyton-Jones
| Cc: GHC Users Mailing List
| Subject: Re: class declaration in boot file
|
| (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@haskell.org
| > [mailto:glasgow-haskell-users-bounces@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
participants (2)
-
Gaal Yahas
-
Simon Peyton-Jones