[Haskell-cafe] Weird defaulting on newEmptyTMVar

Viktor Dukhovni ietf-dane at dukhovni.org
Tue Feb 12 01:42:28 UTC 2019


> On Feb 10, 2019, at 5:07 AM, Viktor Dukhovni <ietf-dane at dukhovni.org> wrote:
> 
> The issues become a bit more clear if we replace the "<-" with
> unsafePerformIO:
> 
>    ...> :m + System.IO.Unsafe
>    ...> let v = unsafePerformIO newEmptyMVar
>    ...> :t v
>    v :: MVar a
>    ...> putMVar v (1 :: Int)
>    ...> let x = unsafePerformIO (readMVar v)
>    ...> :t x
>    x :: a

Taking it further, one quickly runs into real trouble:

  --- foo.hs
  {-# LANGUAGE TypeApplications #-}
  module Main (main) where

  import Control.Concurrent.MVar
  import System.IO.Unsafe

  main :: IO ()
  main = do
    let v = unsafePerformIO newEmptyMVar
    putMVar v (42 :: Int)
    let x = unsafePerformIO (readMVar v)
    print $ x + 0             -- OK
    print $ x + 3.0           -- Weird
    print $ "oops" ++ x       -- Bad
    readMVar @Int x >>= print -- A bridge too far
  ---

  $ ghc foo.hs
  [1 of 1] Compiling Main             ( foo.hs, foo.o )
  Linking foo ...
  $ ./foo
  42
  3.0
  "oops"
  Segmentation fault (core dumped)

So it is interesting to note that "unsafePerformIO" combined with
polymorphic MVars, is sufficient to completely escape not only
protection from race conditions, but also all type safety.
Unsafe code that manages to create, not an "MVar GHC.Types.Any",
but rather an "MVar a", opens a Pandora's box of trouble.

-- 
	Viktor.


More information about the Haskell-Cafe mailing list