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 |
==================================================



_______________________________________________ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Reply via email to