Let's get this finished

Manuel M. T. Chakravarty chak at cse.unsw.edu.au
Sat Jan 6 05:58:26 EST 2001


Sven Panne <Sven.Panne at informatik.uni-muenchen.de> wrote,

> I think we all agree now that malloc & friend can be written in H98 +
> FFI, so the only question is how they should be implemented in
> hslibs. The variant which uses local definitions instead of pattern
> type signatures is nicer IMHO because it *is* H98 and given GHC's
> optimizations, it doesn't make any performance difference. In general
> we should make hslibs as H98-conforming as possible and remove most
> GHCisms. For performance there's always #ifdef (well, at least if we
> consider piping Haskell sources through cpp as "standard"/H98).

If hslibs is meant to be used with systems other than ghc,
too - which I think was the idea - there is no choice but to
rewrite it into H98.  But I guess this is essentially up to
Mr. HsLibs aka SimonM.

> -- MarshalArray ------------------------------------------------------
> 
[...]
> 
>     !!!!! The current MarshalUtils uses
>     !!!!!        peekArray :: Storable a => Ptr a -> Int -> IO [a]
>     !!!!! but the signature below looks more consistent with peekArray0:
>     peekArray        :: Storable a =>         Int -> Ptr a -> IO [a]
>     peekArray0       :: (Storable a, Eq a) => a   -> Ptr a -> IO [a]

Sounds reasonable to me.

> -- MarshalString -----------------------------------------------------
> 
>     !!!!! I'm with Marcin here: Let's keep things simple and do not
>     !!!!! provide an opaque type CString here. We can't guess all
>     !!!!! possible uses, so a type synonym would be the right thing
>     !!!!! here. Using a pointer/length combo is quite common, too,
>     !!!!! so this deserves another type synonym. Note that some
>     !!!!! functions below look a bit strange, but symmetry rulez! :-)
>     !!!!! Charset conversions are a diff{erent,icult} story and should
>     !!!!! be handled by a separate module, so only the well-known
>     !!!!! ignore-the-upper-half variants are given here.
> 
>     type CString    = Ptr CChar
>     type CStringLen = (CString, Int)

Hmmm, yes, although pointer/length pairs are not very common
in C and this module is a language dependent module (and so
should be called `MarshalCString').

> -- MarshalError ------------------------------------------------------
> 
>    !!!!! Haven't thought very deeply about this, but Marcin's QErrors
>    !!!!! probably looks OK after a little polishing (use strerror,
>    !!!!! provide a more complete throwXXX family, ...). And remember:
>    !!!!! errno *is* a thread-local thing.  :-)

But SimonM said that he doesn't want to make errno Haskell
thread local...

> -- MarshalConv -------------------------------------------------------
> 
>    !!!!! I can't see a compelling reason for this module, neither what
>    !!!!! exactly should belong here. ISO C defines a mapping to 0/1,
>    !!!!! which can easily be captured by fromBool/toBool (in MarshalUtils
>    !!!!! below). Maybe is handled there, too.

Ok - as this module doesn't seem to enjoy much support,
let's just drop it.  I can do my only little weird
experiments in C2HS.

> -- MarshalUtils ------------------------------------------------------
> 
>     fromBool   :: Num a => Bool -> a
>     fromBool = fromIntegral . fromEnum
> 
>     toBool   :: Num a => a -> Bool
>     toBool = (/= 0)

Ok, let's do it like this, then.

>     withObject       :: Storable a => a -> (Ptr a -> IO b) -> IO b

BTW, can't we just use `with' now.  IIRC, the only reason
Marcin used `withObject' was because of a clash with the
implicit parameter extension.  This has been changed now,
hasn't it?

>     !!!!! Example usages:
>     !!!!!    do ...
>     !!!!!       mbInt    <- maybeNull peek        ptr1
>     !!!!!       mbString <- maybeNull peekCString ptr2
>     !!!!!       .....
>     !!!!!       maybeNothing withObject Nothing        $ \ptr -> ...
>     !!!!!       maybeNothing withCString (Just "foo!") $ \ptr -> ...
>     !!!!!
>     !!!!! Does anybody have better names for these two functions?
>     !!!!! They sound OK for me, but I'm not a native speaker...
> 
>     maybeNull :: (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
>     maybeNull f ptr | ptr == nullPtr = return Nothing
>                     | otherwise      = liftM Just $ f ptr
> 
>     maybeNothing :: (a -> (Ptr b -> IO c) -> IO c) -> (Maybe a -> (Ptr b -> IO c) -> IO c)
>     maybeNothing = maybe ($ nullPtr)

This is also along the lines of what Marcin proposed.  So,
let's use it.

>     !!!!! Do we really need this?
>     indexPtr         :: Storable a => Ptr a -> Int -> Ptr a

I didn't need it yet.  Marcin, what did you use the function
for?

> As Manuel already wrote it's a good idea to leave C2HS's marshX
> routines out and to re-export all the modules above, but should this
> be done via a new module Marshal or should Foreign do this? Should
> Marshal re-export Foreign or vice-versa? Hmmm...

I was thinking of an extra module mainly because the
MarshalXXX code is system independent - in contrast to the
code in `Foreign'.  However, we may also just let Foreign
do the whole job.  Thinking about it again, I doubt that
anybody will ever import one module, but not the other -
so, let's make Foreign export the whole lot.

There is one exception: MarshalCString shouldn't be
re-exported by Foreign (like CTypes).

> And just a final topic which really should be settled:
> "Marshal" or "Marshall"??   :-}

I would have taken the latter, but I think, SimonM
originally proposed the name MarshalUtils with one "l" and
as he is the native speaker...

Cheers,
Manuel




More information about the FFI mailing list