Type error when deriving Generic for an associated data type

Bas van Dijk v.dijk.bas at gmail.com
Thu Jul 12 12:27:53 CEST 2012


Hi,

I'm hitting on an issue when deriving Generic for an associated data type:

{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DeriveGeneric #-}

import GHC.Generics

class Foo a where
    data T a :: *

instance Foo Int where
    data T Int = Bla deriving Generic

Couldn't match type `Rep (T Int)' with `M1 t0 t1 (M1 t2 t3 U1)'
    Expected type: Rep (T Int) x
      Actual type: M1 t0 t1 (M1 t2 t3 U1) x
    In the pattern: M1 (M1 U1)
    In an equation for `to': to (M1 (M1 U1)) = Bla
    In the instance declaration for `Generic (T Int)'

The GHC trac seems to be down. Is this a known issue?

Cheers,

Bas



More information about the Glasgow-haskell-users mailing list