[GHC] #7715: threadDelay causes segfault on Mac if compiled by 32bit GHC

GHC cvs-ghc at haskell.org
Sat Apr 27 07:31:26 CEST 2013


#7715: threadDelay causes segfault on Mac if compiled by 32bit GHC
----------------------------+-----------------------------------------------
  Reporter:  kazu-yamamoto  |          Owner:         
      Type:  bug            |         Status:  new    
  Priority:  high           |      Milestone:  7.8.1  
 Component:  Compiler       |        Version:  7.7    
Resolution:                 |       Keywords:         
        Os:  MacOS X        |   Architecture:  x86    
   Failure:  None/Unknown   |     Difficulty:  Unknown
  Testcase:                 |      Blockedby:         
  Blocking:                 |        Related:         
----------------------------+-----------------------------------------------

Comment(by kazu-yamamoto):

 Since I suspect the atMost function, I exported GHC.Event.* by editing
 libraries/base/base.cabal and built the GHC.

 With this GHC head on 32bit Mac, the following code sometime causes
 seqfault/bus error if compiled with -threaded:

 {{{
 module Main where

 main :: IO ()
 main = do
     s <- newSource
     ents <- replicateM 100 (entry s)
     let q = fold ents
     print $ Q.atMost 1.5 q

 fold :: [(Q.Key, Q.Prio)] -> Q.PSQ ()
 fold [] = Q.empty
 fold ((u,r):xs) = Q.insert u r () $ fold xs

 entry :: UniqueSource -> IO (Q.Key, Q.Prio)
 entry s = do
     u <- newUnique s
     r <- randomIO
     return (u,r)
 }}}

 Now I believe that this test code makes debug much easier.

 Note that if I copy PSQ.hs and Unique.hs, modify its modules name, and
 compile the Main.hs file with them by GHC head on 32bit Mac, it does not
 cause seqfault/bus error.

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



More information about the ghc-tickets mailing list