qforeign-0.62

Manuel M. T. Chakravarty chak at cse.unsw.edu.au
Thu Nov 23 02:44:15 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.

>     ----------------------------------------------------------------
>     -- 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.

>     ----------------------------------------------------------------
>     -- 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?

>     ----------------------------------------------------------------
>     -- Mutexes. They allow making non-reentrant functions thread-safe,
>     -- without importing the whole Concurrent stuff. They are also
>     -- implementable in a Haskell compiler without concurrency, and
>     -- that's why I think they should be exposed by the FFI instead of
>     -- using Concurrent things directly.
>     
>     -- errno handling is not reentrant, even though it is reentrant
>     -- in native C threads. Instead of protecting all wrappers for C
>     -- functions which use errno by mutexes, I propose that Haskell
>     -- compilers which provide concurrency should be responsible for
>     -- maintaining a thread-local C errno variable.
>     
>     data Mutex
>     newMutex   :: IO Mutex
>     threadSafe :: Mutex -> IO a -> IO a

This sounds like a good idea to me.

Cheers,
Manuel




More information about the FFI mailing list