#2739: GHC API crashes on template haskell splices
---------------------------------+------------------------------------------
    Reporter:  waern             |        Owner:  nominolo        
        Type:  bug               |       Status:  assigned        
    Priority:  normal            |    Milestone:  6.10.2          
   Component:  Compiler          |      Version:  6.10.1          
    Severity:  major             |   Resolution:                  
    Keywords:                    |   Difficulty:  Unknown         
    Testcase:                    |           Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
---------------------------------+------------------------------------------
Comment (by waern):

 I tried to fix this issue in Haddock, by using {{{needsTemplateHaskell}}}
 from the GHC API, and checking this right after doing the {{{depanal}}},
 and then setting the target to {{{HscC}}} before going ahead with
 typechecking. This works.

 However, since {{{HscC}}} is a bit heavy, I also tried
 {{{HscInterpreted}}}. But then another Haddock test fail, namely
 {{{TypeFamilies.hs}}}:

 {{{
 {-# LANGUAGE TypeFamilies #-}

 module TypeFamilies where

 -- | Type family G
 type family G a :: *

 -- | A class with an associated type
 class A a where
   -- | An associated type
   data B a :: * -> *
   -- | A method
   f :: B a Int

 -- | Doc for family
 type family F a


 -- | Doc for G Int
 type instance G Int = Bool
 type instance G Float = Int


 instance A Int where
   data B Int x = Con x
   f = Con 3

 g = Con 5
 }}}

 The error message is:

 {{{
 During interactive linking, GHCi couldn't find the following symbol:
   g
 This may be due to you not asking GHCi to load extra object files,
 archives or DLLs needed by your current session.  Restart GHCi, specifying
 the missing library using the -L/path/to/object/dir and -lmissinglibname
 flags, or simply by naming the relevant files on the GHCi command line.
 Alternatively, this link failure might indicate a bug in GHCi.
 If you suspect the latter, please send a bug report to:
   [email protected]
 }}}

 Is this an orthogonal TypeFamilies bug I've stumbled upon?

 If {{{HscIntepreted}}} would work, I was thinking we could use it instead
 of {{{HscC}}} and eventually try to find some way to work around the
 problem exemplified by unboxed tuples (stuff for which
 {{{HscInterpreted}}} doesn't help).

 Or perhaps a more fine-grained check could be provided by the GHC API to
 check exactly which modules need to use which flag. In that case, using
 {{{HscC}}} may not be so bad.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2739#comment:4>
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

Reply via email to