#2412: Interaction between type synonyms and .hs-boot causes panic 
"tcIfaceGlobal
(local): not found"
-------------------------------+--------------------------------------------
    Reporter:  batterseapower  |       Owner:          
        Type:  bug             |      Status:  new     
    Priority:  normal          |   Component:  Compiler
     Version:  6.9             |    Severity:  normal  
    Keywords:                  |    Testcase:          
Architecture:  Unknown         |          Os:  Unknown 
-------------------------------+--------------------------------------------
 To reproduce, create the files:

 Main.hs:
 {{{
 module Main ( main, Baz ) where

 import Foo ( Bar )

 type Spqr = Bar
 data Baz = Baz Spqr

 main = putStrLn "Hello"
 }}}

 Main.hs-boot:
 {{{
 module Main where

 data Baz
 }}}

 Foo.hs:
 {{{
 module Foo where

 import {-# SOURCE #-} Main ( Baz )

 type Bar = Baz
 }}}

 Then run this command sequence:
 {{{
 $ ghc Main.hs-boot
 ...
 $ ghc Foo.hs
 ...
 $ ghc Main.hs
 ghc-6.8.2: panic! (the 'impossible' happened)
   (GHC version 6.8.2 for i386-apple-darwin):
         tcIfaceGlobal (local): not found:
     main:Main.Baz{tc r2T}
     []

 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
 }}}

 Note the problem does not seem to manifest itself outside of one-shot
 mode.

 The full trace is:
 {{{
 $ ghc Main.hs -ddump-if-trace -ddump-tc-trace
 FYI: cannot read old interface file:
     Main.hi: openBinaryFile: does not exist (No such file or directory)
 Considering whether to load base:Prelude
 Reading interface for base:Prelude; reason: Prelude is directly imported
 readIFace /usr/local/lib/ghc-6.8.2/lib/base-3.0.1.0/Prelude.hi
 updating EPS_
 Considering whether to load main:Foo
 Reading interface for main:Foo; reason: Foo is directly imported
 readIFace Foo.hi
 updating EPS_
 updating EPS_
 Loading orphan modules: base:GHC.Base
 Considering whether to load base:GHC.Base {- SYSTEM -}
 Reading interface for base:GHC.Base;
     reason: base:GHC.Base is a orphan-instance module
 readIFace /usr/local/lib/ghc-6.8.2/lib/base-3.0.1.0/GHC/Base.hi
 updating EPS_
 loadHiBootInterface main:Main
 Reading [boot] interface for main:Main;
     reason: Need the hi-boot interface for main:Main to compare against
 the Real Thing
 readIFace Main.hi-boot
 Finished typechecking interface for main:MainStarting fork { Declaration
 for Baz
 Loading decl for Main.Baz
 updating EPS_
 tcIfaceDecl4 Main.Baz
 } ending fork Declaration for Baz

 Type envt: [(r2T, Type constructor `Main.Baz')]
 Main.hs:1:0: Tc2
 Main.hs:1:0: tcTyAndCl Main
 Main.hs:1:0:
     kcd1 Spqr [[]] [[]]
     In the type synonym declaration for `Spqr'
 Main.hs:5:12:
     lk1 Bar
     In the type synonym declaration for `Spqr'
 Main.hs:5:12:Starting fork { Declaration for Bar
 Loading decl for Foo.Bar
 updating EPS_
 ghc-6.8.2: panic! (the 'impossible' happened)
   (GHC version 6.8.2 for i386-apple-darwin):
         tcIfaceGlobal (local): not found:
     main:Main.Baz{tc r2T}
     []

 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
 }}}

 This happens because when typechecking the type synonym Main.Spqr, kcTyVar
 calls tcLookup. This causes GHC to pull on the declaration for Foo.Bar.
 However, this declaration makes use of Main.Baz via a SOURCE import and we
 haven't yet got around to type checking Main.Baz!

 Hence tcIfaceGlobal dies, unable to find Baz in the type environment.

 Note that reversing the order of the declarations of Main.Baz and
 Main.Spqr doesn't seem to make a difference. I think this is because Baz
 in turn uses Spqr.

 I only have limited knowledge of the type checker, but I think a possible
 fix to this would be to type check the right hand sides of type synonym
 declarations lazily so we put Main.Baz into the environment before we go
 off exploring Foo.Bar. We seem to use a trick to deal with a similar type
 checking interface data constructors?

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