#7165: "match_co bailing out" messages and compiler crash
--------------------------------+-------------------------------------------
 Reporter:  alang               |          Owner:                
     Type:  bug                 |         Status:  new           
 Priority:  normal              |      Component:  Compiler      
  Version:  7.7                 |       Keywords:                
       Os:  Linux               |   Architecture:  x86_64 (amd64)
  Failure:  Compile-time crash  |       Testcase:                
Blockedby:                      |       Blocking:                
  Related:                      |  
--------------------------------+-------------------------------------------
 {{{
 $ cat > Blah.hs
 {-# LANGUAGE GADTs #-}

 module Blah where

 blah :: (dd ~ (Double, Double)) => dd -> dd
 blah (ax, bx)
     | ax < bx = blah (bx, ax)
     | otherwise = (0,0)

 $ cat > Meh.hs
 module Meh where

 import Blah

 meh = blah (0,0)

 }}}

 If we compile with -O2, in 2 separate calls to ghc, we get:

 {{{
 $ ghc -O2 Blah.hs
 [1 of 1] Compiling Blah             ( Blah.hs, Blah.o )
 match_co baling out
     <(ghc-prim:GHC.Types.Double{(w) tc 3u},
       ghc-prim:GHC.Types.Double{(w) tc 3u})>
 match_co baling out
     <(ghc-prim:GHC.Types.Double{(w) tc 3u},
       ghc-prim:GHC.Types.Double{(w) tc 3u})>
 match_co baling out
     <(ghc-prim:GHC.Types.Double{(w) tc 3u},
       ghc-prim:GHC.Types.Double{(w) tc 3u})>
 match_co baling out
     <(ghc-prim:GHC.Types.Double{(w) tc 3u},
       ghc-prim:GHC.Types.Double{(w) tc 3u})>
 match_co baling out
     <(ghc-prim:GHC.Types.Double{(w) tc 3u},
       ghc-prim:GHC.Types.Double{(w) tc 3u})>
 match_co baling out
     <(ghc-prim:GHC.Types.Double{(w) tc 3u},
       ghc-prim:GHC.Types.Double{(w) tc 3u})>

 $ ghc -O2 Meh.hs
 [2 of 2] Compiling Meh              ( Meh.hs, Meh.o )
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.4.2 for x86_64-unknown-linux):
         tcIfaceType
     Refl
         (ghc-prim:GHC.Types.Double{(w) tc 3u},
          ghc-prim:GHC.Types.Double{(w) tc 3u})

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

 }}}

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