qforeign-0.62

Marcin 'Qrczak' Kowalczyk qrczak at knm.org.pl
Sun Nov 19 14:01:20 EST 2000


An updated version is at <http://qrczak.ids.net.pl/qforeign-0.62.tar.gz>.
Major changes from 0.60:

* 'make install' implemented. Installs as package qforeign.
* iconv support is more robust. Works with Konstantin Chuguev's
  iconv implementation too.
* Definitions of character predicates are more correct, after
  discussions on linux-utf8 and unicode mailing lists.
* glue-hsc: #const_str construct added
* Curses interface improved.
* Pcap interface added (incomplete).
* Works under ghc-4.08, 4.08.1, 4.09 (before-ghci-branch). No Unicode or
  'make install' with ghc < 4.09 (I just need to use FFI with ghc-4.08*).
* Things that went into ghc are removed from here (Ptr, Storable).
  glue-hsc from here is used only for ghc < 4.09.

------------------------------------------------------------------------

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.

Unfortunately versions with explicit length need to be separate. Most
code will use those without the length, but in case a C library allows
handling strings with '\0' characters embedded by passing the length
explicitly, the more common versions are not enough.

Their implementation will use ISO-8859-1 for now. Their interface
is not constrained to the case where the length of the C string
translated from Haskell is the same as of the original, nor vice
versa. Eventually they will do the conversion between Unicode and the
default local encoding and there will be separate versions allowing
to supply another conversion.

------------------------------------------------------------------------

After adding the above, the interface provided by ghc alone should be
sufficient to do almost everything currently possible with FFI, without
the need of using private ghc's bits and with reasonable efficiency.

Apart from that, my library contains some convenience functions.
I hope the meaning is clear from names and types. Perhaps some of
them are worth inclusion into ghc?

    ----------------------------------------------------------------
    -- 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.
    
    ----------------------------------------------------------------
    -- Haskellish interface to memcpy and memmove.

    copyArray :: Storable a => Ptr a -> Ptr a -> Int -> IO ()
    copyBytes :: Ptr a -> Ptr a -> Int -> IO ()

    moveArray :: Storable a => Ptr a -> Ptr a -> Int -> IO ()
    moveBytes :: Ptr a -> Ptr a -> Int -> IO ()
    
    ----------------------------------------------------------------
    -- Lifting many functions taking a continuation (which takes a value)
    -- to a single function taking a continuation (which takes a list).
    -- This is tricky to write each time by hand.

    -- Convenient for sequencing alloca and with functions.
    -- For example to allocate an array of C strings.

    sequenceCont :: [(a -> res) -> res] -> ([a] -> res) -> res
    mapCont      :: (a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> res

    ----------------------------------------------------------------
    -- Perhaps unsafePerformIO and unsafeInterleaveIO should be
    -- reexported from module Foreign too. Foreign import may import
    -- pure functions anyway, but in that case the wrapper cannot do
    -- memory allocation etc.

    unsafePerformIO    :: IO a -> a
    unsafeInterleaveIO :: IO a -> IO a

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

-- 
 __("<  Marcin Kowalczyk * qrczak at knm.org.pl http://qrczak.ids.net.pl/
 \__/
  ^^                      SYGNATURA ZASTÊPCZA
QRCZAK





More information about the FFI mailing list