[Haskell-cafe] Bad interaction of inlinePerformIO and mutable vectors

Bertram Felgenhauer bertram.felgenhauer at googlemail.com
Fri Aug 1 21:30:29 UTC 2014


Carter Schonwald wrote:
> I tried compiling your original codes with normal unsafePerformIO on ghc
> 7.8.3, and I get the "B" result at -O0 and the "A" result at O1 and O2
> 
> {-# LANGUAGE BangPatterns,  UnboxedTuples,MagicHash #-}
> 
> import Data.ByteString.Internal (inlinePerformIO)
> import qualified Data.Vector as V
> import qualified Data.Vector.Mutable as VM
> 
> import System.IO.Unsafe
> 
> main :: IO ()
> main = do
>     vm <- VM.new 1
>     VM.write vm 0 'A'
>     !b<- return $! 'B'
>     let !x = unsafePerformIO $! VM.write vm 0 b
>     x `seq` (V.freeze vm >>= print)

Note that the compiler sees through  !b<- return $! 'B', so it does
not introduce a data dependency. Looking at the core, x is getting
evaluated (writing 'B' to the array) before the writeArray# call
resulting from VM.write vm 0 'A'.

I'm not 100% sure that the compiler is within its rights for reordering
code here; after all, writeArray# has a side effect, which will not
be performed in the hypothetical case that evaluation of x diverges.
But at least reordering effects is far less surprising than effects
disappearing completely.

[Michael Snoyman:]
> > One last question on the GHC front, however. It *does* seem like there's
> > still a bug in GHC here, since presumably case-ing on an unboxed tuple
> > should force evaluation of both of its values.

No, it should not. If it did,

  main = return undefined >> print "Foo"

would fail.

Cheers,

Bertram


More information about the Haskell-Cafe mailing list