#4364: Template Haskell: Cycle in type synonym declarations
----------------------------------------+-----------------------------------
Reporter: igloo | Owner: simonpj
Type: bug | Status: new
Priority: high | Milestone: 7.4.1
Component: Compiler (Type checker) | Version: 7.1
Keywords: | Testcase:
Blockedby: | Difficulty:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: None/Unknown
----------------------------------------+-----------------------------------
Changes (by jakewheat):
* cc: jakewheatmail@… (added)
Comment:
Hello,
I am getting the same error with the following code. This code compiles
fine in ghc 6.12.1 - I'm not sure if this is the same bug or not.
ThStuff.hs:
{{{
{-# LANGUAGE TemplateHaskell #-}
module ThStuff (makeRecord) where
import Data.HList
import Language.Haskell.TH
makeRecord :: [(Name,Name)] -> Q Type
makeRecord lvs =
[t| Record $(ps) |]
where
ps = sequence (map mkPair lvs) >>= foldIt
mkPair (l,v) = [t| LVPair (Proxy $(conT l)) $(conT v) |]
foldIt :: [Type] -> Q Type
foldIt = \tt -> case tt of
[] -> [t|HNil|]
(t:ts) -> [t| HCons $(return t) $(foldIt ts)|]
}}}
Types.hs:
{{{
{-# LANGUAGE
TemplateHaskell,EmptyDataDecls,DeriveDataTypeable,FlexibleContexts #-}
module Types where
import Data.HList.MakeLabels
$(label "size")
}}}
Test.hs:
{{{
{-# LANGUAGE TemplateHaskell #-}
import Data.HList
import ThStuff
import Data.HList.Label4 ()
import Types
-- this definition only works in ghc 6.12.1
type TestRow = $(makeRecord [(''Size, ''Int)])
-- using this definition works in both ghc 6.12.1 and ghc 7.0.2
--type TestRow = Record (HCons (LVPair (Proxy Size) Int)
-- HNil)
main :: IO ()
main = do
let t :: TestRow
t = size .=. 1
.*. emptyRecord
print t
}}}
{{{
$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 7.0.2
$ ghc --make Test.hs
[1 of 3] Compiling Types ( Types.hs, Types.o )
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package ffi-1.0 ... linking ... done.
Loading package pretty-1.0.1.2 ... linking ... done.
Loading package array-0.3.0.2 ... linking ... done.
Loading package containers-0.4.0.0 ... linking ... done.
Loading package template-haskell ... linking ... done.
Loading package HList-0.2.3 ... linking ... done.
[2 of 3] Compiling ThStuff ( ThStuff.hs, ThStuff.o )
[3 of 3] Compiling Main ( Test.hs, Test.o )
Test.hs:10:1:
Cycle in type synonym declarations:
Test.hs:10:1-46: type TestRow = $(makeRecord [('Size, 'Int)])
}}}
I am using the GHC from here:
http://haskell.org/ghc/download_ghc_7_0_2#x86_64linux
on Debian testing
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4364#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs