The problem disapears when I use GHC to compile the c file, this somehow allows the linker to find the __stginit_SortPoints3() function. I don't really understand what GHC does differently from gcc at compile time on c files.
Thank you for your time.

   Yann Morvan

Yann Morvan wrote:

Hello,
I am calling a Haskell function from C using foreign export, it works fine on the first call,
but as soon as I call it again I get:

internal error: stg_ap_pp_ret

and I am asked to report it as a bug.
I don't know how much detail I should give, so I'll just reproduce the relevant code (excuse the clumsyness):
On the Haskell side:

module SortPoints3 where
[...]
data Vect2D = Vect2D {xx,yy :: CFloat} deriving Show

instance Storable Vect2D where
 peek a = do
            x <- peekElemOff (castPtr a) 0
            y <- peekElemOff (castPtr a) 1
            return (Vect2D x y)
 poke a (Vect2D x y) = do
                         pokeElemOff (castPtr a) 0 x
                         pokeElemOff (castPtr a) 1 y
 sizeOf a = let dummy = Vect2D 2.0 2.0 in
    (sizeOf (xx dummy) + (sizeOf (yy dummy)))
 alignment a = 4
[...]
foreign export ccall doIt :: (Ptr Vect2D) -> (Ptr Vect2D) -> CInt -> CFloat -> IO ()

doIt :: (Ptr Vect2D) -> (Ptr Vect2D) ->  CInt -> CFloat -> IO ()
doIt pointsPtr projectedPtr n t = do
 points <- peekArray (fromIntegral n) pointsPtr
 (sortedPoints, sortedProjections ) <- sortPoints t points
 pokeArray pointsPtr sortedPoints
 pokeArray projectedPtr sortedProjections
 return ()

On the C side, the function is called from a callback function of the OpenCV library. I pass it pointers to the OpenCV CvPoint2D32f type, which is a simple struct with two floats for coordinates.

I had to remove the call to hs_add_root as the linker (GHC's) couldn't find __stginit_SortPoints3()

I tried the following:

foreign export ccall printIt :: CFloat -> IO ()

printIt :: CFloat -> IO ()
printIt f = putStr $ "\nTest\n" ++ (show f) ++ "\n"

this function has no problem when called several times from the same location in the c code.

Please tell me what to fix if the error is on my side.
Thank you for your time,

   Yann Morvan



_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to