#5071: GHCi crashes on large alloca/allocaBytes requests
---------------------------------+------------------------------------------
Reporter: guest | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 7.0.3 | Keywords:
Testcase: | Blockedby:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: None/Unknown
---------------------------------+------------------------------------------
GHCi, and ghc, seems to exit (crash?) on certain types of memory
allocation exceptions.
The FFI addendum says that the allocation functions should be able to
return null:
http://www.cse.unsw.edu.au/~chak/haskell/ffi/ffi/ffise5.html#x8-230005
Section 5.8 says this:
> If any of the allocation functions fails, a value of Ptr.nullPtr is
produced. If free or reallocBytes is applied to a memory area that has
been allocated with alloca or allocaBytes, the behaviour is undefined. Any
further access to memory areas allocated with alloca or allocaBytes, after
the computation that was passed to the allocation function has terminated,
leads to undefined behaviour. Any further access to the memory area
referenced by a pointer passed to realloc, reallocBytes, or free entails
undefined behaviour.
In practice, code examples and documentation appear to rely on `alloca`
'''NOT''' returning a `nullPtr`:
* http://en.wikibooks.org/wiki/Haskell/FFI
* http://www.haskell.org/haskellwiki/HSFFIG/Examples
* http://book.realworldhaskell.org/read/interfacing-with-c-the-ffi.html
I reported this on the libraries list, and offered a documentation tweak,
and I was asked to create a ticket:
http://www.haskell.org/pipermail/libraries/2011-March/016117.html
That email has details about the testing I did at the time to see the
crashing behavior in ghci. I was using ghc 7.0.2 on 64bit windows, but
this also appears to affect 7.0.3 on linux. It's likely that other
versions of ghc are affected.
My recommendation would be to make the exception thrown by `alloca`
catchable. Possibly offering an alternative to `alloca`, say `alloca'`,
that can produce a `nullPtr` instead of using exceptions. I would advice
against changing the existing `alloca` function to produce `nullPtr` as
that could make a lot of existing code unsafe.
For example, it would be nice if the following printed "exception",
instead of exiting:
{{{
$ ulimit -d 100000 -m 1000000 -v 100000
$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 7.0.3
$ ./Alloca
Alloca: out of memory (requested 2148532224 bytes)
$ cat Alloca.hs
import Foreign
import Foreign.Marshal
import Foreign.Marshal.Alloc
import GHC.Exception
import System.IO.Error
main :: IO ()
main = do
(allocaBytes maxBound compare)
`catch` (\_ -> print "exception")
where
compare p = print ((nullPtr :: Ptr Int) == p)
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5071>
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