Mixing C++ and Haskell, OpenSSL thread safety, and using mmap

I wrotted some messages on fa.haskell newsgroup but then I've figured that
people
actually read mailing lists :)
So this is digest of mine recent messages on this newsgroup.
First I want to say about OpenSSL thread safety. It is not thread safe by
default.
Who wants to import and use OpenSLL functions with FFI, have to set locking
hooks for it,
or else spurious crashes with useless stack trace will result. Higher level
of concurrency,
more likely crash will happen.
Since this hooks are called by C, it is easer to setup mutexes in C module,
then call Haskell
main function from it.
details:
http://www.openssl.org/docs/crypto/threads.html
Second I've successfully linked Haskell and C++ with threaded run time.
Well, I'm planning to use Haskell in C++ programs and to call
Haskell functions from C++ and vice versa.
So far I've tried some small test programs and it seems works ok.
If I launch threads from C++ then call Haskell I have to
link with -threaded flag as Haskell run time complains about
entering functions unsafelly without it.
Also I have another question about hs_add_root.
Is this neccessary? I've tried with and without call to
this function and everything seems to work same way.
That means I don't notice any difference. I ask this because
if for example I have lot of Haskell modules do I need to call
hs_add_root for every and each one?
This is just a small example that works both on linux and windows,
(I have different C++ versions but Haskell module is same).
Haskell makes and frees array of pointers to CStrings (char**)
from argument that is CString(char*). Error checking and handling
is intentionally left out for now.
I would appreciate any critics about it, as I've started
to learn language one month ago, but have professional experience since 92
in other languages, specially C++.
-- Haskell module
module MakeWords where
import Foreign
import Foreign.C.String
import Foreign.Storable
import Foreign.Ptr
import Foreign.Marshal.Array
foreign export ccall makeWords :: CString -> IO (Ptr CString)
foreign export ccall freeWords :: Ptr CString -> IO ()
makeWords :: CString -> IO (Ptr CString)
makeWords cs = do let lst = words $ unsafePerformIO $ peekCString cs
p <- mallocArray0 $ length lst
makeWords' lst p
return (p)
makeWords' :: [String] -> Ptr CString -> IO ()
makeWords' [] p = do poke p nullPtr
makeWords' (s:strs) p = do poke p $ unsafePerformIO $ newCString s
makeWords' strs (plusPtr p $ sizeOf p)
freeWords :: Ptr CString -> IO ()
freeWords p = do freeWords' p
free p
freeWords' :: Ptr CString -> IO ()
freeWords' p = if nullPtr /= (unsafePerformIO $ peek p)
then do free $ unsafePerformIO $ peek p
freeWords' $ plusPtr p $ sizeOf p
else return ()
-- end Haskell module
// C++, windows version
#include

I use OpenSSL in a heavily threaded environment. It works without extra locking. I do not use bound (OS) threads, though. On Dec 8, 2005, at 7:06 AM, Branimir Maksimovic wrote:
First I want to say about OpenSSL thread safety. It is not thread safe by default. Who wants to import and use OpenSLL functions with FFI, have to set locking hooks for it, or else spurious crashes with useless stack trace will result. Higher level of concurrency, more likely crash will happen.

From: Joel Reymont
To: "Branimir Maksimovic" CC: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Mixing C++ and Haskell, OpenSSL thread safety, and using mmap Date: Thu, 8 Dec 2005 09:21:08 +0000 I use OpenSSL in a heavily threaded environment. It works without extra locking. I do not use bound (OS) threads, though.
If code executes concurrently that means you have a problem with OpenSSL for sure. Probably it works now because SSL calls are not concurrent or so, but I wouldn't risk about it as I am sure that you would have problems with that if calls to SSL functions are concurrent. Also, I think that original problem of gethostbyname just hides real SSL problem as you've probably locked around that too, but you can't be really sure. so either lock around every SSL call with global mutex or set locks in C module then call Haskell or setup callbacks from Haskell, whichever way you prefer. Greetings, Bane.
On Dec 8, 2005, at 7:06 AM, Branimir Maksimovic wrote:
First I want to say about OpenSSL thread safety. It is not thread safe by default. Who wants to import and use OpenSLL functions with FFI, have to set locking hooks for it, or else spurious crashes with useless stack trace will result. Higher level of concurrency, more likely crash will happen.
_________________________________________________________________ Express yourself instantly with MSN Messenger! Download today it's FREE! http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/

I only lock around the connectTo to avoid the gethostbyname issue. After that I set up two memory BIOs and hook them to go through a handshake. Encryption is done through the BIOs afterwards since I need to wrap the encrypted data in a header of my own (don't ask). I haven't had a problem with this so far but I might have just been lucky. I will put some locks around. On Dec 8, 2005, at 9:28 AM, Branimir Maksimovic wrote:
Also, I think that original problem of gethostbyname just hides real SSL problem as you've probably locked around that too, but you can't be really sure. so either lock around every SSL call with global mutex or set locks in C module then call Haskell or setup callbacks from Haskell, whichever way you prefer.
participants (2)
-
Branimir Maksimovic
-
Joel Reymont