bug in template haskell (with recursion?)
Jake Wheat
jakewheatmail at googlemail.com
Wed Jan 27 15:34:29 EST 2010
Hello All,
I'm trying to write a splice to make HList type signatures a bit more
concise, I don't know whether this is a good idea or not.
I wrote a small function to do '[(Type,Type)] -> Q Type' for this, and
got the following from GHC. Should I add this to the bug tracker?
Details:
THBug1.hs:
{-# LANGUAGE TemplateHaskell #-}
module THBug1 where
import Data.HList
import Language.Haskell.TH
mhlt :: [(Type,Type)] -> Q Type
mhlt x = [t| Record $(foldThing x)|]
where
foldThing ((f,t):xs) = [t|HCons (LVPair (Proxy $f) $t) $(foldThing xs)|]
foldThing [] = [t|HNil|]
----
$ ghc -c THBug1.hs
THBug1.hs:12:61:
GHC internal error: `foldThing' is not in scope during type
checking, but it passed the renamer
tcg_type_env of environment: []
In the expression: foldThing xs
In the Template Haskell quotation
[t| HCons (LVPair (Proxy $f) $t) $(foldThing xs) |]
In the expression:
[t| HCons (LVPair (Proxy $f) $t) $(foldThing xs) |]
I'm using GHC 6.12.1 from debian experimental:
$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.12.1
$ ghc-pkg list |grep template
template-haskell-2.4.0.0
To get HList to install with GHC 6.12, I downloaded the latest version from
http://old-darcs.well-typed.com/HList/
and altered it slightly, updated package here:
http://launchpad.net/hssqlppp/prealpha/environment/+download/HList-0.2.tar.gz
the changes I made are:
diff -rN old-HList/Data/HList/GhcSyntax.hs new-HList/Data/HList/GhcSyntax.hs
2c2
< {-# LANGUAGE FlexibleContexts #-}
---
> {-# LANGUAGE FlexibleContexts, TypeOperators #-}
diff -rN old-HList/Data/HList/Label2.hs new-HList/Data/HList/Label2.hs
1c1,2
< {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses,
UndecidableInstances, EmptyDataDecls #-}
---
> {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, UndecidableInstances, EmptyDataDecls,
> ExistentialQuantification #-}
36c37
< data HNat x => Label x ns desc -- labels are exclusively type-level entities
---
> data Label x ns desc = HNat x => Label x ns desc -- labels are exclusively type-level entities
diff -rN old-HList/Data/HList/Label3.hs new-HList/Data/HList/Label3.hs
1c1,2
< {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses,
UndecidableInstances, EmptyDataDecls #-}
---
> {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, UndecidableInstances, EmptyDataDecls,
> ExistentialQuantification #-}
37c38
< data HNat x => Label x ns desc -- labels are exclusively type-level entities
---
> data Label x ns desc = HNat x => Label x ns desc -- labels are exclusively type-level entities
(If it's not obvious, I have no idea what I'm doing..., but my small
amount of code which uses HList worked fine with this altered
package.)
Thanks,
Jake Wheat
More information about the Glasgow-haskell-users
mailing list