What am I missing? Cycle in type synonym declarations

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, In this case, you have two 'FooT' names: one is the Type and the other is the Constructor. Perhaps Template Haskell is capturing the wrong one inside the quote (probably the constructor). When you have name shadowing, you should always use a lookup function. You can find these lookup functions in the Template Haskell library. In the meantime, just for a quick test, you can try to change the name of the constructor to something else to avoid capturing, and you can see if the rest of the code works. Jose On Tue, Aug 20, 2013 at 02:00:29PM -0700, David Fox 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 |]
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Tue, Aug 20, 2013 at 5:00 PM, David Fox
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

On Tue, Aug 20, 2013 at 2:35 PM, adam vogt
On Tue, Aug 20, 2013 at 5:00 PM, David Fox
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
Thanks Adam, this must be the answer. And thanks for the equivalent expression.

GHC tries to typecheck quotations. In this case it's trying to typecheck the declaration type Bar = FooT $t Part of type checking is rejecting recursive type synonyms. Here GHC is rejecting it because it *might* be recursive, depending on how $t is filled in. The trouble is that we really *can't* typecheck partial declarations like this one. All this will be fixed when we fold in the new Template Haskell story (it'll be in 7.8). See my blog post on the GHC Trac (from about 2 yrs ago) describing the change. (I'm on a train so don't know the URL.) Geoff has made the change... it just needs to be merged in. Simon | -----Original Message----- | From: Haskell-Cafe [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of David | Fox | Sent: 20 August 2013 22:00 | To: Haskell Cafe | Subject: [Haskell-cafe] What am I missing? Cycle in type synonym declarations | | 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 |] | | _______________________________________________ | Haskell-Cafe mailing list | Haskell-Cafe@haskell.org | http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (4)
-
adam vogt
-
David Fox
-
jabolopes@google.com
-
Simon Peyton-Jones