[GHC] #8114: GHC panic when building `thyme`

GHC ghc-devs at haskell.org
Mon Aug 5 16:32:19 CEST 2013


#8114: GHC panic when building `thyme`
---------------------------------------+----------------------------------
        Reporter:  Ptharien's Flame    |            Owner:
            Type:  bug                 |           Status:  new
        Priority:  normal              |        Milestone:
       Component:  Compiler            |          Version:  7.6.3
      Resolution:                      |         Keywords:
Operating System:  MacOS X             |     Architecture:  x86_64 (amd64)
 Type of failure:  Compile-time crash  |       Difficulty:  Unknown
       Test Case:                      |       Blocked By:
        Blocking:                      |  Related Tickets:
---------------------------------------+----------------------------------

Comment (by monoidal):

 As far as I can tell, the origin of the STG Lint error is Data.Text.Array
 in the text package.

 Here's the crucial part of that module. To reproduce, save this code as
 Array.hs and compile with `ghc -dstg-lint Array`. This gives a Lint error
 in 7.6.3 and HEAD.

 {{{
 {-# LANGUAGE MagicHash, RecordWildCards, UnboxedTuples #-}
 module Array where

 import GHC.Base (ByteArray#, MutableByteArray#, unsafeCoerce#)
 import GHC.ST (ST(..), runST)

 data Array = Array {
       aBA :: ByteArray#
     }

 data MArray s = MArray {
       maBA :: MutableByteArray# s
     }

 unsafeFreeze :: MArray s -> ST s Array
 unsafeFreeze MArray{..} = ST $ \s# ->
                           (# s#, Array (unsafeCoerce# maBA) #)
 }}}

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




More information about the ghc-tickets mailing list