"Manuel M. T. Chakravarty" wrote:
> Some bits & pieces:
> >    * After playing around with this module, I think that it is a
> >      Good Thing (tm) that ...OffAddr use element offsets and not
> >      byte offsets. It makes instance declarations of the following
> >      form much easier:
> >
> >         instance Marshalable a => Marshalable (Foo a) where ...
> Why?  You have `sizeOf'.

OK, I'm going to be more concrete: Suppose you have a 3-dimensional
polymorphic vector. A possible instance with element offsets would be:

-------------------------------------------------------------------
data Vec3 a = Vec3 a a a

instance Marshalable a => Marshalable (Vec3 a) where
   sizeOf    (Vec3 x _ _) = 3 * sizeOf x
   alignment (Vec3 x _ _) = alignment x

   indexOffAddr buf off = 
      let [x, y, z] = map (indexOffAddr buf) [3*off .. 3*off + 2]
      in Vec3 x y z

   readOffAddr buf off = do
      [x, y, z] <- mapM (readOffAddr buf) [3*off .. 3*off + 2]
      return $ Vec3 x y z

   writeOffAddr buf off (Vec3 x y z) =
      zipWithM_ (writeOffAddr buf) [3*off ..] [x, y, z]
-------------------------------------------------------------------

Now suppose that byte offsets are used instead. In this case you
have to use sizeOf in the definitions of indexOffAddr/readOffAddr to
calculate the addresses of consecutive elements. But to use sizeOf,
you have to conjure up an (irrelevant) element of type `a', and I was
unable to come up with a solution to this. OK, that doesn't mean that
it is impossible, but I'd like to see some code before I'm convinced.
:-)  Note that writeOffAddr is not a problem, you can use e.g.
`sizeOf x' here.

> [...] You should also get them from `./configure'.  I guess that
> would be possible by using a struct like
> 
>   struct {char c; long int x:8};
> 
> or something like that in the C2HS_CHECK_ALIGNOF test.
> (Haven't tried it yet, but looks plausible, doesn't it :-)

It looks plausible but, alas, that won't work. Quoting Harbison/Steele
("C - A reference manual"), section 5.6.5:

   The address operator & may not be applied to bit-field components,
   since many computers cannot address arbitrary-sized fields directly.

C2HS_CHECK_ALIGNOF uses & indirectly.

> [malloc code]
> How about letting our favourite Mega Hack(tm) - autoconf -
> do the job?
> 
>   C2HS_CHECK_SIZEOF(size_t,$SIZEOF_INT)
> 
> and then use a similar mechanism as C->HS's `configure.in'
> to compute a Haskell type for it.

Slowly, but surely, configure rewrites most of my binding before
ghc gets its hand on it...   :-}

> [...] So how about calling this library `FFI'? (Where exactly the
> `Int' and `Word' stuff should go remains a matter for discussion.)

`FFI' sounds good to me. I don't have a strong opinion about Int and
Word, as long as FFI re-exports them both.

> We should maybe found a `Standard Haskell FFI Task Force' or so
> [...]

This would make sense if people apart from Manuel and Sigbjorn exist
who have called more than C's `sin' from Haskell.   :-)
Hello, anybody there...?

Cheers,
   Sven
-- 
Sven Panne                                        Tel.: +49/89/2178-2235
LMU, Institut fuer Informatik                     FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen              Oettingenstr. 67
mailto:[EMAIL PROTECTED]            D-80538 Muenchen
http://www.informatik.uni-muenchen.de/~Sven.Panne

Reply via email to