#5700: TH: InlinePs inside InstanceD are handled inconsistently
--------------------------------+-------------------------------------------
 Reporter:  mikhail.vorozhtsov  |          Owner:                  
     Type:  bug                 |         Status:  new             
 Priority:  normal              |      Component:  Template Haskell
  Version:  7.3                 |       Keywords:                  
       Os:  Unknown/Multiple    |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown        |       Testcase:                  
Blockedby:                      |       Blocking:                  
  Related:                      |  
--------------------------------+-------------------------------------------
 Consider the following modules:
 {{{
 module Base where

 class C a where
   inlinable :: a -> ()
 }}}
 {{{
 {-# LANGUAGE TemplateHaskell #-}

 module TH where

 import Language.Haskell.TH
 import Base

 mkC :: Name -> Q [Dec]
 mkC n = return
   [InstanceD [] (AppT (ConT ''C) (ConT n))
     [ FunD 'inlinable [Clause [WildP] (NormalB (ConE '())) []]
     ]
   ]
 }}}
 {{{
 {-# LANGUAGE TemplateHaskell #-}

 module Use where

 import TH

 data D = D

 $(mkC ''D)
 }}}
 which compile just fine with GHC. Lets throw in an InlineP pragma after
 the FunD:
 {{{
 PragmaD (InlineP 'inlinable (InlineSpec True False Nothing))
 }}}
 Sadly, this results in an error:
 {{{
 Use.hs:9:3:
     `Base.inlinable' is not a (visible) method of class `Base.C'
 }}}
 or, with 7.2.1:
 {{{
 Use.hs:9:3:
     The INLINE pragma for `Base.inlinable'
       lacks an accompanying binding
 }}}
 OK, another try with
 {{{
 PragmaD (InlineP (mkName "inlinable") (InlineSpec True False Nothing))
 }}}
 Still a no-go in 7.3.20111130 (but accepted by 7.2.1):
 {{{
 Use.hs:9:3: `inlinable' is not a (visible) method of class `Base.C'
 }}}
 Finally, I was able to satisfy GHC by importing Base into Use.
 I think that names in FunD and PragmaD should be treated uniformly (i.e.
 using 'inlinable works/fails in both cases. I'd prefer it works, without
 importing Base).

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5700>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to