tl;dr: Thanks to Felipe's comments, I think I've found the issue, which is in the primitive package, together with a possible GHC bug. Following is my blow-by-blow walk through on this issue.
OK, a little more information, and a simpler repro. This is reproducible entirely with the primitive package:
import Control.Monad.Primitive
import Data.Primitive.Array
main :: IO ()
main = do
arr <- newArray 1 'A'
let unit = unsafeInlineIO $ writeArray arr 0 'B'
readArray arr 0 >>= print
return $! unit
readArray arr 0 >>= print
However, it's not reproducible with the underlying primops:
{-# LANGUAGE MagicHash, UnboxedTuples #-}
import
GHC.IO (IO (..))
import GHC.Prim
writeB :: MutableArray# RealWorld Char -> ()
writeB arr# =
case writeArray# arr# 0# 'B' realWorld# of
_ -> ()
read0 :: MutableArray# RealWorld Char -> IO Char
read0 arr# = IO $ \s0# -> readArray# arr# 0# s0#
test :: IO ((), IO Char)
test = IO $ \s0# ->
case newArray# 1# 'A' s0# of
(# s1#, arr# #) ->
(# s1#, (writeB arr#, read0 arr#) #)
main :: IO ()
main = do
(unit, getter) <- test
getter >>= print
return $! unit
getter >>= print
This behavior only occurs with optimizations turned on (unsurprising, given Felipe's find about the simplifier pass). Now, if I define a new operation: