
Dear Cafe, I am reading an article on HaskellWiki about unsafe IO[1]. It gives the guideline about usage of unsafeDupablePerformIO: "If you need extra speed, and it's acceptable for the action to be performed multiple times, and it's acceptable if this action is canceled halfway through its execution, use unsafeDupablePerformIO.” Inside `ByteStirng` module[2], I noticed that when converting [Char] to ByteString, it uses unsafeDupablePerformIO to allocate space for the ByteString, as the following code shows (important information highlighted): packChars :: [Char] -> ByteString packChars cs = unsafePackLenChars (List.length cs) cs : unsafePackLenBytes :: Int -> [Word8] -> ByteString unsafePackLenBytes len xs0 = unsafeCreate len $ \p -> go p xs0 where go !_ [] = return () go !p (x:xs) = poke p x >> go (p `plusPtr` 1) xs unsafeCreate :: Int -> (Ptr Word8 -> IO ()) -> ByteString unsafeCreate l f = unsafeDupablePerformIO (create l f) -- | A way of creating ByteStrings outside the IO monad. The @Int@ -- argument gives the final size of the ByteString. -- | Create ByteString of size @l@ and use action @f@ to fill it's contents. create :: Int -> (Ptr Word8 -> IO ()) -> IO ByteString create l f = do fp <- mallocByteString l withForeignPtr fp $ \p -> f p return $! PS fp 0 l {-# INLINE create #-} -- | Wrapper of 'mallocForeignPtrBytes' with faster implementation for GHC -- mallocByteString :: Int -> IO (ForeignPtr a) mallocByteString = mallocPlainForeignPtrBytes {-# INLINE mallocByteString #-} The doc of `mallocPlainForeignPtrBytes`, however, explicitly says that no finalizer is added for the allocated memory. So my question is: would not the allocation code in ByteString module cause memory leaks? The doc of `unsafeDupablePerformIO` mentions that it "duplicated IO actions is only run partially, and then interrupted in the middle without an exception being raised”. Thus, it might happen that we have already allocated the memory but then the action is interrupted, without reclaiming the memory. [1] https://wiki.haskell.org/Evaluation_order_and_state_tokens [2] http://hackage.haskell.org/package/bytestring-0.10.8.2/docs/src/Data.ByteStr... Best Regards, Qingbo Liu