Help: writing ffi bindings to a C library

Ronald Legere rjljr2@yahoo.com
Sat, 31 May 2003 07:25:25 -0700 (PDT)


One strategy is to wrap that funtion in another
function (in C) that encapsulates the 'typical'
call you want to make. THen import this function into
haskell. 
In any event, start with something simpler, to 
get the hang of it. Try to write a function (in C)
that adds two integers,or prints something and import
that in to haskell. There are some examples floating
around to get you started, but I can't
find them at the moment on the CVS tree.  Anyone?

Also, read "Tackling the awkward squad" (Google it)

Ron

--- "Bayley, Alistair"
<Alistair_Bayley@ldn.invesco.com> wrote:
> So...
> 
> I'm still trying to write this Oracle OCI ffi
> binding. Can anyone tell me
> how to declare the Haskell type for this function:
> 
> sword   OCIEnvCreate (OCIEnv **envp, ub4 mode, dvoid
> *ctxp,
>                  dvoid *(*malocfp)(dvoid *ctxp,
> size_t size),
>                  dvoid *(*ralocfp)(dvoid *ctxp,
> dvoid *memptr, size_t
> newsize),
>                  void   (*mfreefp)(dvoid *ctxp,
> dvoid *memptr),
>                  size_t xtramem_sz, dvoid
> **usrmempp);
> 
> Note that when I use it, I'm passing 0 (NULL) into
> almost all of the args,
> so the usage in C is typically:
> 
> 	rc = OCIEnvCreate(&envhp, OCI_DEFAULT, 0, 0, 0, 0,
> 0, 0);
> 
> i.e. I don't care about most of the args, so that
> should make the Haskell
> declaration simpler. Some of the arguments are
> pointers to functions, for
> example.
> 
> What I can't figure out is how to declare the type
> of the first arg. Is is
> Ptr (Ptr OCIEnv) ?
> 
> Here's what I have so far (not much, I know):
> 
> > module Main where
> > import Foreign
> > import Foreign.C.Types
> > import Foreign.C.String
> > import Foreign.Ptr
> 
> > data OCIEnv
> 
> > foreign import ccall "oci.h OCIEnvCreate"
> ociEnvCreate :: Ptr OCIEnv ->
> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int
> 
> 
> 
> -----Original Message-----
> From: Ronald Legere [mailto:rjljr2@yahoo.com]
> Sent: 21 May 2003 20:32
> To: 'haskell-cafe@haskell.org'
> Subject: Re: Help: writing ffi bindings to a C
> library
> 
> 
> Agreeing with David, but I like to use 
>  types rather than (). YOu can do this because,
> in ghc, you can write:
> data Blah
> with no rhs, and it is understood to be an 'opaque'
> type.  Ghc beleives any claims you make about
> passing Ptr Blah back and forth to C  in your
> foreign
> import declarations <* Grin *>.
> 
> As for passing structures back and forth, and
> accessing the components, you can do it from Haskell
> or from the "c-side"... I can send you a sample of
> doing it from haskell if you wish.
> 
> Ron
> 
> 
> --- David Roundy <droundy@abridgegame.org> wrote:
> > On Wed, May 21, 2003 at 04:27:10PM +0100, Bayley,
> > Alistair wrote:
> 
> > > construct a Ptr a? What type should "a" be?).
> > 
> > Unless you actually need to ever access their
> > contents, I'd just define the
> > pointers to be of type Ptr (), essentially like a
> > void * pointer in C.  No
> > need to use Storable if they are only ever
> accessed
> > through C functions
> > (which I would hope would be the case).
> > --
> 
> 
>
*****************************************************************
> The information in this email and in any attachments
> is 
> confidential and intended solely for the attention
> and use 
> of the named addressee(s). This information may be 
> subject to legal professional or other privilege or
> may 
> otherwise be protected by work product immunity or
> other 
> legal rules.  It must not be disclosed to any person
> without 
> our authority.
> 
> If you are not the intended recipient, or a person 
> responsible for delivering it to the intended
> recipient, you 
> are not authorised to and must not disclose, copy, 
> distribute, or retain this message or any part of
> it.
>
*****************************************************************
> 
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe


=====
-------------------------------------
Ronald Legere  rjljr2@yahoo.com
-------------------------------------

__________________________________
Do you Yahoo!?
Yahoo! Calendar - Free online calendar with sync to Outlook(TM).
http://calendar.yahoo.com