[Haskell-cafe] Weird issue with ConstraintKinds

Dag Odenhall dag.odenhall at gmail.com
Sat Oct 26 14:10:33 UTC 2013


This is a bug fixed in HEAD <http://ghc.haskell.org/trac/ghc/ticket/8359>.


On Sat, Oct 26, 2013 at 3:49 PM, Jacques Carette <carette at mcmaster.ca>wrote:

> Consider the following (minimal, for illustration purposes) code:
>
> {-# LANGUAGE ConstraintKinds #-}
> module Weird where
>
> class A a where
> class B b where
> class C c where
>
> data X a = X a
> data Y a = Y a
>
> -- works fine, but can be verbose when things multiply
> instance (A a, B a) => C (X a) where
>
> -- So use ConstraintKinds:
> type D a = (A a, B a)
> instance D a => C (Y a) where
>
> =====
> and now I get
>     Variable `a' occurs more often than in the instance head
>       in the constraint: D a
>     (Use -XUndecidableInstances to permit this)
>     In the instance declaration for `C (Y a)'
>
> Why??  Since D is an abbreviation, why would it behave differently than
> when I hand expand it?
> [This is with GHC 7.6.3]
>
> Jacques
> ______________________________**_________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/**mailman/listinfo/haskell-cafe<http://www.haskell.org/mailman/listinfo/haskell-cafe>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20131026/f761ed55/attachment.html>


More information about the Haskell-Cafe mailing list