Is Safe Haskell intended to allow segfaults?

Edward Z. Yang ezyang at mit.edu
Mon Aug 8 18:05:59 UTC 2016


Hello Ryan,

The guarantee that Safe Haskell gives with regards to IO is a little
subtle and is mentioned in Section 3.1 of the paper, and detailed
in Section 5.1. Essentially, to use Safe Haskell, you are responsible
for defining the type at which untrusted code is to be called.
Using an untrusted value at type IO a in main imposes no safety
restrictions by design--it's up to the user of Safe Haskell to
decide what kind of security properties it needs out of user code.

Edward

Excerpts from Ryan Newton's message of 2016-08-08 13:27:16 -0400:
> 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


More information about the ghc-devs mailing list