[commit: packages/binary] master: Add @dcoutts's comments regarding accursedUnutterablePerformIO. (ad6e2a2)

git at git.haskell.org git at git.haskell.org
Tue Feb 2 21:04:57 UTC 2016


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

On branch  : master
Link       : http://git.haskell.org/packages/binary.git/commitdiff/ad6e2a2d507b11ef8e6d0d08e76cf7d11dbce51d

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

commit ad6e2a2d507b11ef8e6d0d08e76cf7d11dbce51d
Author: Lennart Kolmodin <kolmodin at gmail.com>
Date:   Mon Jan 18 23:15:55 2016 +0100

    Add @dcoutts's comments regarding accursedUnutterablePerformIO.


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

ad6e2a2d507b11ef8e6d0d08e76cf7d11dbce51d
 src/Data/Binary/Builder/Base.hs | 5 +++++
 src/Data/Binary/Get/Internal.hs | 4 ++++
 2 files changed, 9 insertions(+)

diff --git a/src/Data/Binary/Builder/Base.hs b/src/Data/Binary/Builder/Base.hs
index 1b1c0b1..62d286e 100644
--- a/src/Data/Binary/Builder/Base.hs
+++ b/src/Data/Binary/Builder/Base.hs
@@ -198,6 +198,11 @@ flush = Builder $ \ k buf@(Buffer p o u l) ->
       then k buf
       else let !b  = Buffer p (o+u) 0 l
                !bs = S.PS p o u
+           -- It should be safe to use accursedUnutterablePerformIO here.
+           -- The place in the buffer where we write is determined by the 'b'
+           -- value, and writes should be deterministic. The thunk should not
+           -- be floated out and shared since the buffer references the
+           -- incoming foreign ptr.
            in return $! L.Chunk bs (accursedUnutterablePerformIO (k b))
 {-# INLINE [0] flush #-}
 
diff --git a/src/Data/Binary/Get/Internal.hs b/src/Data/Binary/Get/Internal.hs
index 9dcd22c..10e372f 100644
--- a/src/Data/Binary/Get/Internal.hs
+++ b/src/Data/Binary/Get/Internal.hs
@@ -414,7 +414,11 @@ unsafeReadN :: Int -> (B.ByteString -> a) -> Get a
 unsafeReadN !n f = C $ \inp ks -> do
   ks (B.unsafeDrop n inp) $! f inp -- strict return
 
+-- | @readNWith n f@ where @f@ must be deterministic and not have side effects.
 readNWith :: Int -> (Ptr a -> IO a) -> Get a
 readNWith n f = do
+    -- It should be safe to use accursedUnutterablePerformIO here.
+    -- The action must be deterministic and not have any external side effects.
+    -- It depends on the value of the ByteString so the value dependencies look OK.
     readN n $ \s -> accursedUnutterablePerformIO $ B.unsafeUseAsCString s (f . castPtr)
 {-# INLINE readNWith #-}



More information about the ghc-commits mailing list