[commit: ghc] wip/interleave-rw: Use runRW# to implement unsafeInterleaveIO (544b6b1)

git at git.haskell.org git at git.haskell.org
Thu Mar 9 23:40:38 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/interleave-rw
Link       : http://ghc.haskell.org/trac/ghc/changeset/544b6b14ae8636f7d2a7feb15bac2610499ba345/ghc

>---------------------------------------------------------------

commit 544b6b14ae8636f7d2a7feb15bac2610499ba345
Author: David Feuer <David.Feuer at gmail.com>
Date:   Thu Mar 9 18:39:16 2017 -0500

    Use runRW# to implement unsafeInterleaveIO
    
    Summary:
    Instead of holding on to the past, let's start a new timeline.
    This seems a lot cleaner, and may even allow inlining.
    
    Fixes Trac #13405
    
    Reviewers: austin, hvr, bgamari
    
    Subscribers: rwbarton, thomie
    
    Differential Revision: https://phabricator.haskell.org/D3308


>---------------------------------------------------------------

544b6b14ae8636f7d2a7feb15bac2610499ba345
 libraries/base/GHC/IO/Unsafe.hs | 9 +++------
 1 file changed, 3 insertions(+), 6 deletions(-)

diff --git a/libraries/base/GHC/IO/Unsafe.hs b/libraries/base/GHC/IO/Unsafe.hs
index 7523535..2a5a87f 100644
--- a/libraries/base/GHC/IO/Unsafe.hs
+++ b/libraries/base/GHC/IO/Unsafe.hs
@@ -130,14 +130,11 @@ unsafeInterleaveIO m = unsafeDupableInterleaveIO (noDuplicate >> m)
 -- a readMVar, but it seems wrong for unsafeInterleaveIO to sometimes
 -- share and sometimes not (plus it probably breaks the noDuplicate).
 -- So now, we do not inline unsafeDupableInterleaveIO.
-
-{-# NOINLINE unsafeDupableInterleaveIO #-}
+{-# INLINE unsafeDupableInterleaveIO #-}
 unsafeDupableInterleaveIO :: IO a -> IO a
 unsafeDupableInterleaveIO (IO m)
-  = IO ( \ s -> let
-                   r = case m s of (# _, res #) -> res
-                in
-                (# s, r #))
+  = IO ( \ s ->
+       (# s, runRW# (\s2 -> case m s2 of (# _, res #) -> res) #))
 
 {-|
 Ensures that the suspensions under evaluation by the current thread



More information about the ghc-commits mailing list