FFI Help
Manuel M T Chakravarty
chak at cse.unsw.edu.au
Mon Jun 9 04:54:46 EDT 2003
"Simon Peyton-Jones" <simonpj at microsoft.com> wrote,
> Would it be worth mentioning or amplifying this point in the FFI spec,
> or perhaps in an accompanying Appendix/Commentary of examples and FAQs?
> Else someone else is going to trip over it sooner rather than later.
Good point. I think this is central enough to include it
into the spec itself. Hence, I have added the following
text to the end of 4.1.1 (where the import declarations for C
are described):
It should be noted that a static foreign declaration that does not import an
address (i.e., where \gterm\& is not used in the specification of the external
entity) always refers to a C function, even if the Haskell type is
non-functional. For example,
%
\begin{quote}
\begin{verbatim}
foreign import ccall foo :: CInt
\end{verbatim}
\end{quote}
%
refers to a pure C function \code{foo} with no arguments that returns an
integer value. Similarly, if the type is \code{IO CInt}, the declaration
refers to an impure nullary function. If a Haskell program needs to access a
C variable \code{bar} of integer type,
%
\begin{quote}
\begin{verbatim}
foreign import ccall "&" bar :: Ptr CInt
\end{verbatim}
\end{quote}
%
must be used to obtain a pointer referring to the variable. The variable can
be read and updated using the routines provided by the module \code{Storable}
(cf.\ Section~\ref{sec:Storable}).
I hope that this clarifies the point.
Thanks,
Manuel
> | -----Original Message-----
> | From: haskell-cafe-admin at haskell.org
> [mailto:haskell-cafe-admin at haskell.org] On Behalf Of Glynn
> | Clements
> | Sent: 04 June 2003 08:32
> | To: Matthew Donadio
> | Cc: haskell-cafe at haskell.org
> | Subject: Re: FFI Help
> |
> |
> | Matthew Donadio wrote:
> |
> | > I am just starting to experiment with FFI, and am running into a
> | > problem. I was to create an FFI to the lgamma(3) found in many of
> the
> | > newer libm implementations. My code follows the sig.
> | >
> | > The lgamma function works. The gamma function core dumps (I am
> using
> | > ghc 5.04.3) on me. gdb reports a SIGSEGV in signgam(), but I'm not
> sure
> | > why. I believe that I need to use the monad because signgam is only
> | > valid after lgamma returns.
> | >
> | > Does anyone have an idea what I am doing wrong?
> | >
> | > Thanks.
> | >
> | > --
> | > Matthew Donadio <m.p.donadio at ieee.org>
> | >
> | > > module Gamma (gamma, lgamma) where
> | >
> | > > import System.IO.Unsafe
> | >
> | > > foreign import ccall "math.h lgamma" lgammaC :: Double -> IO
> Double
> | > > foreign import ccall "math.h signgam" signgamC :: IO Int
> |
> | signgam is an "int" variable, but this assumes that it is a function
> | of type "int signgam(void)".
> |
> | Write a C wrapper "int get_signgam(void) { return signgam; }" and
> | import that.
> |
> | --
> | Glynn Clements <glynn.clements at virgin.net>
>
>
>
> | Or alternatively, foreign import the address of the int and read it
> | directly with 'peek'.
> |
> | import Foreign
> | ...
> | foreign import ccall "math.h &signgam" signgamC :: Ptr Int32
> | ...
> | gammaIO :: Double -> IO Double
> | gammaIO x = do lg <- lgammaC x
> | s <- peek signgamC
> | return $ fromIntegral s * exp lg
> |
> |
> | Regards,
> | Malcolm
>
>
> _______________________________________________
> FFI mailing list
> FFI at haskell.org
> http://www.haskell.org/mailman/listinfo/ffi
More information about the FFI
mailing list