Is Safe Haskell intended to allow segfaults?

Ryan Newton rrnewton at gmail.com
Mon Aug 8 17:27:16 UTC 2016


We're trying to spend some cycles pushing on Safe Haskell within the
stackage packages.  (It's looking like a slog.)

But we're running up against some basic questions regarding the core
packages and Safe Haskell guarantees.  The manual currently says:
<https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/safe_haskell.html#safe-language>


*Functions in the IO monad are still allowed and behave as usual. *
As usual?  So it is ok to segfault GHC?  Elsewhere it says "in the safe
language you can trust the types", and I'd always assumed that meant Safe
Haskell is a type safe language, even in the IO fragment.

Was there an explicit decision to allow segfaults and memory corruption?
This can happen not just with FFI calls but with uses of Ptrs within
Haskell, for example the following:


```

{-# LANGUAGE Safe #-}

module Main where

import Foreign.Marshal.Alloc

import Foreign.Storable

import Foreign.Ptr

import System.Random


fn :: Ptr Int -> IO ()

fn p = do

  -- This is kosher:

  poke p 3

  print =<< peek p

  -- This should crash the system:

  ix <- randomIO

  pokeElemOff p ix 0xcc



main = alloca fn

```


  -Ryan
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20160808/86c0bb87/attachment.html>


More information about the ghc-devs mailing list