Passing CString array to Haskell shared library

Hello everyone! Long time reader, first time poster. Was wondering if someone could give me some direction or hints on how I might go about passing a CString array into an exported Haskell function. What I'm trying to do is augment the RecordLinkage package from R using Haskell. Seems pretty straight forward. With some help from Neil Mitchell's excellent blog post on the subject ( http://neilmitchell.blogspot.com/2011/10/calling-haskell-from-r.html) I've managed to make calls into Haskell and utilize the Text.EditDistance package. This is working rather well, except that I'm trying to calculate the edit distance from each of 3000 strings to each of 780,000 strings. Since I'm calling Haskell from R once for every comparison (and allocating a result record in R for each return) I find myself running out of memory rather quickly. What I'd like to do is send both complete string lists into Haskell to process, and have it pass me back a result vector. Below is how I'm currently making the call using individual strings. I've tried looking through the GHC User's Guide, through the Wiki on usingthe FFI, and a number of other resources, but I seem to have come to an impasse. Could anyone lend some assistance? ------------- Code start ----- {-# LANGUAGE ForeignFunctionInterface #-} module Levenshtein where import Foreign.C.Types import Foreign.C.String import Foreign.Ptr import Foreign.Storable import Text.EditDistance levenshteinWeight :: Ptr Int -> Ptr Int -> Ptr Int -> Ptr CString -> Ptr CString -> Ptr Int -> IO () levenshteinWeight del ins subs str1 str2 result = do del <- peek del ins <- peek ins subs <- peek subs str1' <- peekCString =<< peek str1 str2' <- peekCString =<< peek str2 poke result $ levenshteinDistance EditCosts { deletionCosts = ConstantCost del, insertionCosts = ConstantCost ins, substitutionCosts = ConstantCost subs, transpositionCosts = ConstantCost 1} str1' str2' foreign export ccall levenshteinWeight :: Ptr Int -> Ptr Int -> Ptr Int -> Ptr CString -> Ptr CString -> Ptr Int -> IO () ------------- Code end ----- Thanks in Advance! Alex
participants (1)
-
Alexander Mumme