ffi & recursive data types

Alastair Reid reid@cs.utah.edu
Mon, 2 Apr 2001 12:26:38 -0600


> I'm new in ffi stuff and tools like greencard.
> Everything was working ok, until I wanted to:
>
> translate a haskell recursive data type(list,trees,etc) into
> a corresponding C type and back again.
>
> How can I do this?

If you want to see how to convert Haskell lists into arrays, look at the string support in StdDIS.gc or look at the handling of
lists of <almost anything> in the various greencard examples out there (like the X11 support in the HGL).

If you want to convert haskell data structures to isomorphic C data structures, you want to write a C constructor function which
will allocate and initialize an object corresponding to each Haskell constructor and then write a Haskell function which will copy
the data structure from Haskell to Haskell (this is a warmup) and then convert it to copy from Haskell to C.

And to convert back, you define functions with which to implement "pattern matching" on the C objects and use those to modify your
copy function again.

For example:

  data T = T1 Int | T2 Int T T

->

  enum T_tag { T1, T2 }
  struct T1 { int tag; int f1 }
  struct T2 { int tag; int f1; union T* f2; union T* f3 }
  union T { T1 t1; T2 t2 }

  union T* mkT1(int f1) { ... malloc ... }
  union T* mkT2(int f1, union T* f2, union T* f3) { ... malloc ... }
  int fromT1(union T* t, int *f1_out) {
    if (t->t1.tag == T1) {
      *f1_out = t->t1.tag;
      return 1;
    } else {
      return 0;
    }
  }
  int fromT2(...) { ... }

  data T_C = ...
  %fun mkT1 :: Int -> IO T_C
  %fun mkT2 :: Int -> T_C -> T_C -> IO T_C

  %fun fromT1 :: T_C -> IO (Maybe Int)
  % details a bit tricky... may need to be done in 2 steps...
  %fun fromT2 :: T_C -> IO (Maybe (Int,T_C,T_C)
  % ditto

  copy_H2H :: T -> IO T
  copy_H2H (T1 f1) = return (T1 f1)
  copy_H2H (T2 f1 f2 f3) = do
    f2' <- copy_H2H f2
    f3' <- copy_H2H f3
    return (T2 f1 f2' f3')

  copy_H2C :: T -> IO T_C
  copy_H2C (T1 f1) = mkT1 f1
  copy_H2C (T2 f1 f2 f3) = do
    f2' <- copy_H2C f2
    f3' <- copy_h2C f3
    mk_T2 f1 f2' f3'

  -- can probably be coded more elegantly using maybe, fromMaybe, Maybe monad, etc.
  copy_C2H :: T_C -> IO T
  copy_C2H t =
    case fromT1 t of
      Just f1 -> return (T1 f1)
      Nothing -> case fromT2 t of
                   Just (f1,f2,f3) -> return (T2 f1 f2 f3)
                   Nothing         -> error "copy_C2H: invalid T_C object"

More advanced versions of this method might:

o avoid the IO monad if the T_C objects are truly immutable
o convert data structures lazily (using unsafeInterleaveIO)
o preserve sharing within T_C objects (using pointer equality tests)
o preserve sharing within T objects... Ummm, no, that's probably not legal.


Hope this helps,

--
Alastair Reid