"Sigbjorn Finne (Intl Vendor)" <[EMAIL PROTECTED]> wrote,

> Manuel M. T. Chakravarty writes: 
> > 
>  ...
> > 
> > Unfortunately, the implementation in GHC 4.01 is still a bit 
> > buggy.  Two bugs are reproduced by the following program
> > 
> >   import Int (Int8, intToInt8, Int16, intToInt16, Int32, intToInt32,
> >           Int64, intToInt64)
> > 
> >   foreign import ccall "" "foo" 
> >              foo :: Int8 -> Int16 -> Int32 -> Int64 -> IO ()
> > 
> >   --(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.)

> >   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.  

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

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.

Thanks,

Manuel

Reply via email to