[Haskell-cafe] Tail Recursion within the IO Monad

Rob Hoelz hoelz at wisc.edu
Wed May 16 12:23:43 EDT 2007


Hello everyone,

You may have seen my message about how I'm writing a binding to a C
library.  This is another question related to that.

So, let's say I have a linked list implemented in C.  Here's what its
definition looks like:

struct __linked_list {
    void *data;
    struct __linked_list *next;
};

typedef struct __linked_list linked_list_t;

void *linked_list_getdata(linked_list_t *);
linked_list_t *linked_list_next(linked_list_t *);

Keep in mind, this is just a segment.

So using the Haskell FFI, I import these into my .hsc file:

data LinkedList = LL (Ptr linked_list_t)

foreign import ccall unsafe "linked_list.h" 
    linked_list_getdata :: Ptr LinkedList -> IO Ptr a

foreign import ccall unsafe "linked_list.h"
    linked_list_next :: Ptr LinkedList -> IO Ptr LinkedList

So now that that's done, I attempt to write a Ptr LinkedList ->
[String] function (assuming the given LinkedList is holding c strings):

linkedListToStringList :: Ptr LinkedList -> IO [String]
linkedListToStringList listPtr =
    if listPtr == nullPtr
        then 
	    return []	    
        else do
            item <- linked_list_getdata listPtr
	    next <- linked_list_next listPtr
            cStr <- peek item
            hStr <- peekCString cStr
            t <- linkedListToStringList next
            return (hStr : t)

This is just ugly...making the recursive call first, THEN consing the
value on?  However, this is the only way I could think of doing it.  I
figure there are three possibilities from here:

1) Leave this code alone, as GHC will optimize it because it's smart.
2) There's a way to more effectively write this code!  Change it!
3) Roll my own optimization.

I know how to do 3, but I'd rather avoid it.  I guess I'm looking for
an answer to 2, but if 1 is true, that'd be ok too.  Could anyone give
me a hand?

And as long as I'm asking, is there some kind of monadic function
composition operator?  I'd like to clean up the above with something
like peekCString . peek . linked_list_getdata...

Many thanks,
Rob Hoelz


More information about the Haskell-Cafe mailing list