[GHC] #8001: Coercion causes "impossible" error

GHC ghc-devs at haskell.org
Fri Jun 21 06:23:07 CEST 2013


#8001: Coercion causes "impossible" error
-------------------------------+--------------------------------------------
Reporter:  gridaphobe          |          Owner:                
    Type:  bug                 |         Status:  new           
Priority:  normal              |      Component:  Compiler      
 Version:  7.6.3               |       Keywords:                
      Os:  Linux               |   Architecture:  x86_64 (amd64)
 Failure:  Compile-time crash  |      Blockedby:                
Blocking:                      |        Related:                
-------------------------------+--------------------------------------------
 The following, heavily-redacted version of a function in `text` is causing
 GHC to die after reporting that the impossible happened.

 {{{
 module Encoding where

 import Data.ByteString as B
 import Data.ByteString.Internal as B
 import Data.Text.Internal (Text(..), safe, textP)
 import Data.Word (Word8)
 import Foreign.C.Types (CSize)
 import Foreign.ForeignPtr (withForeignPtr, ForeignPtr)
 import Foreign.Ptr (Ptr, minusPtr, plusPtr)


 -- | Encode text using UTF-8 encoding.
 encodeUtf8 :: Text -> ByteString
 encodeUtf8 (Text arr off len) = inlinePerformIO $ do
   let size0 = max len 4
   mallocByteString size0 >>= start size0 off 0
  where
 --  start :: Int -> Int -> Int -> ForeignPtr Word8 -> IO ByteString
   start size n0 m0 fp = withForeignPtr fp $ go n0 m0
    where
       offLen = off + len
       go n m ptr
         | n == offLen = return (PS fp 0 m)
         | otherwise = do
             let ensure k act
                   | size-m >= k = act
                   | otherwise = do
                       let newSize = size
                       fp' <- mallocByteString newSize
                       start newSize n m fp'
                 {-# INLINE ensure #-}
             ensure 4 $ return $ PS fp 0 m
 }}}


 {{{
 $ ghc -fext-core Encoding.hs
 [1 of 1] Compiling Encoding ( Encoding.hs, Encoding.o )
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.6.3 for x86_64-unknown-linux):
         make_exp (App _ (Coercion _))

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

 Note that it only happens when I try to make GHC output the Core, it will
 happily compile otherwise. The crash can also be prevented by uncommenting
 the type-annotation or removing the inline-annotation.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/8001>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler



More information about the ghc-tickets mailing list