#5230: Segfault in cgrun064
----------------------------------+-----------------------------------------
Reporter: daniel.is.fischer | Owner: tibbe
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 7.1 | Keywords:
Testcase: | Blockedby:
Os: Linux | Blocking:
Architecture: x86 | Failure: None/Unknown
----------------------------------+-----------------------------------------
Comment(by daniel.is.fischer):
freezeArray is at least one cause for the segfaults. With the simple
example
{{{
{-# LANGUAGE MagicHash, UnboxedTuples #-}
module Try where
import GHC.Base
import GHC.ST
list :: [Int]
list = toList ar 5
where
ar = runST $ do
src <- newArray 16 3
freezeArray src 4 10
data Array a = Array { unArray :: Array# a }
data MArray s a = MArray { unMArray :: MutableArray# s a }
newArray :: Int -> a -> ST s (MArray s a)
newArray (I# n#) a = ST $ \s# -> case newArray# n# a s# of
(# s2#, marr# #) -> (# s2#, MArray marr# #)
indexArray :: Array a -> Int -> a
indexArray arr (I# i#) = case indexArray# (unArray arr) i# of
(# a #) -> a
writeArray :: MArray s a -> Int -> a -> ST s ()
writeArray marr (I# i#) a = ST $ \ s# ->
case writeArray# (unMArray marr) i# a s# of
s2# -> (# s2#, () #)
freezeArray :: MArray s a -> Int -> Int -> ST s (Array a)
freezeArray src (I# six#) (I# n#) = ST $ \ s# ->
case unsafeFreezeArray# (unMArray src) s# of
(# s2#, arr# #) -> (# s2#, Array arr# #)
-- case freezeArray# (unMArray src) six# n# s# of
-- (# s2#, arr# #) -> (# s2#, Array arr# #)
toList :: Array a -> Int -> [a]
toList arr n = go 0
where
go i | i >= n = []
| otherwise = indexArray arr i : go (i+1)
}}}
it works. Using freezeArray# instead, it segfaults. But it also segfaults
on copying when not using freezeArray# for freezing, so it's not the only
culprit.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5230#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs