[Haskell-cafe] Using unsafePerformIO and free with CString

Nikita Karetnikov nikita at karetnikov.org
Sun Dec 15 20:32:49 UTC 2013


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.

   
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 835 bytes
Desc: not available
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20131216/ff802630/attachment.sig>


More information about the Haskell-Cafe mailing list