[Template-haskell] Re: TH2 bug
Keean Schupke
k.schupke at imperial.ac.uk
Wed Oct 27 10:11:47 EDT 2004
Just checked and 'Type' has an entry (ArrowT) for functions.
Why not just use the existing Type. IE
reify ''(->)
data Info =
PrimTyCon Type
TyConI Dec
This would be fine for tuples as well, I wonder if () could be
encoded as a tuple of 0?
Keean.
Keean Schupke wrote:
> Actually I would like it to be a special name... but I guess there
> are other possibilities.
>
> Ideally I would like:
>
> case info of
> (PrimTyCon name) -> instanceD (cxt []) (appT (conT classname) (appT
> (appT (conT name) (varT a) (varT b)))
>
> to generate:
>
> instance ClassName (a -> b)
>
>
> Keean
>
> Simon Peyton-Jones wrote:
>
>> OK, now I get it. I'm copying the TH list in the hope that other TH
>> aficionados will chime in.
>>
>> The problem is with reify, not the '' notation. Here it is in a
>> nutshell:
>> what value should be returned by the call (reify ''(->) )?
>>
>> Recall that
>> reify :: Name -> Q Info
>>
>> So reify claims to return an Info, and for a type constructor it
>> currently returns a TyConI; but a TyConI contains a Dec, and there
>> simply is no Dec in the TH syntax for a function type; it's built in,
>> rather like Int# etc. So reify falls over in a bad way.
>>
>> It's obviously unsatisfactory for reify to just fall over in this case,
>> but what would you like? A new constructor in Info for primitive
>> tycons? A new constructor in Dec?
>> And what questions do you want to be able to ask of the value in the
>> Info? For example would it be enough to day
>>
>> data Info = TyConI Dec
>> | PrimTyCon
>> | ClassI Dec
>> ...etc...
>>
>> where the PrimTyCon is returned for (->), Int#, etc?
>>
>> Nothing difficult about fixing this once the design is clear.
>>
>> Simon
>>
>> | -----Original Message-----
>> | From: Keean Schupke [mailto:k.schupke at imperial.ac.uk]
>> | Sent: 27 October 2004 11:14
>> | To: Simon Peyton-Jones
>> | Subject: Re: TH2 bug
>> | | Yup, using HEAD. Here's an example template:
>> | | ttypeshow :: Name -> Q [Dec]
>> | ttypeshow q = do
>> | r <- reify q
>> | case r of
>> | (TyConI t) -> runIO . putStrLn . show $ t
>> | _ -> return ()
>> | return []
>> | | Then in another file we do:
>> | | $(ttypeshow ''(->))
>> | | Which fails, as does ''(), and ''(,) etc...
>> | | ''[] works okay however
>> | | Keean.
>> | | | Simon Peyton-Jones wrote:
>> | | >I can't reproduce this. Works for me. What version of GHC are you
>> | >using? The HEAD I assume?
>> | >
>> | >Simon
>> | >
>> | >| -----Original Message-----
>> | >| From: MR K P SCHUPKE [mailto:k.schupke at imperial.ac.uk]
>> | >| Sent: 22 October 2004 18:23
>> | >| To: glasgow-haskell-users at haskell.org; Simon Peyton-Jones
>> | >| Subject: TH2 bug
>> | >|
>> | >|
>> | >| Just reporting a bug, taking types using '' works fine for:
>> | >|
>> | >| ''Int
>> | >| ''[]
>> | >|
>> | >| But when you try:
>> | >|
>> | >| ''(->)
>> | >|
>> | >| you get:
>> | >|
>> | >| No match in record selector TyCon.algTcRhs
>> | >|
>> | >| Please report it as a compiler bug to
>> | >glasgow-haskell-bugs at haskell.org,
>> | >| or http://sourceforge.net/projects/ghc/.
>> | >|
>> | >|
>> | >| Keean.
>> | >
>> | >
>>
>>
>>
>
> _______________________________________________
> template-haskell mailing list
> template-haskell at haskell.org
> http://www.haskell.org/mailman/listinfo/template-haskell
More information about the template-haskell
mailing list