[Haskell-Cafe] FFI and foreign function returning a structure

shelarcy shelarcy at capella.freemail.ne.jp
Tue Mar 1 23:58:15 EST 2005


I think this is relation to my problem.

I wnant to write Haskell interface to FFmpeg. So first, I try to port
output_example.c to Haskell. But output_example.c's wants to initialize
structure like this,


void write_audio_frame(AVFormatContext *oc, AVStream *st)
{
      int out_size;
      AVCodecContext *c;
      AVPacket pkt;
      av_init_packet(&pkt);

      c = &st->codec;

      get_audio_frame(samples, audio_input_frame_size, c->channels);

      pkt.size= avcodec_encode_audio(c, audio_outbuf, audio_outbuf_size,
samples);

      pkt.pts= c->coded_frame->pts;
      pkt.flags |= PKT_FLAG_KEY;
      pkt.stream_index= st->index;
      pkt.data= audio_outbuf;

      /* write the compressed frame in the media file */
      if (av_write_frame(oc, &pkt) != 0) {
          fprintf(stderr, "Error while writing audio frame\n");
          exit(1);
      }
}

then I need to return a structure.

But I know that :

On Wed, 02 Mar 2005 14:45:54 +1100, Ben Lippmeier
<Ben.Lippmeier at anu.edu.au> wrote:
> No. The way data is organised in memory is dramatically different in  
> Haskell when compared with C. You need to write functions to read in  
> each field in turn and then "reconstruct" the structure on the Haskell  
> side.
>
> It's a tedious process. My advice is that if you have a lot of  
> structures to read, write a (simple) preprocessor to generate the  
> marshalling code.. that's what I did.


so I wrote a code like this,
(This use hsc2hs to write "read and write each field".)

-----------------------------------------------------------------------------
-- -*- mode: haskell -*-
{-# OPTIONS -fglasgow-exts #-}

#include <avformat.h>
#include <avcodec.h>

module FFmpeg
where

import Foreign

data CAVPacket = CAVPacket {pktPts :: !(#type int64_t), pktDts :: !(#type
int64_t),
                              pktDatas :: !(Ptr (#type uint8_t)), pktSize ::
!Int, pktStreamIndex :: !Int,
                              pktFlags :: !Int, pktDuration :: !Int}
                              deriving (Eq,Show)

instance Storable CAVPacket where
    peek p   = do{ pts <- (#peek AVPacket, pts) p; dts <- (#peek AVPacket,
dts) p;
                   datas <- (#peek AVPacket, data) p; size <- (#peek
AVPacket, size) p;
                   stream_index <- (#peek AVPacket, stream_index) p; flags
<- (#peek AVPacket, flags) p;
                   duration <- (#peek AVPacket, duration) p;
                   return $! CAVPacket pts dts datas size stream_index flags
duration }
    poke p (CAVPacket pts dts datas size stream_index flags duration)
              = do{(#poke AVPacket, pts) p pts; (#poke AVPacket, dts) p dts;
                   (#poke AVPacket, data) p datas; (#poke AVPacket, size) p
size;
                   (#poke AVPacket, stream_index) p stream_index ; (#poke
AVPacket, flags) p flags;
                   (#poke AVPacket, duration) p duration}
    sizeOf _  = (#size AVPacket)
    -- I don't confident this value.
    alignment _ = 7


av_init_packet :: IO (Ptr CAVPacket)
av_init_packet =
      alloca $ \pkt -> do
          c_av_init_packet pkt
          return pkt


foreign import ccall unsafe "av_init_packet"
    c_av_init_packet :: Ptr CAVPacket -> IO ()
-----------------------------------------------------------------------------

but ghc-6.2.2 said :

FFmpeg.o(.text+0x44):fake: undefined reference to `av_init_packet' .

Of cource, this problem is only here, ghc can refers to other C function
by FFI. And if I don't pass the link option to ghc, then ghc's refer
problem message is normaly, like this :

c:/ghc/ghc-6.2.2/libHSrts.a(Main.o)(.text+0x87):Main.c: undefined
reference to `__stginit_ZCMain'


Where is a problem of my code?


-- 
shelarcy <shelarcy capella.freemail.ne.jp>
http://page.freett.com/shelarcy/


More information about the Haskell-Cafe mailing list