bindings-common-0.2.2: Low-level library bindings, base package.Source codeContentsIndex
Bindings
Contents
Code facilities
How to wrap a library using this package
Macros
Example
C API
Haskell low level binding
Clean Haskell code
Better interface
Description
Package bindings-common provides many facilities to do low-level FFI to C libraris, in the form of macros and modules. It also sets a base module under which low-level bindings to C libraries can be inserted.
Synopsis
Code facilities
See documentation for module Bindings.Utilities.
How to wrap a library using this package
If you want to write a comprehensive binding to your favorite library, and you want to try this package to see if it suits your needs, you can look at this documentation and then at the source code for Bindings.C, which tries to wrap the full standard C library.
Macros
Starting from version 0.2, package bindings-common provides many hsc2hs macros to easy C binding. Here we list the most important.
Example
We'll take a small piece of C code and wrap it using hsc2hs macros available in bindings-common. Our intention is to show that we can write Haskell code with the help of existing C code, but using a Haskell interface that is not built on the C interface. This is an alternative to the usual style of using adapted versions of native C calls. In our opinion, the style shown here is easier to write and give results that are more confortable to use in Haskell.
C API

This is a small (artificial, naive and ugly) API for UTF-8 coding of characters. Most APIs have better design, but we just want to show how to deal with it.

 #define UNICODE_2_UTF8 1
 #define UTF8_2_UNICODE 2

struct unicode_translator {
   uint32_t unicode;
   uint8_t eight_bits[4];
   int nchars;
 };

void translate (int, struct unicode_translator *);

We use it filling unicode field with an unicode number, and then calling translate with UNICODE_2_UTF8; or filling eight_bits and calling translate with UTF8_2_UNICODE.

Haskell low level binding

Now we make use of hsc2hs macros inside Haskell.

#bindings_num UNICODE_2_UTF8 #bindings_num UTF8_2_UNICODE

#bindings_starttype struct unicode_translator #bindings_field unicode , Word32 #bindings_array_field eight_bits , Word8 , 4 #bindings_field nchars , CInt #bindings_stoptype

#bindings_function translate , CInt -> Ptr Unicode_translator -> IO ()

This gives us a set of declarations as below.

 _UNICODE_2_UTF8 :: (Num a) => a
 _UTF8_2_UNICODE :: (Num a) => a

data Unicode_translator = Unicode_translator {
   unicode_translator'unicode :: Word32,
   unicode_translator'eight_bits :: [Word8],
   unicode_translator'nchars :: CInt
 }

translate :: CInt -> Ptr Unicode_translator -> IO ()
Clean Haskell code

Now we declare a few Haskell utilities that better fit Haskell programming.

 toChar :: (Enum a, Enum b) => a -> b
 toChar = toEnum . fromEnum
 fromChar :: (Enum a, Num b) => a -> b
 fromChar = fromIntegral . fromEnum

unicodeToUtf :: String -> IO String
 unicodeToUtf string = liftM concat $ alloca $ ptrUt ->
   (flip mapM) string $ char -> do
       ut <- peek ptrUt
       poke ptrUt (ut {unicode_translator'unicode = toChar char})
       translate _UNICODE_2_UTF8 ptrUt
       ut <- peek ptrUt
       let nChars = fromIntegral $ unicode_translator'nchars ut
       let eightBits = unicode_translator'eight_bits ut
       return $ (map toChar) $ reverse $ take nChars eightBits

utfToUnicode :: String -> IO String
 utfToUnicode =
  (. (map fromChar)) $
  (. splitCodes) $
  mapM $ c -> do
     let ut = Unicode_translator {
                unicode_translator'nchars = fromIntegral $ length c,
                unicode_translator'eight_bits = reverse $ map fromChar c,
                unicode_translator'unicode = 0
               }
     unicode - with ut $ \ptr - do
         translate _UTF8_2_UNICODE ptr
         liftM unicode_translator'unicode $ peek ptr
     return $ toChar $ unicode
  where
      splitCodes :: [Word8] -> [[Word8]]
      splitCodes [] = []
      splitCodes (a:t) = if (a < 0x80)
        then
          [a]:(splitCodes t)
        else
          let i = findIndex (c -> c  0x80 || c  0xBF) t
              (t1,t2) = maybe ([],t) (flip splitAt t) i
          in (a:t1):(splitCodes t2)

unicodeToUtf and utfToUnicode now use Haskell day-to-day types.

Better interface

Our functions are effect-free.

 toUtf8 :: String -> String
 toUtf8 = unsafePerformIO . unicodeToUtf

fromUtf8 :: String -> String
 fromUtf8 = unsafePerformIO . utfToUnicode

And this is something we can confortably use.

 printAsInt :: String -> IO ()
 printAsInt s = putStrLn $ show $ map fromEnum s

main = do
   let a = Exceo
   printAsInt a
   printAsInt $ toUtf8 a
   printAsInt $ fromUtf8 $ toUtf8 a

Outputs:

 [69,120,99,101,231,227,111]
 [69,120,99,101,195,167,195,163,111]
 [69,120,99,101,231,227,111]
Produced by Haddock version 2.4.2