Yes, global IORefs = Bad.
But anyone know what might be happening here? Basically, we want to bracket
setting/unsetting an IORef. But reading the IORef (also with unsafePerformIO) has different behavior when inlining the definition of bracket
:
import Data.IORef
import Control.Exception
import System.IO.Unsafe
{-# NOINLINE isSetRef #-}
isSetRef :: IORef Bool
isSetRef = unsafePerformIO $ newIORef False
setMessage :: IO ()
setMessage =
writeIORef isSetRef True
unsetMessage :: IO ()
unsetMessage =
writeIORef isSetRef False
{-# INLINE message #-}
message :: String
message =
unsafePerformIO $
readIORef isSetRef >>= \case
True -> pure "SET"
False -> pure "UNSET"
main :: IO ()
main = do
let before = setMessage
let after () = unsetMessage
let thing () = print message
-- (1)
let test1 = do
bracket before after thing
-- (2)
let test2 = do
mask $ \restore -> do
a <- before
r <- restore (thing a) `onException` after a
_ <- after a
return r
-- (3)
let test3 = do
before
thing ()
after ()
{- ******************************************************************************** -}
putStrLn "Should print 'SET':"
test1
{- ******************************************************************************** -}
putStrLn "Should print 'UNSET':"
print message
With test1
, it shows SET/SET, but test2
and test3
show the correct SET/UNSET. I’m not sure why test1 and test2 have different behavior. Any ideas?