Tail Recursion within the IO Monad

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

On May 16, 2007, at 12:23 , Rob Hoelz wrote:
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...
(=<<)? -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

"Brandon S. Allbery KF8NH"
On May 16, 2007, at 12:23 , Rob Hoelz wrote:
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...
(=<<)?
Thanks for the reply; I can't believe I missed that one! But while looking over the documentation, completely humbled, I discovered sequence, which allows me to write my code cleanly! Thanks for the help! -Rob

Rob Hoelz wrote:
"Brandon S. Allbery KF8NH"
wrote: On May 16, 2007, at 12:23 , Rob Hoelz wrote:
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... (=<<)?
Thanks for the reply; I can't believe I missed that one! But while looking over the documentation, completely humbled, I discovered sequence, which allows me to write my code cleanly! Thanks for the help!
sequence still isn't tail-recursive, although sequence_ is. If you want a tail-recursive sequence, the only way to do it is like this: sequence' :: [IO a] -> IO [a] sequence' ms = do let as = map unsafePerformIO ms foldr seq (return ()) as return as although that's likely to be a lot slower, too. Cheers, Simon

On Thu, May 17, 2007 at 11:22:34AM +0100, Simon Marlow wrote:
sequence still isn't tail-recursive, although sequence_ is. If you want a tail-recursive sequence, the only way to do it is like this:
sequence' :: [IO a] -> IO [a] sequence' ms = do let as = map unsafePerformIO ms foldr seq (return ()) as return as
sequence :: Monad m => [m a] -> m [a] sequence ms = reverse `liftM` sequence' [] ms sequence' l [] = return l sequence' l (m:ms) = m >>= \x -> sequence' (x:l) ms Stefan

Stefan O'Rear wrote:
On Thu, May 17, 2007 at 11:22:34AM +0100, Simon Marlow wrote:
sequence still isn't tail-recursive, although sequence_ is. If you want a tail-recursive sequence, the only way to do it is like this:
sequence' :: [IO a] -> IO [a] sequence' ms = do let as = map unsafePerformIO ms foldr seq (return ()) as return as
sequence :: Monad m => [m a] -> m [a] sequence ms = reverse `liftM` sequence' [] ms
sequence' l [] = return l sequence' l (m:ms) = m >>= \x -> sequence' (x:l) ms
In a moment of insanity, I discounted reverse because I thought it had linear stack usage, but of course it can be written (and is) to use only linear heap. You're quite right, sorry for unnecessarily suggesting the use of unsafePerformIO :-) Simon

Rob Hoelz wrote:
item <- linked_list_getdata listPtr next <- linked_list_next listPtr cStr <- peek item hStr <- peekCString cStr t <- linkedListToStringList next return (hStr : t)
item <- linked_list_getdata listPtr next <- linked_list_next listPtr cStr <- peek item hStr <- peekCString cStr fmap (hStr :) linkedListToStringList next
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:
I think you're over-valuing tail recursion. It's not an exciting thing in a lazy language the way it is in a pure language. The change I made above may not result in particularly better code, although it is more concise.
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...
Yes, that's what >>= and =<< are. hStr <- peekCString =<< peek =<< linked_list_getdata listPtr fmap (hStr :) linkedListToStringList =<< linked_list_next listPtr ...or even... liftM2 (:) (peekCString =<< peek =<< linked_list_getdata listPtr) (linkedListToStringList =<< linked_list_next listPtr) It's really a matter of taste.... you could turn the arrows round, too. Jules
participants (5)
-
Brandon S. Allbery KF8NH
-
Jules Bean
-
Rob Hoelz
-
Simon Marlow
-
Stefan O'Rear