Using unsafePerformIO and free with CString

I’m trying to write a wrapper for a C function. Here is an example of such code: {-# LANGUAGE ForeignFunctionInterface #-} import Foreign.C.String import Foreign.C.Types import System.IO.Unsafe import Foreign.Marshal.Alloc foreign import ccall "string.h strcmp" c_strcmp :: CString -> CString -> CInt strcmp :: String -> String -> Ordering strcmp s t = unsafePerformIO $ do s' <- newCString s t' <- newCString t let n = c_strcmp s' t' -- free s' -- free t' return $ case () of _ | n == 0 -> EQ | n < 0 -> LT | otherwise -> GT Two questions: 1. May I safely use unsafePerformIO in such cases? 2. What’s the proper way of using free here? If I uncomment the above, the function returns incorrect results.

On Sun, Dec 15, 2013 at 3:32 PM, Nikita Karetnikov
let n = c_strcmp s' t' -- free s' -- free t' return $ case () of _ | n == 0 -> EQ | n < 0 -> LT | otherwise -> GT
Two questions:
1. May I safely use unsafePerformIO in such cases?
Yes, although you might prefer to use the variant specified by the FFI standard, unsafeLocalState.
2. What’s the proper way of using free here? If I uncomment the above, the function returns incorrect results.
Note that you have not forced evaluation of `n` when you free the CString-s, so `c_strcmp` has not necessarily been called yet. Control.Exception.evaluate may be of use here. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

On Sun, Dec 15, 2013 at 3:32 PM, Nikita Karetnikov
I’m trying to write a wrapper for a C function. Here is an example of such code:
... s' <- newCString s t' <- newCString t let n = c_strcmp s' t' -- free s' -- free t'
...
It'd be better to use withCString [1] instead, to avoid a memory leak if an exception occurs between newCString and free. Also, make c_strcmp an IO function: foreign import ccall "string.h strcmp" c_strcmp :: CString -> CString -> IO CInt The way you had it, c_strcmp had an implicit unsafePerformIO, which we don't want or need here. strcmp has the side effect of reading from pointers at a given moment in time. As Brandon brought up, right now, your code might as well say: strcmp s t = unsafePerformIO $ do s' <- newCString s t' <- newCString t -- free s' -- free t' return $ case c_strcmp s' t' of _ | n == 0 -> EQ | n < 0 -> LT | otherwise -> GT Because of laziness, n = c_strcmp s' t' isn't evaluated until it is needed. What you should say instead is: ... n <- c_strcmp s' t' ... This places the strcmp in the monadic chain so it will run at the right time (after newCString and before freeCString). [1]: http://hackage.haskell.org/package/base/docs/Foreign-C-String.html#v:withCSt...
participants (3)
-
Brandon Allbery
-
Joey Adams
-
Nikita Karetnikov