Hi Sylvain,
thank you for your response! I try to use  this 2 lines

allocaArray (w*n) $ \var -> do
                  xs <- peekArray (w) var
to code
char **varnames = ccl_new_array (char *, w);

but it return [CString] not a [String]
On 04/29/2014 01:58 PM, Sylvain Henry wrote:
Hi,

"varnames" is an array of pointers, you cannot allocate it with mallocBytes (n*100).

Try something like this (not tested):

mallocList :: [String] -> IO (Ptr CString)
mallocList xs = newArray =<< forM xs g
  where
    g x = do
       b <- mallocBytes 100
       pokeCString b x 99
       return b

pokeCString :: CString -> String -> Int -> IO ()
pokeCString dst value maxLen = withCStringLen (take maxLen value) $ uncurry (copyArray dst)

-Sylvain


2014-04-29 13:11 GMT+02:00 Lamine <mohamadoulam...@gmail.com <mailto:mohamadoulam...@gmail.com>>:


    Hi,

    I want to do write this C code in haskell code, but i have some pb:

    int w ;
    char **varnames = ccl_new_array (char *, w);

    int i;
              for (i = 0; i < w; i++)
                {
                  varnames[i] = ccl_new_array (char, 100);
                  sprintf (varnames[i], "x%d", i);
                }

    I try this code unsing mallocList to (http://lpaste.net/report/712):
    mallocList :: [CString] -> IO (Ptr CString)
    mallocList xs = do let n = Prelude.length xs
                       p <- mallocBytes (n*100)
                       forM_ (Prelude.zip [0..] xs)
                        (uncurry (pokeByteOff p))
                       return p

    let n = sizeOf(undefined :: CString)
               allocaArray w $ \var -> do
                      xs <- peekArray (w*n) var
                      varnames <- mallocList xs

    I have an error "segmentation fault(core dumped)".
    can someone please help me? Thank you.

    Lamine
    _______________________________________________
    FFI mailing list
    FFI@haskell.org <mailto:FFI@haskell.org>
    http://www.haskell.org/mailman/listinfo/ffi




--
« Chaque génération doit, dans un état relatif de captivité, découvrir sa mission. Elle a le choix de la remplir ou la trahir». Frantz Fanon
_______________________________________________
FFI mailing list
FFI@haskell.org
http://www.haskell.org/mailman/listinfo/ffi

Reply via email to