Manuel M. T. Chakravarty <[EMAIL PROTECTED]> writes: 
> 
.... 
> > >   --(2) foreign import ccall "" "bar" bar :: IO Int64
> > > 
> > 
> > this can be reduced to
> > 
> >      foreign import "bar" bar :: IO Int64
> 
> So, `ccall' is the default?  (This is not documented, I think.)
> 

There's been some changes relatively recently, making the calling
convention optional and dropping the requirement that a 'foreign
import'ed function has got to be an IO action, i.e., you can now 
write
  
   foreign import "sin" my_sin :: Float -> Float

I'll see if I can put up a new version of the spec which reflects
these changes.

> > >   main = do
> > >      foo (intToInt8 8) (intToInt16 16) (intToInt32 32) 
> > > (intToInt64 64) 
> > >   --(2)    _ <- bar
> > >      return ()
> > > 
> > > The first problem is that `Int8', `Int16', and `Int32' are
> > > all implemented by the same C data type, namely the one
> > > represented by `I_' in the HC file -- this makes all of them
> > > 32 bit `signed int' on my Pentium machine.  The generated HC 
> > > code for the call to `foo' is
> > > 
> > 
> > ghc does not currently make any attempts to provide and use a
> > mapping from the Int* Haskell types onto equivalent C types.
> > Why? Mainly because an Int8 is just represented as a differently
> > boxed Int# - i.e., there's no sized Ints at the level of
> > unboxed types.
> > 
> > You may get some warnings when compiling the above "foo", but
> > the right coercions will be inserted, no?
> 
> It works with gcc on my Pentium, but I think it is pure
> luck.  Unfortunately, I don't have a C reference manual at
> the moment, but I think to recall that C doesn't do any
> coercions during parameter passing -- it *definitely* won't
> do any coercions if you don't supply a function prototype.
> It works on my box only because gcc on the Pentium always
> pushes a full 4-byte word even if you only pass a
> character.  
> 

The type promotions that apply when passing params in C
are those that apply when assigning, i.e.,

    void shorty(short x);
    short s; int i;

    s = i;
    shorty(i);

I'm not so sure that it wouldn't work without prototypes,
K&R C managed fine without them. However, maybe modern
ABIs do now assume the presence of parameter type info
to get things right all the time..

> This may prove quite tricky to define in the FFI spec in a
> portable manner -- but I guess, you are already aware of
> that. 
> 

Yes, it probably won't work with a native codegen either.
It needs to be addressed at some stage by ghc.

> BTW, I saw in some of the extended libraries that the Hugs
> code uses "<libname>.so" arguments for the external
> locations.  I was wondering whether it wouldn't be more
> portable if the external location could be specified without
> the file suffix `.so'.  The suffix may depend on the OS;
> omitting it in the foreign declaration, would allow the FFI
> to add the standard suffix of the OS.  Of course, when the
> name refers to a standard library, this name is probably
> also OS dependent, but in the case where the library is part
> of the package that includes the Haskell code, it might be
> possible to save some of the ugly preprocessor directives.
> 

Indeed - I believe Alastair faintly agrees with this, just
that he didn't get around to implementing it. I'll add
something about this to the spec - thanks for bringing
it up.

--Sigbjorn

Reply via email to