[Haskell-cafe] A few questions about unsafe IO

Qingbo Liu quentin.liu.0415 at gmail.com
Mon Dec 31 04:06:20 UTC 2018


Oh I see. Thank you!

I tried to search for some articles particularly on finalizers in Haskell but most I found were just documentations. So according to the documentation in Foreign.ForeignPtr, finalizers associated with a foreign pointer will be invoked when there are no more references to the pointer, with the finalizers typically being the routine of a foreign language. If the finalizer of a foreign pointer does not do anything, e.g. it ignores the argument, will the memory allocated for the foreign pointer be garbage collected? In other words, are the finalizers typically used for cleaning up resources such as file handles (but not memory)?

Best Regards,
Qingbo Liu

On Dec 30, 2018, 09:03 +0800, Zemyla <zemyla at gmail.com>, wrote:
> No finalizer is added for the allocated memory because the address
> given is just that of a pinned ByteArray, which is garbage collected.
> If the operation is interrupted, then the memory will be reclaimed
> during the next GC cycle.
>
> On Fri, Dec 28, 2018 at 9:26 PM Qingbo Liu <quentin.liu.0415 at gmail.com> wrote:
> >
> > 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.ByteString.Internal.html#ByteString
> >
> > Best Regards,
> > Qingbo Liu
> > _______________________________________________
> > Haskell-Cafe mailing list
> > To (un)subscribe, modify options or view archives go to:
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> > Only members subscribed via the mailman list are allowed to post.
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20181231/38a7fe0e/attachment.html>


More information about the Haskell-Cafe mailing list