Skip to content

Commit

Permalink
mkCurlWithCleanup: use Foreign.Concurrent.addForeignPtrFinalizer for …
Browse files Browse the repository at this point in the history
…our Haskell-based finalizers
  • Loading branch information
Sigbjorn Finne committed Apr 21, 2009
1 parent 0eefd17 commit 7db79c0
Showing 1 changed file with 14 additions and 12 deletions.
26 changes: 14 additions & 12 deletions Network/Curl/Types.hs
@@ -1,4 +1,4 @@
{-# LANGUAGE ForeignFunctionInterface, EmptyDataDecls #-}
{-# LANGUAGE ForeignFunctionInterface, EmptyDataDecls, CPP #-}
--------------------------------------------------------------------
-- |
-- Module : Network.Curl.Types
Expand All @@ -25,9 +25,9 @@ import Network.Curl.Debug

import Foreign.Ptr
import Foreign.ForeignPtr
import Foreign.Concurrent ( addForeignPtrFinalizer )
import Data.Word
import Control.Concurrent
import Control.Monad.Fix(mfix)
import Data.Maybe(fromMaybe)
import qualified Data.IntMap as M
import Data.IORef
Expand Down Expand Up @@ -64,16 +64,16 @@ mkCurl h = mkCurlWithCleanup h om_empty
mkCurlWithCleanup :: CurlH -> OptionMap -> IO Curl
mkCurlWithCleanup h clean = do
debug "ALLOC: CURL"
v2 <- newIORef clean
fh <- newForeignPtr_ h
v1 <- newMVar fh
v2 <- newIORef clean
let new_h = Curl { curlH = v1, curlCleanup = v2 }

fin <- mkIOfin $ do debug "FREE: CURL"
easy_cleanup h
runCleanup v2
addForeignPtrFinalizer fin fh

let fnalizr = do
debug "FREE: CURL"
easy_cleanup h
runCleanup v2
Foreign.Concurrent.addForeignPtrFinalizer fh fnalizr
return new_h


Expand Down Expand Up @@ -137,17 +137,19 @@ shareIO act =
return new_act
--------------------------------------------------------------------------------


{- UNUSED:
-- FFI for inalizers.
-- | Make a finalizer from an IO action.
mkIOfin :: IO a -> IO (FinalizerPtr b)
mkIOfin m = mfix (\ptr -> ioFinalizer (m >> freeHaskellFunPtr ptr))
foreign import ccall
"curl/curl.h curl_easy_cleanup" easy_cleanup :: CurlH -> IO ()

foreign import ccall "wrapper"
ioFinalizer :: IO () -> IO (FinalizerPtr a)
-}

foreign import ccall
"curl/curl.h curl_easy_cleanup" easy_cleanup :: CurlH -> IO ()

0 comments on commit 7db79c0

Please sign in to comment.