
On Mon, Sep 3, 2012 at 12:00 PM, Roman Cheplyaka
There's a bug in syb-with-class reported by Alexey Rodriguez Yakushev in 2008 [1]. I can confirm that the bug is still there (syb-with-class-0.6.1.3, ghc 7.4.1).
[1]: http://www.haskell.org/pipermail/haskell-cafe/2008-March/041179.html
Here's an even simpler test case:
{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, UndecidableInstances, TemplateHaskell, OverlappingInstances, DeriveDataTypeable #-} import Data.Generics.SYB.WithClass.Basics import Data.Generics.SYB.WithClass.Derive
data Foo = Foo Foo | Bar deriving (Typeable, Show)
deriveData [''Foo]
f :: (Data NoCtx ast, Typeable ast) => ast -> TypeRep f = typeOf
main = print $ f $ Foo Bar
This is pretty similar to what ended up being a ghc bug, fixed in 7.0 though: http://hackage.haskell.org/trac/ghc/ticket/3731
The cause of this bug is a self-referencing instance created by deriveData:
instance (Data ctx Foo, Sat (ctx Foo)) => Data ctx Foo where ...
What's the proper way to fix it?
From a few tests it seems we no longer need the circular context hack in ghc-7.4.1 to get the instance to typecheck, so we could side-step the issue entirely by removing it from the generated code.
-- Andrea Vezzosi