[Haskell-cafe] FFI woes!
Robert Dockins
robdockins at fastmail.fm
Thu Dec 16 08:56:15 EST 2004
>>1) Finalizers are not (some say cannot) be guaranteed to run, even on
>>normal program termination, even if you force GC before exiting.
>
>
> I only need a guarantee that it will be run if the Ptr is no longer
> being referenced.
This is exactly the guarantee you _don't_ have. The only guarantee you
have is that it _won't_ be run if the Ptr _is_ being referenced.
>>I would suggest you find some way to accomplish what you want without
>>using finalizers.
>
>
> That would require the user to manually free up resources once they're
> not needed anymore. Something which I believe is a bit too low-level
> for my tastes.
> I basically want the user to be able to just create a sound resource
> and then play it, without having to do any book-keeping as to when the
> sound resource is not used anymore and can be released.
My concern is that this approach is a little too non-deterministic.
Because playing sound involves HW resources, it is better to make users
do the bookkeeping and have well-defined behavior rwt releasing resources.
That said, you can probably get what you want by using weak pointers.
Wrap up your Ptr in a ForiegnPtr and wrap _that_ up in an abstract
datatype, and attach a weak pointer to the ForeignPtr (make sure all
functions that access the Ptr use 'withForeignPtr' or
'touchForeignPtr'). Add a (Ptr,WeakPtr ()) pair to a list of "open"
songs, which is monitored by a single clean-up thread (use an MVar for
the list). Return the high level value to the user; when the enclosed
ForeignPtr is garbage collected deRefWeak on the weak pointer will
return Nothing. Then the clean-up thread can begin polling the song
object to see if it is finished. You can also poke this thread at
program-end to force it to free all resources it knows about, so that
your program behaves well, assuming normal termination. Weak pointers
are documented here:
http://www.haskell.org/ghc/docs/latest/html/libraries/base/System.Mem.Weak.html
I think that something like this would work:
module MySongs ( Song, mkSong, something ) where
foreign .... makeASong :: whatever -> IO (Ptr ())
foreign .... doSomething :: Ptr () -> IO ()
data Song = Song ForeignPtr
mkSong :: whatever -> MVar [(Ptr,Weak ())] -> IO Song
mkSong x mvar = do
p <- makeASong x
f <- newForeignPtr_ p
w <- mkWeak f ()
l <- takeMVar mvar
putMVar mvar ((p,w):l)
return Song f
something :: Song -> IO ()
something (Song f) = do
withForeignPtr f \p ->
do doSomething p
More information about the Haskell-Cafe
mailing list