[Haskell-cafe] change in overlapping instance behavior between GHC 6.12 and GHC 7 causes compilation failure

David Fox ddssff at gmail.com
Wed Nov 3 23:04:43 EDT 2010


I would love to know the answer to this.

On Tue, Nov 2, 2010 at 3:36 PM, Jeremy Shaw <jeremy at n-heptane.com> wrote:
> Hello,
>
> I have a module, XMLGenerator, which has some overlapping instances.
> I have a second module, Test, which imports that module and also adds
> some more overlapping instances.
>
> Both modules contain {-# LANGUAGE OverlappingInstances #-} at the top.
>
> Under some old version of 6.13 (and probably 6.12), if I put both
> modules in the same directory and try to load Test.hs, it gets the
> error:
>
> Test.hs:16:15:
>    Overlapping instances for EmbedAsChild (M IO) (XMLGenT m (XML m))
>      arising from a use of `asChild' at Test.hs:16:15-21
>    Matching instances:
>      instance (m1 ~ m, EmbedAsChild m c) =>
>               EmbedAsChild m (XMLGenT m1 c)
>        -- Defined at XMLGenerator.hs:16:10-68
>      instance (XML m ~ x, XMLGen m) => EmbedAsChild m x
>        -- Defined at XMLGenerator.hs:19:10-51
>    In the first argument of `($)', namely `asChild'
>    In the expression: asChild $ (genElement "foo")
>    In the definition of `asChild':
>        asChild b = asChild $ (genElement "foo")
>
> If I put the XMLGenerator module in a separate package, dummy-hsx, and
> the Test modules links against it, I still get the error.
>
> *but* if I add:
>
>  Extensions:      OverlappingInstances
>
> to the dummy-hsx.cabal file, then Test.hs compiles just fine! So, for
> starters, I do not understand why that happens.
>
> Under GHC 7.0rc1, modifying the .cabal file has no effect. Instead I
> always get the error:
>
> Test.hs:16:15:
>    Overlapping instances for EmbedAsChild (M IO) (XMLGenT m (XML m))
>      arising from a use of `asChild'
>    Matching instances:
>      instance [overlap ok] (m1 ~ m, EmbedAsChild m c) =>
>                            EmbedAsChild m (XMLGenT m1 c)
>        -- Defined in XMLGenerator
>    (The choice depends on the instantiation of `m'
>     To pick the first instance above, use -XIncoherentInstances
>     when compiling the other instance declarations)
>
> Adding the IncoherentInstances flag does make it compile -- but I have
> never enabled that flag and not regretted it.
>
> What changed between GHC 6.12 and GHC 7.0? Is there a some solution
> besides using IncoherentInstances in every module that imports
> XMLGenerator?
>
> I have attached XMLGenerator.hs, Test.hs, and dummy-hsx.cabal.
>
> thanks!
> - jeremy
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>


More information about the Haskell-Cafe mailing list