[Haskell-cafe] What am I missing? Cycle in type synonym declarations

adam vogt vogt.adam at gmail.com
Tue Aug 20 23:35:17 CEST 2013


On Tue, Aug 20, 2013 at 5:00 PM, David Fox <dsf at seereason.com> wrote:
> This file gives me the error "Cycle in type synonym declarations"  Can
> anyone tell me why?  I'm just trying to write a function to create a
> type that is a FooT with the type parameter fixed.
>
> {-# LANGUAGE TemplateHaskell #-}
> import Language.Haskell.TH (Q, Dec, TypeQ)
>
> data FooT a = FooT a
>
> foo :: TypeQ -> Q [Dec]
> foo t = [d| type Bar = FooT $t |]

Hi David,

That's strange considering you can accomplish  the same thing with:

foo t = fmap (:[]) $ tySynD (mkName "Bar") [] [t| FooT $t |]

Bugs like <http://ghc.haskell.org/trac/ghc/ticket/4230> are a similar
problem. In your case it seems that GHC is too eager to prevent the
cycle you could make with  foo (conT (mkName "Bar")))

Regards,
Adam




More information about the Haskell-Cafe mailing list