[GHC] #8834: 64-bit windows cabal.exe segfaults in GC
GHC
ghc-devs at haskell.org
Thu Mar 13 14:41:38 UTC 2014
#8834: 64-bit windows cabal.exe segfaults in GC
----------------------------------+----------------------------------
Reporter: awson | Owner:
Type: bug | Status: patch
Priority: highest | Milestone: 7.8.1
Component: Compiler | Version: 7.8.1-rc2
Resolution: | Keywords:
Operating System: Windows | Architecture: x86_64 (amd64)
Type of failure: Runtime crash | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
----------------------------------+----------------------------------
Comment (by thoughtpolice):
I can confirm Kyril's example above works properly and produces the
segfault as well. Here's my updated version:
{{{#!haskell
module Main (main) where
import Prelude hiding (null, take, drop)
import Data.ByteString hiding (elemIndex)
import qualified Data.ByteString as B
import Data.ByteString.Internal
import Data.Word
import Foreign
elemIndex1 :: Word8 -> ByteString -> Maybe Int
elemIndex1 c (PS x s l) = inlinePerformIO $ withForeignPtr x $ \p -> do
let p' = p `plusPtr` s
q <- memchr p' c (fromIntegral l)
return $! if q == nullPtr then Nothing else Just $! q `minusPtr` p'
{-# INLINE elemIndex1 #-}
elemIndex :: Char -> ByteString -> Maybe Int
elemIndex = elemIndex1 . c2w
{-# INLINE elemIndex #-}
lines1 :: ByteString -> [ByteString]
lines1 ps
| null ps = []
| otherwise = case search ps of
Nothing -> [ps]
Just n -> take n ps : lines1 (drop (n+1) ps)
where search = elemIndex '\n'
main = do
f <- B.readFile "00-index.cache"
print (Prelude.length $ lines1 f)
}}}
You can grab the `00-index.cache` file from
`/c/Users/$USER/AppData/Roaming/cabal/packages/hackage.haskell.org/00-index.cache`
I'm investigating reverting the PAP patch (still building).
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8834#comment:29>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list