conflicting multi-parameter family instance declarations
Michal Konečný
m.konecny at aston.ac.uk
Tue Jan 13 12:08:02 UTC 2015
Dear all,
The following compiles with ghc 7.6 but fails with ghc 7.8:
-----
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Test where
class M t s where
type T t s
data I t = I t
instance M t t where
type (T t t) = ()
instance M t (I t) where
type (T t (I t)) = ()
-----
The error I get with ghc 7.8.3 and 7.8.4 is:
Test.hs:12:10:
Conflicting family instance declarations:
T t t -- Defined at Test.hs:12:10
T t (I t) -- Defined at Test.hs:15:10
I am curious if this change is an improvement or a bug. I would be grateful for help as this issue affects a fairly large library I develop.
Best regards,
Michal
--
|-| Dr. Michal Konecny, Computer Science, Aston University
|-| Room MB212D | Tel +44 121 204 3462 | Fax +44 121 204 3681
|-| http://duck.aston.ac.uk/konecnym
|-| OpenPGP key http://duck.aston.ac.uk/konecnym/ki.aston
More information about the Glasgow-haskell-users
mailing list