[Template-haskell] change in [d| |] and creating instances in template-haskell 2.7

Jeremy Shaw jeremy at n-heptane.com
Thu Sep 8 17:42:06 CEST 2011


On Sep 8, 2011, at 4:00 AM, Simon Peyton-Jones wrote:

> [Redireting to ghc users; the TH list is pretty dormant and I keep  
> thinking I should close it down altogether.]
>
> Jeremy
>
> Actually this is by design.  See the long thread at http://hackage.haskell.org/trac/ghc/ticket/5375
>
> When you say
>
> | inferBar typeName =
> |    do s <- [d| bar _ = "sucker"
> |              |]
>
> you are asking for a *new* definition bar _ = "sucker".  But in an  
> instance declaration you have to mention the *existing* method name.

Right. That makes sense.

> To put it another way, do you expect this to work?
>
>  do { bar_nm <- newName "bar"
>     ; return (InstanceD [] <type> [FunD bar_nm <rhs>]) }
>
> where you make up a *fresh name* (whose string-name is "bar") and  
> use it in an instance declaration binding.

no.

> I suppose you could argue that for the odd case of instance decls,  
> TH should ignore the exact identity of the method name, and just use  
> its string name. It would be convenient; but another weirdness too.

Yeah. I would expect this to work:

inferBar2 :: Name -> Q [Dec]
inferBar2 typeName =
   [d| instance Bar $(conT typeName) where
         bar _ = "sucker"
     |]

But I get the same error:

     inferBar2 'Bool
   ======>
     show-test.hs:4:3-18
     instance Bar Bool where
         { bar_aTK _ = "sucker" }

show-test.hs:4:3:
     Warning: No explicit method nor default method for `bar'
     In the instance declaration for `Bar Bool'

Presumably because bar is still being created as a *fresh name*. I  
think in that version, it is more surprising that it does not work  
because the whole instance declaration is inside the [d| |].  
Additionally, it is not obvious (to me) how to work around the issue  
and keep the code pretty / easily readable.

But, as you point out, making bar not be a fresh name there creates a  
'special case'. So, that is not great either..

When you saw inferBar2, did you find it somewhat 'surprising' that it  
didn't work ?

- jeremy

> User advice welcome!
>
> Simon
>
>
> | -----Original Message-----
> | From: template-haskell-bounces at haskell.org [mailto:template-haskell-
> | bounces at haskell.org] On Behalf Of Jeremy Shaw
> | Sent: 07 September 2011 20:50
> | To: template-haskell at haskell.org
> | Subject: [Template-haskell] change in [d| |] and creating  
> instances in template-
> | haskell 2.7
> |
> | Hello,
> |
> | I have some code that likes like this, which works in template- 
> haskell
> | 2.5 / GHC 7.0.3:
> |
> | ---------------
> | {-# Language TemplateHaskell, TypeFamilies #-}
> | module Show where
> |
> | import Language.Haskell.TH
> |
> | class Bar a where
> |    bar :: a -> String
> |
> | inferBar :: Name -> Q [Dec]
> | inferBar typeName =
> |    do s <- [d| bar _ = "sucker"
> |              |]
> |       d <- instanceD (return []) (appT (conT ''Bar) (conT typeName))
> | (map return s)
> |       return [d]
> |
> | -----------------
> |
> | $(inferBar ''Bool)
> |
> | But, in template-haskell 2.6 / GHC 7.2.1, I get an error,
> |
> |     Warning: No explicit method nor default method for `bar'
> |      In the instance declaration for `Bar Bool'
> |
> | Comparing the output of -ddump-splices we see in GHC 7.0.3/ TH  
> 2.5, we
> | have:
> |
> | bar-test.hs:1:1: Splicing declarations
> |      inferBar 'Bool
> |    ======>
> |      bar-test.hs:4:3-17
> |      instance Bar Bool where
> |          { bar _ = "sucker" }
> |
> | But in GHC 7.2.1 / TH 2.6 we have:
> |
> | bar-test.hs:1:1: Splicing declarations
> |      inferBar 'Bool
> |    ======>
> |      bar-test.hs:4:3-17
> |      instance Bar Bool where
> |          { bar_acAU _ = "sucker" }
> |
> | The difference being that instead 'bar' we have 'bar_acAU'.  So  
> maybe
> | that is why it can't find the method 'bar' in the instance
> | declaration? Though, I would kind of expect an error like,
> |
> | `bar_acAU' is not a (visible) method of class `Bar'.
> |
> | Am I doing something wrong? Should I file a bug ?
> |
> | Thanks!
> |
> | - jeremy
> |
> |
> |
> | _______________________________________________
> | template-haskell mailing list
> | template-haskell at haskell.org
> | http://www.haskell.org/mailman/listinfo/template-haskell
>




More information about the Glasgow-haskell-users mailing list