#2926: Foreign exported function returns wrong type
-----------------------------+----------------------------------------------
Reporter: fasta | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler (FFI)
Version: 6.10.1 | Severity: normal
Keywords: | Testcase:
Os: Unknown/Multiple | Architecture: Unknown/Multiple
-----------------------------+----------------------------------------------
I call foo, foreign export ccall foo :: Int -> IO CInt, from C code like
this: printf("%d\n", (int)foo((HsInt32)2500)); but when I remove the (int)
cast, gcc complains (warnings, not errors) because it thinks that the
thing that foo returns is a HsInt32, and not a C int. The type for foo
clearly specifies it is a CInt.
The bug is that GHC is probably not generating a CInt, but a HsInt32.
{{{
{-# LANGUAGE ForeignFunctionInterface #-}
-- name this file ExportHaskellToCStruct.hs
module ExportHaskellToCStruct(foo) where
import Foreign.C
import Data.List
foreign export ccall foo :: Int -> IO CInt
foo = return . genericLength . f
f :: Int -> [Int]
f 0 = []
f n = n:(f (n-1))
}}}
{{{
#include <stdio.h>
#include "/correctpathto/include/HsFFI.h" /* FIX PATH for your
installation */
#define __GLASGOW_HASKELL__
#ifdef __GLASGOW_HASKELL__
#include "ExportHaskellToCStruct_stub.h"
#endif
#ifdef __GLASGOW_HASKELL__
extern void __stginit_ExportHaskellToCStruct(void);
#endif
int main(int argc, char *argv[])
{
int i;
hs_init(&argc, &argv);
#ifdef __GLASGOW_HASKELL__
hs_add_root(__stginit_ExportHaskellToCStruct);
#endif
for (i = 0; i < 5; i++) {
printf("%d\n", (int)foo((HsInt32)2500));
}
hs_exit();
return 0;
}
}}}
{{{
gcc --version
gcc (Ubuntu 4.3.2-1ubuntu11) 4.3.2
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2926>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs