HSFFIG/Examples

From HaskellWiki
< HSFFIG(Redirected from HSFFIG Examples)
Jump to navigation Jump to search

Berkeley DB binding

On this page, you can find code snippets demonstrating correspondence between C code and Haskell code using hsffig.


Beginning of the program. The C code includes all the necessary header files.

#include <sys/types.h>

#include <stdio.h>
#include <stdlib.h>
#include <string.h>

#include "db.h"

The Haskell code just imports the DB_H module auto-generated by hsffig:

-- A Haskell implementation of the Berkeley DB example program (example.cs)

{-# OPTIONS -fglasgow-exts #-}

module Main where

import DB_H

import Control.Monad

The main program begins:

#define	DATABASE "access.db"

int
main()
{

Same in Haskell:

main = do

  let dbperm = fromIntegral $ c_S_IRUSR .|. c_S_IWUSR .|. c_S_IRGRP .|. c_S_IWGRP .|. c_S_IROTH

  putStrLn "Test of Autogenerated BerkeleyDB Binding"

Here, the file access permissions constants are OR'ed to obtain the correct binary mask. Names of the constants are as imported from <stat.h>, prefixed with "c_". Application of fromIntegral is needed to be able to pass this value to foreign functions.


The C program declares local variables with types. The Haskell program does not need this: all necessary "variables" are alloca 'ed as necessary when foreign functions are called.

	DB *dbp;
	DBT key, data;
	int ret, t_ret;

The first step: create the database handle.

	/* Create the database handle and open the underlying database. */
	if ((ret = db_create(&dbp, NULL, 0)) != 0) {
		fprintf(stderr, "db_create: %s\n", db_strerror(ret));
		exit (1);
	}

The C db_create function requires a pointer to the database handle variable to return the result into. The variable was declared earlier as DB *dbp.

-- Create the database handle and open the underlying database.

  (ret, dbp) <- alloca $ \pdbp -> do
    r <- f_db_create pdbp nullPtr 0
    h <- peek pdbp
    return (r,h)

  putStrLn $ "DB Handle created: " ++ (show ret)

In Haskell however, the same may be achieved with using the alloca function. It acts similarly to C 's alloca, reserving memory space upon entry into the "action" and freeing the space after the action completes. So, alloca $ \pdbp -> do allocates necessary space to fit the value f_db_create places in, being called within the "action" (whatever follows after do. The pdbp identifier will be bound to the pointer to that space. Note that it is not needed to specify the type for pdbp (this may be some clumsy identifier hsffig assigns internally). Type inference is driven by the FFI declarations autogenerated by hsffig from its input, C header file(s).

The return code of f_db_create is bound to r. Next, h is bound to whatever f_db_create placed into the memory at the pointer provided to it via pdbp: peek retrieves the value.

Returned is a tuple containing the completion code (which may be analyzed for errors), and the database handle.

At this point, the Haskell program does not analyze for database opening error: this will be shown in next steps.


The next step: open the database:

	if ((ret = dbp->open(dbp,
	    NULL, DATABASE, NULL, DB_BTREE, DB_CREATE, 0664)) != 0) {
		dbp->err(dbp, ret, "%s", DATABASE);
		goto err;
	}

Haskell code:

  ret <- withCString "access.db" $ \dbname -> do
    r <- (dbp ==> X_open) dbp
                          nullPtr
                          dbname
                          nullPtr
                          (fromIntegral e_DB_BTREE)
                          (fromIntegral c_DB_CREATE)
                          dbperm
    return r

  putStrLn $ "Database created: " ++ (show ret)
  when (ret /= 0) $ do errmsg <- f_db_strerror ret >>= peekCString
                       putStrLn $ "Error: " ++ errmsg

The string with database filename is passed to the action containing call to the database open function. Pointer to that function is stored in the database handle structure initialized at the previous step. So, (dbp ==> X_open) retrieves that pointer and applies the arguments: the function is called after that.

Note the difference in getting the error message text. The dbp -> err function is variadic, and it is not possible to call it from Haskell code. However the f_db_strerror function is OK. Its result is marshalled back to Haskell by calling peekCString.

This example program does not use I/O exceptions (in real life program they are of course necessary).


The next step: write a key/data pair into the database:

	/* Initialize key/data structures. */
	memset(&key, 0, sizeof(key));
	memset(&data, 0, sizeof(data));
	key.data = "fruit";
	key.size = sizeof("fruit");
	data.data = "apple";
	data.size = sizeof("apple");

	/* Store a key/data pair. */
	if ((ret = dbp->put(dbp, NULL, &key, &data, 0)) == 0)
		printf("db: %s: key stored.\n", (char *)key.data);
	else {
		dbp->err(dbp, ret, "DB->put");
		goto err;
	}

The Haskell code doing the same:

-- Initialize key/data structures.

  ret <- alloca $ \dbkey ->
         alloca $ \dbdata ->
         withCStringLen "fruit" $ \fruit ->
         withCStringLen "apple" $ \apple -> do
           (dbkey,V_data) <-- fst fruit
           (dbkey,V_size) <-- (fromIntegral $ snd fruit)
           (dbdata,V_data) <-- fst apple
           (dbdata,V_size) <-- (fromIntegral $ snd apple)

-- Store a key/value pair.

           r <- (dbp ==> X_put) dbp nullPtr dbkey dbdata 0
           return r

  putStrLn $ "Data item stored: " ++ (show ret)
  when (ret /= 0) $ do errmsg <- f_db_strerror ret >>= peekCString
                       putStrLn $ "Error: " ++ errmsg

Using alloca in Haskell is similar to opening a new C block statement (within curly brackets) and declaring local variables in it: their identifiers are visible only within the block statement. Same way here: dbkey, dbdata, fruit, apple are not visible outside. While fruit and apple are constants (string literals) from the C function standpoint, dbkey and dbdata are true variables: C functions may change their contents; alloca allocates a whole structure on the imaginary stack. Dbkey and dbdata contain pointers to DBT 's (Berkeley DB structure types to hold keys and values) allocated by alloca. So dbkey in the Haskell example is equivalent to &key in the C example, etc.


The next step: retrieve the value stored at the preceding step:

	/* Retrieve a key/data pair. */
	if ((ret = dbp->get(dbp, NULL, &key, &data, 0)) == 0)
		printf("db: %s: key retrieved: data was %s.\n",
		    (char *)key.data, (char *)data.data);
	else {
		dbp->err(dbp, ret, "DB->get");
		goto err;
	}

Haskell code:

-- Retrieve a key/value pair.

  (ret,
   ks,
   vs) <- alloca $ \dbkey ->
          alloca $ \dbdata ->  
          withCStringLen "fruit" $ \fruit -> do
            (dbkey,V_data) <-- fst fruit
            (dbkey,V_size) <-- (fromIntegral $ snd fruit)
            r <- (dbp ==> X_get) dbp nullPtr dbkey dbdata 0
            ksc <- (dbkey --> V_data) :: IO CString
            kss <- dbkey --> V_size
            if (r == 0) 
              then do dsc <- (dbdata --> V_data) :: IO CString
                      dss <- dbdata --> V_size
                      ks <- peekCStringLen (ksc, fromIntegral kss)
                      vs <- peekCStringLen (dsc ,fromIntegral dss)
                      return (r, ks, vs)
              else return (r, undefined, undefined)

  putStrLn $ "Data item retrieved: " ++ (show ret)

  if (ret == 0) 
    then putStrLn $ "Value is: " ++  vs
    else do errmsg <- f_db_strerror ret >>= peekCString
            putStrLn $ "Error: " ++ errmsg

The C code does not re-initialize the key structure: it was not changed by the database store operation. The Haskell code has to do this again because previous dbkey was lost. It can however be avoided if alloca $ \dbkey -> was placed in the very beginning of the program: this is same as enclosing part of the C code in curly brackets and declaring local variables within.

Once (dbp ==> X_get) fills in the DBT structure dbdata points at, returned string is marshalled back to Haskell by calling peekCStringLen.

Possible error code is processed as shown before.


The next step: delete the value stored:

	/* Delete a key/data pair. */
	if ((ret = dbp->del(dbp, NULL, &key, 0)) == 0)
		printf("db: %s: key was deleted.\n", (char *)key.data);
	else {
		dbp->err(dbp, ret, "DB->del");
		goto err;
	}

Haskell code:

-- Delete a key/value pair.

  ret <- alloca $ \dbkey ->
         withCStringLen "fruit" $ \fruit -> do
           (dbkey,V_data) <-- fst fruit
           (dbkey,V_size) <-- (fromIntegral $ snd fruit)
           r <- (dbp ==> X_del) dbp nullPtr dbkey 0
           return r

  putStrLn $ "Data item deleted: " ++ (show ret)
  when (ret /= 0) $ do errmsg <- f_db_strerror ret >>= peekCString
                       putStrLn $ "Error: " ++ errmsg

Nothing really new here: (dbp ==> X_del) removes the key-value pair.


The rest of the example program retrieves the previously deleted key-value pair again, and returns with error because the pair is no longer in the database.



User:DimitryGolubovsky