Thanks for the examples showcasing how things can go wrong. I had not even really considered something like the second case. It's weird that STM discards exception handlers, but the idea of ever trying to smuggle something like that into an STM transaction seems insane. Interestingly, it appears that this deadlock can be induced without unsafePerformIO, using the mildly-less-awful unsafeIOToSTM from GHC.Conc. The documentation for it backs up your second example.

On Sun, Nov 12, 2017 at 2:41 PM, Bertram Felgenhauer via Libraries <libraries@haskell.org> wrote:
Andrew Martin wrote:
> In the stm package, the docs for atomically read:
>
> > You cannot use 'atomically' inside an 'unsafePerformIO' or
> 'unsafeInterleaveIO'. Any attempt to do so will result in a runtime error.
>  (Reason: allowing this would effectively allow a transaction inside a
> transaction, depending on exactly when the thunk is evaluated.)
>
> This doesn't seem to be true. The following program runs fine:
>
>     import Control.Monad.STM
>     import Control.Concurrent.STM.TVar
>     import System.IO.Unsafe
>
>     main :: IO ()
>     main = do
>       v <- atomically $ newTVar (7 :: Int)
>       print $ unsafePerformIO $ atomically $ do
>         readTVar v
>
> I suspect that the runtime only gives you an error if you actually create a
> nested transaction. Is my understanding correct?

Yes, that is correct. But you should not conclude from this that using
`unsafePerformIO`, in particular in connection with STM, is safe in any
way. Consider the following program, especially the `main2` function:

  import Control.Monad.STM
  import Control.Concurrent.STM.TVar
  import System.IO.Unsafe
  import Control.Concurrent.MVar
  import Control.Concurrent
  import Control.Monad
  import System.Mem

  -- This is not very scary but bad news for compositionality:
  -- using STM inside `unsafePerformIO`, used inside `atomically`,
  -- causes an error.
  --
  -- output:
  -- foo: Control.Concurrent.STM.atomically was nested

  main1 = do
      let val = unsafePerformIO (atomically (return (0 :: Int)))
      atomically (return $! val) >>= print

  -- This one is much worse:
  --
  -- There is no use of STM in the unsafePerformIO-ed action, but the
  -- program ends up taking a resource (an MVar here) without releasing
  -- it; it turns out that when retrying an STM action that is in the
  -- middle of an unsafePerformIO computation, the IO action is stopped
  -- without raising an exception!
  --
  -- output (tested with ghc 7.10.2, 8.0.2 and 8.2.1, but I see no way
  --   to ensuring that it always works):
  -- foo: thread blocked indefinitely in an MVar operation

  main2 = do
      var <- newMVar ()
      tvar <- atomically $ newTVar (0 :: Int)
      let val v = unsafePerformIO $
          withMVar var $ \_ -> threadDelay 10000 >> return v
      replicateM_ 32 $ do
          forkIO $ atomically (readTVar tvar >>= (writeTVar tvar $!) . val . succ)
      threadDelay 100000
      performGC
      takeMVar var >>= print

  main = main2

Cheers,

Bertram
_______________________________________________
Libraries mailing list
Libraries@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries



--
-Andrew Thaddeus Martin