On 10/26/07, Graham Fawcett <graham.fawcett@gmail.com> wrote:
On 10/25/07, Derek Elkins <derek.a.elkins@gmail.com> wrote:
> On Thu, 2007-10-25 at 11:30 -0400, Graham Fawcett wrote:
> > I'm writing a Gnu DBM module as an exercise for learning Haskell and
> > its FFI. I'm wondering how I might write a function that returns the
> > database keys as a lazy list.
> Just use unsafeInterleaveIO in the obvious definition to read all the
> keys. That said, it's not called unsafeInterleaveIO for no reason.
I got it to work, using unsafeInterleaveIO. Thanks! But I suspect I
might be working too hard to get the result. Is anyone willing to
critique my code?
Given firstKey and nextKey:
firstKey :: DbP -> IO (Maybe String)
nextKey :: DbP -> String -> IO (Maybe String)
I wrote these eager and lazy key-iterators:
allKeys :: DbP -> IO [String]
allKeys = traverseKeys id
unsafeLazyKeys :: DbP -> IO [String]
unsafeLazyKeys = traverseKeys unsafeInterleaveIO
traverseKeys :: (IO [String] -> IO [String]) -> DbP -> IO [String]
traverseKeys valve db = traverse firstKey
where traverse :: (DbP -> IO (Maybe String)) -> IO [String]
traverse func = do nxt <- func db
case nxt of
Nothing -> return []
Just v -> do rest <- valve $
traverse (\db ->
nextKey db v)
return $ v : rest
Intuition suggests there's a higher-order way of writing 'traverse'.
'traverse' is a sort of unfold. Here's the type of unfoldr:
unfoldr :: (b -> Maybe (a,b)) -> b -> [a]
It's not too hard to implement a monadic version, although I don't think it's in the libraries:
unfoldrM :: (Monad m) => (b -> m (Maybe (a,b))) -> b -> m [a]
unfoldrM f b = do
next <- f b
case next of
Just (a, b') -> liftM (a:) (unfoldrM f b')
Nothing -> return []
You can probably see the similarity to traverse. However, the type is different enough from traverse that I don't think it would be that simple to implement traverseKeys in terms of unfoldrM. The fact that traverseKeys uses different functions for the first step and all the rest makes things difficult, too. In the end it looks to me like you're probably better off just implementing traverse directly as you have done, although perhaps someone will find a better way.
I will note, however, that the last few lines of traverse can be written more simply as:
Just v -> liftM (v:) . valve . traverse $ (\db -> nextKey db v)
or even
Just v -> liftM (v:) . valve . traverse . flip nextKey $ v
Perhaps that's going too far for your taste, but the main point is the liftM (v:); instead of extracting 'rest', consing v, and then putting the new list back in IO with 'return', you can just use liftM to apply the cons function inside the monad in the first place.
-Brent