[GHC] #9032: Panic with self-import

GHC ghc-devs at haskell.org
Tue May 27 19:59:15 UTC 2014


#9032: Panic with self-import
---------------------------------------+-----------------------------------
        Reporter:  jstolarek           |            Owner:
            Type:  bug                 |           Status:  new
        Priority:  normal              |        Milestone:
       Component:  Compiler            |          Version:  7.8.2
      Resolution:                      |         Keywords:
Operating System:  Unknown/Multiple    |     Architecture:
 Type of failure:  Compile-time crash  |  Unknown/Multiple
       Test Case:                      |       Difficulty:  Unknown
        Blocking:                      |       Blocked By:
                                       |  Related Tickets:
---------------------------------------+-----------------------------------

Comment (by monoidal):

 Here's a test case with no external dependencies, obtained from singletons
 and th-desugar; crashes 7.8.2 and HEAD. Put two files

 CustomStar.hs

 {{{
 {-# LANGUAGE TypeFamilies, KindSignatures, TemplateHaskell #-}

 module CustomStar ( singletonStar ) where

 import Language.Haskell.TH
 import Language.Haskell.TH.Syntax ( Quasi(..) )

 data family Sing a

 singFamilyName :: Name
 singFamilyName = ''Sing

 singletonStar :: Quasi q => q [Dec]
 singletonStar = do
   aName <- qNewName "z"
   return $ [DataInstD [] singFamilyName [SigT (VarT aName) StarT] [] []]
 }}}

 Star.hs

 {{{
 {-# LANGUAGE CPP, TemplateHaskell, TypeFamilies #-}

 module Star where

 import CustomStar

 #ifdef ERR
 import Star
 #endif

 $(singletonStar)
 }}}

 and execute

 {{{
 rm -f *.dyn_hi *.dyn_o *.hi *.o
 ghc CustomStar.hs
 ghc -c Star.hs
 ghc -c Star.hs -DERR
 }}}

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9032#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list