Bad interaction of inlinePerformIO and mutable vectors

I'm trying to understand why some code isn't behaving as I'd expect, and to determine whether it's a bug or not (and where that bug might be). Here's the simplest version of the code: import Data.ByteString.Internal (inlinePerformIO) import qualified Data.Vector as V import qualified Data.Vector.Mutable as VM main :: IO () main = do vm <- VM.new 1 VM.write vm 0 'A' let x = inlinePerformIO $ VM.write vm 0 'B' x `seq` (V.freeze vm >>= print) A more complete example is available on lpaste[1]. The problem is that I would expect the output to be "B", but in fact "A" is still printed. From the longer paste that I linked to, you can see that: * When using unsafePerformIO and unsafeDupablePerformIO, the semantics work as I would have expected: "B" is printed after forcing evaluation of the result. * If I add a `VM.read vm 0` call after the write, it also works. * Using IORef, the behavior is also as I would have expected: as soon as the result is evaluated, the reference is updated. I'm testing on GHC 7.8.3, Ubuntu 64-bit, and compiling with -O2. I'm curious if anyone has an idea as to why there is this difference in behavior. Michael [1] http://lpaste.net/108483

Hey, Michael! I'm not going to give you the answer to your question, just a new bit of information. If you check the core generated from -O2 you'll see that this is what the IORef version of "inlinePerformIO" looks like: -- prints "inlinePerformIO" case Handle.Text.hPutStr2 Handle.FD.stdout lvl2_r5GX True ipv28_X3s6 of _ [Occ=Dead] { (# ipv30_X3vu, ipv31_X3sc #) -> -- reads current value case readMutVar# @ RealWorld @ Char ipv3_a3pa ipv30_X3vu of _ [Occ=Dead] { (# ipv32_X3uU, ipv33_X3uX #) -> -- prints current value case Handle.Text.hPutStr2 Handle.FD.stdout ($fShowChar_$cshow ipv33_X3uX) True ipv32_X3uU of _ [Occ=Dead] { (# ipv34_X3si, ipv35_X3sk #) -> -- sets new value case writeMutVar# @ RealWorld @ Char ipv3_a3pa lvl10_r5H5 realWorld# of _ [Occ=Dead] { __DEFAULT -> -- reads current value case readMutVar# @ RealWorld @ Char ipv3_a3pa ipv34_X3si of _ [Occ=Dead] { (# ipv36_X3v6, ipv37_X3v9 #) -> -- prints current value case Handle.Text.hPutStr2 Handle.FD.stdout ($fShowChar_$cshow ipv37_X3v9) True ipv36_X3v6 -- ... While this is what the Vector version of "inlinePerformIO" looks like: -- prints "inlinePerformIO" case Handle.Text.hPutStr2 Handle.FD.stdout lvl2_r5GX True ipv72_X3zS of _ [Occ=Dead] { (# ipv74_X3uq, ipv75_X3us #) -> -- prints current value case a_s32R ipv74_X3uq of _ [Occ=Dead] { (# ipv76_X3uu, ipv77_X3uw #) -> -- prints current value case a_s32R ipv76_X3uu of _ [Occ=Dead] { (# ipv78_X3v5, ipv79_X3v7 #) -> -- ... Ouch! Everything was optimized away :(. For reference, this is what the "inlinePerformIO + read" version looks like: -- prints "inlinePerformIO + read" case Handle.Text.hPutStr2 Handle.FD.stdout lvl1_r5GW True ipv78_X3v5 of _ [Occ=Dead] { (# ipv80_X3Bs, ipv81_X3vb #) -> -- prints current value case a_s32R ipv80_X3Bs of _ [Occ=Dead] { (# ipv82_X3vd, ipv83_X3vf #) -> -- sets new value then read it case readArray# @ (Control.Monad.Primitive.PrimState IO) @ Char ipv55_a2Ze 0 (writeArray# @ (Control.Monad.Primitive.PrimState IO) @ Char ipv55_a2Ze 0 lvl_r5GV (realWorld# `cast` ((State# (Sym Control.Monad.Primitive.TFCo:R:PrimStateIO[0]))_R :: State# RealWorld ~# State# (Control.Monad.Primitive.PrimState IO)))) of _ [Occ=Dead] { (# ipv84_s5yV, ipv85_s5yW #) -> -- prints current value a_s32R ipv82_X3vd Hmmmm... -- Felipe.

Checking a bit deeper using: $ ghc-core --no-cast --no-asm snoyberg.hs -O1 -ddump-simpl \ -dverbose-core2core -dcore-lint This is the last time we see the "inlinePerformIO" function call (before it being optimized away): lvl_s2R1 = \ (vm_a2gL [OS=ProbOneShot] :: Data.Vector.Mutable.MVector RealWorld Char) -> thenIO @ () @ () lvl_s2QY (let { a_s2QN :: State# RealWorld -> (# State# RealWorld, () #) a_s2QN = \ (eta_Xm [OS=OneShot] :: State# RealWorld) -> ((bindIO @ (Data.Vector.Vector Char) @ () (Data.Vector.unsafeFreeze @ IO @ Char Control.Monad.Primitive.$fPrimMonadIO (vm_a2gL `cast` ...)) lvl_s2QV) `cast` ...) eta_Xm } in thenIO @ () @ () (a_s2QN `cast` ...) (case $ @ (IO ()) @ () (Data.ByteString.Internal.inlinePerformIO @ ()) (Data.Vector.Mutable.write @ IO @ Char Control.Monad.Primitive.$fPrimMonadIO (vm_a2gL `cast` ...) lvl_s2QZ lvl_s2R0) of _ [Occ=Dead] { () -> a_s2QN `cast` ... })) lvl_s2QV is the action that prints the array contents. The above snippet prints the contents, writes the new value then prints the contents again. But then comes a simplifier phase which lead us to: ... of _ [Occ=Dead] { (# ipv_X3cp [OS=OneShot], ipv1_X3cr #) -> let { a_s2QN :: State# RealWorld -> (# State# RealWorld, () #) [LclId, Arity=1, Unf=Unf{Src=<vanilla>, TopLvl=False, Arity=1, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [0] 91 0}] a_s2QN = \ (eta_Xm [OS=OneShot] :: State# RealWorld) -> case unsafeFreezeArray# @ (Control.Monad.Primitive.PrimState IO) @ Char ipv1_a2NI (eta_Xm `cast` ...) of _ [Occ=Dead] { (# ipv_a2Oy [OS=OneShot], ipv1_a2Oz #) -> Handle.Text.hPutStr2 Handle.FD.stdout (Data.Vector.$fShowVector_$cshow @ Char $fShowChar (Data.Vector.Vector @ Char 0 1 ipv1_a2Oz)) True (ipv_a2Oy `cast` ...) } } in case a_s2QN ipv_X3cp of _ [Occ=Dead] { (# ipv_X3cv [OS=OneShot], ipv1_X3dt #) -> a_s2QN ipv_X3cv ... Note that a_s2QN has changed due to inlining but still performs the same action. However! ipv_X3cp is *not* the same as the big case with our inlinePerformIO, it's merely the resulting RealWorld from printing "inlinePerformIO"! This is the spot. Now I'm stuck, though. I have no idea why the simplifier did this. Cheers! -- Felipe.

Thanks for digging into this Felipe! That's certainly an interesting
result, though I similarly have no idea why that's what the simplifier is
doing.
On Thu, Jul 31, 2014 at 5:27 PM, Felipe Lessa
Checking a bit deeper using:
$ ghc-core --no-cast --no-asm snoyberg.hs -O1 -ddump-simpl \ -dverbose-core2core -dcore-lint
This is the last time we see the "inlinePerformIO" function call (before it being optimized away):
lvl_s2R1 = \ (vm_a2gL [OS=ProbOneShot] :: Data.Vector.Mutable.MVector RealWorld Char) -> thenIO @ () @ () lvl_s2QY (let { a_s2QN :: State# RealWorld -> (# State# RealWorld, () #)
a_s2QN = \ (eta_Xm [OS=OneShot] :: State# RealWorld) -> ((bindIO @ (Data.Vector.Vector Char) @ () (Data.Vector.unsafeFreeze @ IO @ Char Control.Monad.Primitive.$fPrimMonadIO (vm_a2gL `cast` ...)) lvl_s2QV) `cast` ...) eta_Xm } in thenIO @ () @ () (a_s2QN `cast` ...) (case $ @ (IO ()) @ () (Data.ByteString.Internal.inlinePerformIO @ ()) (Data.Vector.Mutable.write @ IO @ Char Control.Monad.Primitive.$fPrimMonadIO (vm_a2gL `cast` ...) lvl_s2QZ lvl_s2R0) of _ [Occ=Dead] { () -> a_s2QN `cast` ... }))
lvl_s2QV is the action that prints the array contents. The above snippet prints the contents, writes the new value then prints the contents again.
But then comes a simplifier phase which lead us to:
... of _ [Occ=Dead] { (# ipv_X3cp [OS=OneShot], ipv1_X3cr #) -> let { a_s2QN :: State# RealWorld -> (# State# RealWorld, () #) [LclId, Arity=1,
Unf=Unf{Src=<vanilla>, TopLvl=False, Arity=1, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [0] 91 0}] a_s2QN = \ (eta_Xm [OS=OneShot] :: State# RealWorld) -> case unsafeFreezeArray# @ (Control.Monad.Primitive.PrimState IO) @ Char ipv1_a2NI (eta_Xm `cast` ...) of _ [Occ=Dead] { (# ipv_a2Oy [OS=OneShot], ipv1_a2Oz #) -> Handle.Text.hPutStr2 Handle.FD.stdout (Data.Vector.$fShowVector_$cshow @ Char $fShowChar (Data.Vector.Vector @ Char 0 1 ipv1_a2Oz)) True (ipv_a2Oy `cast` ...) } } in case a_s2QN ipv_X3cp of _ [Occ=Dead] { (# ipv_X3cv [OS=OneShot], ipv1_X3dt #) -> a_s2QN ipv_X3cv ...
Note that a_s2QN has changed due to inlining but still performs the same action. However! ipv_X3cp is *not* the same as the big case with our inlinePerformIO, it's merely the resulting RealWorld from printing "inlinePerformIO"! This is the spot.
Now I'm stuck, though. I have no idea why the simplifier did this.
Cheers!
-- Felipe.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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: unsafeWriteArray :: MutableArray RealWorld a -> Int -> a -> () unsafeWriteArray (MutableArray arr#) (I# i#) x = case writeArray# arr# i# x realWorld# of _ -> () and then replace my unit above with: let unit = unsafeWriteArray arr 0 'B' it works as expected. Similarly, the following tweak fixes the example as well: arr@(MutableArray arr#) <- newArray 1 'A' let unit = case writeArray# arr# 0# 'B' realWorld# of _ -> () So it appears the bug is in writeArray, or more likely in primitive_. Sure enough, setting NOINLINE on primitive_ *does* resolve the issue. And looking at the definition of primitive_: primitive_ f = primitive (\s# -> (# f s#, () #)) this is starting to make sense. unsafeInlineIO is completely ignoring the resulting state value, as can be seen by its implementation: unsafeInlineIO m = case internal m realWorld# of (# _, r #) -> r Therefore `f s#` is never getting evaluated. However, if we force evaluation by switching to: primitive_ f = primitive (\s# -> case f s# of s'# -> (# s'#, () #)) seems to solve the problem. I think this is the right approach for now, and I've sent a pull request to primitive with this tweak[1]. 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. Indeed, after going through the above debugging, I can reproduce the issue using just primops: {-# LANGUAGE MagicHash, UnboxedTuples #-} import GHC.IO (IO (..)) import GHC.Prim writeB :: MutableArray# RealWorld Char -> IO () writeB arr# = IO $ \s0# -> (# writeArray# arr# 0# 'B' s0#, () #) inlineWriteB :: MutableArray# RealWorld Char -> () inlineWriteB arr# = case f realWorld# of (# _, x #) -> x where IO f = writeB arr# test :: IO Char test = IO $ \s0# -> case newArray# 1# 'A' s0# of (# s1#, arr# #) -> case seq# (inlineWriteB arr#) s1# of (# s2#, () #) -> readArray# arr# 0# s2# main :: IO () main = test >>= print I've filed this as a bug with GHC[2]. Michael [1] https://github.com/haskell/primitive/pull/11 [2] https://ghc.haskell.org/trac/ghc/ticket/9390

a) are you certain you're using inlinePerformIO correctly?
it was recently renamed to accursedUnutterablePerformIO
for good reason!
https://github.com/haskell/bytestring/blob/2530b1c28f15d0f320a84701bf507d565...
links to a few choice tickets from attempts to use it
https://github.com/haskell/bytestring/commit/71c4b438c675aa360c79d79acc9a491...
https://github.com/haskell/bytestring/commit/210c656390ae617d9ee3b8bcff5c88d...
https://ghc.haskell.org/trac/ghc/ticket/3486
https://ghc.haskell.org/trac/ghc/ticket/3487
https://ghc.haskell.org/trac/ghc/ticket/7270
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)
i don't think the issue has to do with inlinePerformIO (though it doesn't
help matters), because changing the optimization level impacts normal
unsafePerformIO too!
On Fri, Aug 1, 2014 at 1:00 AM, Michael Snoyman
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:
unsafeWriteArray :: MutableArray RealWorld a -> Int -> a -> () unsafeWriteArray (MutableArray arr#) (I# i#) x = case writeArray# arr# i# x realWorld# of _ -> ()
and then replace my unit above with:
let unit = unsafeWriteArray arr 0 'B'
it works as expected. Similarly, the following tweak fixes the example as well:
arr@(MutableArray arr#) <- newArray 1 'A' let unit = case writeArray# arr# 0# 'B' realWorld# of _ -> ()
So it appears the bug is in writeArray, or more likely in primitive_. Sure enough, setting NOINLINE on primitive_ *does* resolve the issue. And looking at the definition of primitive_:
primitive_ f = primitive (\s# -> (# f s#, () #))
this is starting to make sense. unsafeInlineIO is completely ignoring the resulting state value, as can be seen by its implementation:
unsafeInlineIO m = case internal m realWorld# of (# _, r #) -> r
Therefore `f s#` is never getting evaluated. However, if we force evaluation by switching to:
primitive_ f = primitive (\s# -> case f s# of s'# -> (# s'#, () #))
seems to solve the problem. I think this is the right approach for now, and I've sent a pull request to primitive with this tweak[1].
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. Indeed, after going through the above debugging, I can reproduce the issue using just primops:
{-# LANGUAGE MagicHash, UnboxedTuples #-} import GHC.IO (IO (..)) import GHC.Prim
writeB :: MutableArray# RealWorld Char -> IO () writeB arr# = IO $ \s0# -> (# writeArray# arr# 0# 'B' s0#, () #)
inlineWriteB :: MutableArray# RealWorld Char -> () inlineWriteB arr# = case f realWorld# of (# _, x #) -> x where IO f = writeB arr#
test :: IO Char test = IO $ \s0# -> case newArray# 1# 'A' s0# of (# s1#, arr# #) -> case seq# (inlineWriteB arr#) s1# of (# s2#, () #) -> readArray# arr# 0# s2#
main :: IO () main = test >>= print
I've filed this as a bug with GHC[2].
Michael
[1] https://github.com/haskell/primitive/pull/11 [2] https://ghc.haskell.org/trac/ghc/ticket/9390
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Fri, Aug 1, 2014 at 8:51 AM, Carter Schonwald wrote: a) are you certain you're using inlinePerformIO correctly?
it was recently renamed to accursedUnutterablePerformIO
for good reason! No, I'm not certain yet, my next task was to look into this further and be
certain that what I was doing was actually safe. I took this detour first,
and was planning on following up on the safety (or lack thereof) of
the-function-which-shall-not-be-named. The links you've provided will
certainly be very helpful, thank you. https://github.com/haskell/bytestring/blob/2530b1c28f15d0f320a84701bf507d565...
links to a few choice tickets from attempts to use it https://github.com/haskell/bytestring/commit/71c4b438c675aa360c79d79acc9a491... https://github.com/haskell/bytestring/commit/210c656390ae617d9ee3b8bcff5c88d... https://ghc.haskell.org/trac/ghc/ticket/3486 https://ghc.haskell.org/trac/ghc/ticket/3487 https://ghc.haskell.org/trac/ghc/ticket/7270 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) i don't think the issue has to do with inlinePerformIO (though it doesn't
help matters), because changing the optimization level impacts normal
unsafePerformIO too! Thank you for pointing out that the problem exists even with the "benign"
unsafePerformIO. I'm not sure if that makes me relieved or more worried.
Michael On Fri, Aug 1, 2014 at 1:00 AM, Michael Snoyman 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: unsafeWriteArray :: MutableArray RealWorld a -> Int -> a -> ()
unsafeWriteArray (MutableArray arr#) (I# i#) x =
case writeArray# arr# i# x realWorld# of
_ -> () and then replace my unit above with: let unit = unsafeWriteArray arr 0 'B' it works as expected. Similarly, the following tweak fixes the example as
well: arr@(MutableArray arr#) <- newArray 1 'A'
let unit =
case writeArray# arr# 0# 'B' realWorld# of
_ -> () So it appears the bug is in writeArray, or more likely in primitive_.
Sure enough, setting NOINLINE on primitive_ *does* resolve the issue. And
looking at the definition of primitive_: primitive_ f = primitive (\s# -> (# f s#, () #)) this is starting to make sense. unsafeInlineIO is completely ignoring the
resulting state value, as can be seen by its implementation: unsafeInlineIO m = case internal m realWorld# of (# _, r #) -> r Therefore `f s#` is never getting evaluated. However, if we force
evaluation by switching to: primitive_ f = primitive (\s# ->
case f s# of
s'# -> (# s'#, () #)) seems to solve the problem. I think this is the right approach for now,
and I've sent a pull request to primitive with this tweak[1]. 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. Indeed, after going through
the above debugging, I can reproduce the issue using just primops: {-# LANGUAGE MagicHash, UnboxedTuples #-}
import GHC.IO (IO (..))
import GHC.Prim writeB :: MutableArray# RealWorld Char -> IO ()
writeB arr# =
IO $ \s0# ->
(# writeArray# arr# 0# 'B' s0#, () #) inlineWriteB :: MutableArray# RealWorld Char -> ()
inlineWriteB arr# =
case f realWorld# of
(# _, x #) -> x
where
IO f = writeB arr# test :: IO Char
test = IO $ \s0# ->
case newArray# 1# 'A' s0# of
(# s1#, arr# #) ->
case seq# (inlineWriteB arr#) s1# of
(# s2#, () #) ->
readArray# arr# 0# s2# main :: IO ()
main = test >>= print I've filed this as a bug with GHC[2]. Michael [1] https://github.com/haskell/primitive/pull/11
[2] https://ghc.haskell.org/trac/ghc/ticket/9390 _______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

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

On Sat, Aug 2, 2014 at 12:30 AM, Bertram Felgenhauer < bertram.felgenhauer@googlemail.com> wrote:
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.
One last question on the GHC front, however. It *does* seem like
[Michael Snoyman:] 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.
Ahh, good point, thanks. Michael

Indeed unboxed tuples, unboxed vectors, and unboxed Ints are "unboxed"
in rather different ways. Unboxed vectors have no boxes inside of
them. Unboxed Ints have no boxes around them. Unboxed tuples ... I'm
not even sure why they're called that, but what they *really* are is a
mechanism for functions to return multiple values, a notion you may
have encountered if you've used Scheme. There are rather harsh
restrictions on their use to ensure that they work efficiently for
this purpose.
On Sun, Aug 3, 2014 at 2:40 AM, Michael Snoyman
On Sat, Aug 2, 2014 at 12:30 AM, Bertram Felgenhauer
wrote: 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.
Ahh, good point, thanks.
Michael
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sun, Aug 3, 2014 at 2:58 AM, David Feuer
I'm not even sure why they're called that, but what they *really* are is a mechanism for functions to return multiple values
They are unboxed in a way similar to the way the others are: no constructor in their internal representation. They *do* have an extra level of indirection still, just not the constructor cell that normally goes with it. (This is also why historically their use in GHC has been rather restricted.) -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
participants (6)
-
Bertram Felgenhauer
-
Brandon Allbery
-
Carter Schonwald
-
David Feuer
-
Felipe Lessa
-
Michael Snoyman