overlapping instances and modules

Simon Peyton-Jones simonpj at microsoft.com
Thu Feb 12 12:05:23 EST 2004


I believe this is a buglet in the error message itself.  If you compile
one file at a time, you instead get:

Overlapping instance declarations:
  In module Test: C (T m)
  In module Test: C (t m)

The complaint here is reasonable: you need -fallow-overlapping-instances
when compiling Test.  (One could argue about whether
-fallow-overlapping-instances should apply to the instance declarations
themselves, or to the situation when GHC tries to decide which instance
to use, but GHC currently takes the latter approach.)

It's undoubtedly wrong for GHC to complain about *no* instances when
there are actually *too many*.  It turns out that I fixed this some time
ago, as part of an overhaul of the overlap resolution machinery in the
HEAD.   (The above error message is improved too.)  But since it's
rather a corner case I doubt I'll fix 6.2.  Meanwhile give the flag when
compiling Test.

Simon

| -----Original Message-----
| From: glasgow-haskell-users-bounces at haskell.org
[mailto:glasgow-haskell-users-
| bounces at haskell.org] On Behalf Of Iavor S. Diatchki
| Sent: 13 January 2004 16:49
| To: Haskell Mailing List; glasgow-haskell-users at haskell.org
| Subject: overlapping instances and modules
| 
| hello,
| i am a bit stuck on the following problem,
| which seems to be GHC related.
| consider the following two modules:
| 
|  > {-# OPTIONS -fglasgow-exts -fallow-overlapping-instances #-}
|  > module Test where
|  >
|  > data T m a = T (m a)
|  >
|  > class C m where get :: m a
|  >
|  > instance C (T m)
|  > instance C m => C (t m)
|  >
|  > obs :: T [] Int
|  > obs = get
| 
|  > module Test1 where
|  >
|  > import Test
|  >
|  > obs' :: T [] Int
|  > obs' = get
| 
| i can load the first one (Test) without problems,
| but when i load the second one (Test1) a get the error:
| Test1.hs:6:
|     No instance for (C [])
|       arising from use of `get' at Test1.hs:6
|     In the definition of `obs'': obs' = get
| 
| this seems to indicate that the second instance is being used,
| but i cannot figure out why.  am i doing something silly here?
| 
| -iavor
| ps: i am not on the GHC users list so please cc me if you replay there
| 
| 
| 
| 
| --
| ==================================================
| | Iavor S. Diatchki, Ph.D. student               |
| | Department of Computer Science and Engineering |
| | School of OGI at OHSU                          |
| | http://www.cse.ogi.edu/~diatchki               |
| ==================================================
| 
| 
| _______________________________________________
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users at haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


More information about the Glasgow-haskell-users mailing list