So this is definitely a GHC bug, but I think the problem is probably
triggered by this line:

instance  Serializable a b => IResource a

I don't think this is a valid instance declaration without a functional
dependency on Serializable, as it's impossible to know which type 'b' to use
in the methods of IResource.

  -- ryan

On Tue, Jun 28, 2011 at 3:43 AM, Alberto G. Corona <agocor...@gmail.com>wrote:

> I have an "'impossible' happened" error.
>
> The code may look a little bit convoluted but it is part of my real code.:
>
>
> --------- begin of code------
>
> {-# LANGUAGE   FlexibleInstances, UndecidableInstances
>                , MultiParamTypeClasses
>                 #-}
>
> class Serializable a b
>
>
> class IResource a     --The rest of the instance definitions does not
> matter for the error
>
>
> instance  Serializable a b => IResource a
>
> data DBRef a=  DBRef String   a
>
>
> instance  (IResource a) => Read (DBRef a)
>
>
> data   Votation a= Votation{
>   content         :: DBRef a
> } deriving (Read)
>
> ------------------------------- end of code ---
>
> gives the following error at compilation time:
>
> tests>runghc impossiblelloop.hs
> ghc: panic! (the 'impossible' happened)
>   (GHC version 7.0.3 for i386-unknown-mingw32):
>         solveDerivEqns: probable loop
>     (impossiblelloop.hs:20:13-16 main:Main.$fReadVotation{v rhI} [a{tv abB}
> [tv]
> ] base:GHC.Read.Read{tc 2d} [main:Main.Votation{tc rbo}
>
>                                a{tv abB} [tv]] = [base:GHC.Read.Read{tc 2d}
>
>                                                     (main:Main.DBRef{tc
> rbu}
>
>                                                        a{tv abB} [tv])])
>     [[main:Main.Serializable{tc rbA} a{tv abB} [tv] b{tv ajE} [tcs]]]
>
> Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to