Panic with self-import
A test in the singletons
package leads to a panic when run:
ghc: panic! (the 'impossible' happened)
(GHC version 7.8.2 for x86_64-unknown-linux):
tcIfaceGlobal (local): not found:
singletons-1.0:Singletons.Star.TFCo:R:DemoteRep*KProxy{tc r0}
[]
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
Edit: see ticket:9032#comment:83149 for a testcase.
- Show closed items
Relates to
Activity
-
Newest first Oldest first
-
Show all activity Show comments only Show history only
- Jan Stolarek mentioned in issue #1012 (closed)
mentioned in issue #1012 (closed)
- Jan Stolarek changed weight to 5
changed weight to 5
- Jan Stolarek added Tbug Trac import labels
added Tbug Trac import labels
- Developer
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, TemplateHaskell #-} module CustomStar ( singletonStar ) where import Language.Haskell.TH data family Sing a singFamilyName :: Name singFamilyName = ''Sing singletonStar :: Q [Dec] singletonStar = do aName <- newName "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
- Author
Trac metadata
Trac field Value Related → #1012 (closed) - Thomas Miedema changed the description
changed the description
- Thomas Miedema changed milestone to %7.10.1
changed milestone to %7.10.1
Still present in 7.9. I have cleaned up the description a bit.
Trac metadata
Trac field Value Component Compiler → Template Haskell - Thomas Miedema added TemplateHaskell label
added TemplateHaskell label
- Simon Peyton Jones changed weight to 10
changed weight to 10
- Developer
I think a module should simply never import itself. I propose to make this an error. Does anyone object?
I'm increasing the priority to highest to make sure that we attend to this, not because it's terribly important. It's very easy to implement if we agree that it should be illegal.
Simon
Trac metadata
Trac field Value Priority normal → highest - Developer
It's already an error (
Module imports form a cycle: module 'X' imports itself
), but in this case the self-import somehow gives a panic. - Developer
Replying to [ticket:9032#comment:92593 monoidal]:
It's already an error (
Module imports form a cycle: module 'X' imports itself
), but in this case the self-import somehow gives a panic.Good point. So it's already an error; albeit one that is only reported with
--make
. We should get a decent error in one-shot mode too.Simon
- Simon Peyton Jones mentioned in commit edd233ac
mentioned in commit edd233ac
- Simon Peyton Jones closed
closed
- Developer
Trac metadata
Trac field Value Resolution Unresolved → ResolvedFixed Test case → rename/should_fail/T9032 - Herbert Valerio Riedel reopened
reopened
- Herbert Valerio Riedel added 1 deleted label
added 1 deleted label
- Herbert Valerio Riedel closed
closed
- Herbert Valerio Riedel removed 1 deleted label
removed 1 deleted label
- Maintainer
has been cherry-picked into ghc-7.10 branch
- Herbert Valerio Riedel mentioned in issue #9997 (closed)
mentioned in issue #9997 (closed)
- trac-import added compiler crash label
added compiler crash label
- Ben Gamari added Phighest label
added Phighest label