qforeign-0.62
Simon Marlow
simonmar at microsoft.com
Tue Nov 28 05:55:07 EST 2000
> qrczak at knm.org.pl (Marcin 'Qrczak' Kowalczyk) wrote,
>
> > qforeign got smaller because of changes in ghc, but what is ghc is
> > still a bit incomplete.
> >
> > Most important incompleteness is in string handling. Since ghc's
> > Unicode support is half-baked and it is not yet clear how
> the library
> > interface will look like, I propose adding the following functions
> > to the module Foreign:
> >
> > peekCString :: Ptr CChar -> IO String
> > peekCStringLen :: Ptr CChar -> Int -> IO String
> >
> > withCString :: String -> (Ptr CChar -> IO a) -> IO a
> > withCStringLen :: String -> (Ptr CChar -> Int -> IO a) -> IO a
> >
> > newCString :: String -> IO (Ptr CChar)
> > newCStringLen :: String -> IO (Ptr CChar, Int)
> > -- Memory is obtained by malloc and must be freed using free.
>
> I believe that this stuff belongs into the higher-level
> marshalling library. In fact, it should be instances of
> more general routines dealing with lists of Storable
> elements. Similar to how it is done in the C2HS library.
I think Marcin is right in that C Strings are special (unfortunately).
This interface seems reasonable, and simple. Do we have any objections?
> > ----------------------------------------------------------------
> > -- Storable arrays. No new expressiveness, but they are commonly
> > -- used.
> >
> > peekArray :: Storable a => Ptr a -> Int -> IO [a]
> > peekArray0 :: (Storable a, Eq a) => a -> Ptr a -> IO [a]
> >
> > pokeArray :: Storable a => Ptr a -> [a] -> IO ()
> > pokeArray0 :: Storable a => a -> Ptr a -> [a] -> IO ()
> >
> > withObject :: Storable a => a -> (Ptr a -> IO b) -> IO b
> > withArray :: Storable a => [a] -> (Ptr a -> IO b) -> IO b
> > withArray0 :: Storable a => a -> [a] -> (Ptr a -> IO b) -> IO b
> >
> > newObject :: Storable a => a -> IO (Ptr a)
> > newArray :: Storable a => [a] -> IO (Ptr a)
> > newArray0 :: Storable a => a -> [a] -> IO (Ptr a)
> > -- Memory is obtained by malloc and must be freed using free.
>
> This seems to go into the direction that I mentioned above.
Ok. The naming scheme is a little inconsistent: we haven't used
"Object" everywhere (it is just omitted in some places). eg.
malloc :: Storable a => IO (Ptr a)
arguably, withObject and newObject should be named with and new
("Object" is awfully vague and seems redundant anyway).
> > ----------------------------------------------------------------
> > -- Handling errors. Mostly conversion of errno to Haskell's IO
> > -- exceptions.
> >
> > -- Get the current value of C errno.
> > getErrno :: IO Int
> >
> > -- Throw an exception based on function name and given
> error code.
> > throwCError :: String -> Int -> IO a
> > -- Throw an exception based on function name and current errno
> > -- value. Much more common than the above but less general,
> > -- that's why there are two functions.
> > throwErrno :: String -> IO a
> >
> > -- Perform an action and ignore its result. A stupid
> thing but quite
> > -- common, especially after the result was converted to
> exceptions.
> > ignore :: IO a -> IO ()
> >
> > -- Wrappers that convert the result to a possible exception.
> > -- *_EINTR variants repeat the action if there was an error
> > -- and errno == EINTR.
> > throwIf :: (a -> Bool) -> String -> IO a -> IO a
> > throwIf_EINTR :: (a -> Bool) -> String -> IO a -> IO a
> >
> > throwIfMinus1 :: Num a => String -> IO a -> IO a
> > throwIfMinus1_EINTR :: Num a => String -> IO a -> IO a
> > throwIfNull :: String -> IO (Ptr a) -> IO (Ptr a)
> > throwIfNull_EINTR :: String -> IO (Ptr a) -> IO (Ptr a)
>
> Again, this belongs into the higher-level marshalling
> library. Did you have a look at the corresponding routines
> in C2HS?
Your ifRaise family is fairly similar (except that it doesn't deal
explicitly with C's errno and EINTR). I don't particularly mind what
these functions are called or where they live, as long as we have them!
Admittedly the functions above are C-specific and should probably go
into a C-specific library on top of Foreign. CForeign anyone?
Meanwhile we should have some non-C-specific error-handling utilities in
Foreign.
Cheers,
Simon
More information about the FFI
mailing list