[Haskell-cafe] Semantics of ForeignPtr Finalizers

Bas van Dijk v.dijk.bas at gmail.com
Sun Jun 19 09:52:59 CEST 2011


Hello,

I have a question about the semantics of finalizers of ForeignPtrs:

If an in scope value has a reference to a ForeignPtr is the foreign
object always kept alive, even if that reference is not used? Or do I
always need to wrap each computation, which needs to have the foreign
object alive, inside withForeignPtr?

To make my question more concrete, I will give a simplified example
from my usb library (a high-level binding to the libusb C library):

https://github.com/basvandijk/usb

To use the library you first need to initialize libusb which will
yield a context:

newtype Ctx = Ctx {getCtxFrgnPtr ∷ (ForeignPtr C'libusb_context)}

When you're finished with libusb you need to exit the library. This is
done automatically using a ForeignPtr:

newCtx ∷ IO Ctx
newCtx = mask_ $ do
           ctxPtr ← libusb_init
	   Ctx <$> newForeignPtr p'libusb_exit ctxPtr
    where
      libusb_init ∷ IO (Ptr C'libusb_context)
      libusb_init = alloca $ \ctxPtrPtr → do
                      handleUSBException $ c'libusb_init ctxPtrPtr
                      peek ctxPtrPtr

I provide a handy internal utility function for accessing the pointer
to the context:

withCtxPtr ∷ Ctx → (Ptr C'libusb_context → IO α) → IO α
withCtxPtr = withForeignPtr ∘ getCtxFrgnPtr

Because this function uses withForeignPtr it's guaranteed that the
context is kep alive during the duration of the given function. For
example, in the following, it is guaranteed that c'libusb_set_debug is
always given a live context:

setDebug ∷ Ctx → Verbosity → IO ()
setDebug ctx verbosity = withCtxPtr ctx $ \ctxPtr →
                           c'libusb_set_debug ctxPtr $ genFromEnum verbosity

There are also types which are derived from a context. For example:
getDevices ∷ Ctx → IO [Device] is a function which given a context
returns a list of USB devices currently attached to your system.

The requirement is that when you need to use a device the context has
to be kept alive. Therefor I keep a reference to the context inside
the device:

data Device = Device
    { getCtx ∷ !Ctx
    , getDevFrgnPtr ∷ !(ForeignPtr C'libusb_device)
    , deviceDesc ∷ !DeviceDesc
    }

The idea is that as long as you have a reference to a device you also
keep the context alive because the device references the context.
(Note that a device, in turn, also contains a ForeignPtr)

getDevices ∷ Ctx → IO [Device]
getDevices ctx = ...
    where
      mkDev ∷ Ptr C'libusb_device → IO Device
      mkDev devPtr = liftA2
                       (Device ctx)
                       (newForeignPtr p'libusb_unref_device devPtr)
                       (getDeviceDesc devPtr)

Again I provide a handy internal utility function for accessing the
pointer to a device:

withDevicePtr ∷ Device → (Ptr C'libusb_device → IO α) → IO α
withDevicePtr = withForeignPtr ∘ getDevFrgnPtr

And now my question. Is it guaranteed that when the device is in scope
the context is always kept alive? For example, is the context kept
alive in the following:

openDevice ∷ Device → IO DeviceHandle
openDevice dev = withDevicePtr dev $ \devPtr →
                   alloca $ \devHndlPtrPtr → do
                     handleUSBException $ c'libusb_open devPtr devHndlPtrPtr
                     DeviceHandle dev <$> peek devHndlPtrPtr

Or do I also need to call withCtxPtr inside withDevicePtr as such:

withDevicePtr (Device ctx devFP _) f = withCtxPtr ctx $ \_ →
                                         withForeignPtr devFP f

Thanks,

Bas



More information about the Haskell-Cafe mailing list