Bugs item #655400, was opened at 2002-12-17 12:43
You can respond by visiting: 
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=655400&group_id=8032

Category: Compiler
Group: 5.04.2
Status: Open
Resolution: None
Priority: 5
Submitted By: Henrik Nilsson (nhn)
Assigned to: Nobody/Anonymous (nobody)
Summary: Returning Double from foreign fun. fails

Initial Comment:
Returning doubles from foreign functions
can fail when optimizations (-O1) is turned on.
Things work when using the native code generator
or when compiling with -fvia-c and -O0.

I've tried on Linux (RedHat 7.3) with both GHC 5.04.1
and GHC 5.04.2.

What seems to be going on is that the inclusion
of the header file containing the foreign function
prototype is not propagated along with the actual
C call when it gets inlined. This leads to warnings
like:

/usr/local/bin/ghc-5.04.2 -c  -fglasgow-exts -O1
-package lang  -keep-hc-files  -o Graphics/SP/M1.o -ohi
Graphics/SP/M1.hi Graphics/SP/M1.hs
Graphics/SP/M1.hc: In function `r8Hd_fast1':
Graphics/SP/M1.hc:103: warning: implicit declaration of
function `prim_foreignF4'

The original GreenCard definition looks like this
(from a file called Graphics_SP_Foreign.gc):

%fun foreignF4 :: Double -> Double
%call (double x)
%code double y;
%     y = sin(x);
%     printf("x = %f, y = %f\n", x, y);
%result (double y)

The GreenCard generated C code in

    Graphics_SP_Foreign_stub_ffi.c

looks like this:

double prim_foreignF4(double x)
{ double y;
  do { double y;
     y = sin(x);
     printf("x = %f, y = %f\n", x, y);
      
      return((double)(y));} while(0);
}

and the related header file,
Graphics_SP_Foreign_stub_ffi.h:

#include <math.h>
#include "c_stuff.h"
#include "c_stuff2.h"
#include "HsFFI.h"
extern int prim_foreignF1(int x);
extern int prim_foreignF2(int x);
extern double prim_foreignF4(double x);

The GreenCard generated Haskell:

foreignF4 :: Double -> Double
foreignF4 x =
  unsafePerformIO(
    prim_foreignF4 x
    >>= \  y  ->
    (return (y)))
foreign import  ccall unsafe
"Graphics_SP_Foreign_stub_ffi.h prim_foreignF4"
prim_foreignF4 :: Double -> IO (Double)

Graphics_SP_Foreign.hc starts like this:

#include "Stg.h"
#include "HsBase.h"
#include "HsLang.h"
#include "Graphics_SP_Foreign_stub_ffi.h"
#include "Graphics_SP_Foreign_stub_ffi.h"
#include "Graphics_SP_Foreign_stub_ffi.h"

i.e., the header file is included properly.

and the place where prim_foreignF4 actually gets
called looks like this:

INFO_TABLE_SRT_BITMAP(s1hc_info,s1hc_ret,0,0,0,0,RET_SMALL,static
,IF_,0,0);
IFN_(s1hc_ret) {
StgDouble _B0_;
StgDouble _B3_;
FB_
_B0_=PK_DBL((W_*)(R1.p+1));
*Sp=(W_)((P_)&s1hd_info);
{
StgDouble _ccall_result;
StgDouble _ccall_arg1=_B0_;
CALLER_SAVE_SYSTEM
_ccall_result = (prim_foreignF4((_ccall_arg1)));
CALLER_RESTORE_SYSTEM
_B3_=_ccall_result;
}
ASSIGN_DBL((W_*)(Sp-2),_B3_);
Sp=Sp-3;
JMP_(ENTRY_CODE((P_)(Sp[3])));
FE_
}


This is fine. However, there is another module M1
where foreignF4 also gets called:

module Graphics.SP.M1 where

import Graphics.SP.M2
import Graphics.SP.M3
import Graphics_SP_Foreign

sp_m1 n = "Graphics.SP.M1 [\n"
          ++ take n' (repeat ' ') ++ "sp_m2 = " ++
sp_m2 n' ++ "\n"
          ++ take n' (repeat ' ') ++ "sp_m3 = " ++
sp_m3 n' ++ "\n"
          ++ take n' (repeat ' ') ++ "foreignF1 3 = "
          ++ show (foreignF1 3) ++ "\n"
          ++ take n' (repeat ' ') ++ "foreignF2 3 = "
          ++ show (foreignF2 3) ++ "\n"
          ++ take n' (repeat ' ') ++ "foreignF3 = "
          ++ show foreignF3 ++ "\n"
          ++ take n' (repeat ' ') ++ "foreignF4 (pi/6)
= "
          ++ show (foreignF4 (pi/6)) ++ "\n"
          ++ "]\n"
    where n' = n + 4

It's .hc file starts like this:

#include "Stg.h"
#include "HsBase.h"
#include "HsLang.h"

i.e., Graphics_SP_Foreign_stub_ffi.h does not get
included.

Yet it does contain the following call to
prim_foreignF4:

II_(r8Hd_info);
IFN_(r8Hd_fast1) {
StgDouble _B0_;
StgDouble _B3_;
FB_
STK_CHK(4,(P_)&r8Hd_info,R1.p,0,Sp[-1]=(W_)((ARG_TAG(0)));
Sp=Sp-1;);
_B0_=0.5235987755982988;
Sp[-1]=(W_)((P_)&s8Kk_info);
Sp=Sp-1;
{
StgDouble _ccall_result;
StgDouble _ccall_arg1=_B0_;
CALLER_SAVE_SYSTEM
_ccall_result = (prim_foreignF4((_ccall_arg1)));
CALLER_RESTORE_SYSTEM
_B3_=_ccall_result;
}
ASSIGN_DBL((W_*)(Sp-2),_B3_);
Sp=Sp-3;
JMP_(ENTRY_CODE((P_)(Sp[3])));
FE_
}

I've attached the complete source files as well in
case you need them.

If you need further info, I'll be happy to assist.

Regards,

/Henrik


----------------------------------------------------------------------

Comment By: Nobody/Anonymous (nobody)
Date: 2002-12-17 13:55

Message:
Logged In: NO 

I have also observed this bug, which also occurs when using 
the FFI directly (without any use of GreenCard).

The observation that "the inclusion 
of the header file containing the foreign function 
prototype is not propagated along with the actual 
C call" is certainly correct.  However, note that it is perfectly 
reasonable to write foreign import declarations which do not 
refer to a header file containing a C prototype, and ghc should 
still be prepared to produce correct code for this case.  

I believe that if ghc is going to do code generation via C, ghc 
must be prepared to emit its own prototype for the foreign 
function directly from the foreign import declaration, without 
requiring an external header file.


If you would like a slightly smaller test case that reproduces 
this bug without using greencard, or have further questions, 
please let me know.

-Antony
antony at apocalypse dot org

----------------------------------------------------------------------

You can respond by visiting: 
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=655400&group_id=8032
_______________________________________________
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to