Re: [Haskell-cafe] lazily traversing a foreign data structure

2007-10-26 Thread Graham Fawcett
On 10/25/07, Derek Elkins [EMAIL PROTECTED] 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'.

(It was an 'aha' moment for me to realize Haskell would let me choose
strict or lazy evaluation by passing in a different 'valve'
function. Powerful stuff.)

Thanks again,
Graham
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] lazily traversing a foreign data structure

2007-10-26 Thread Brent Yorgey
On 10/26/07, Graham Fawcett [EMAIL PROTECTED] wrote:

 On 10/25/07, Derek Elkins [EMAIL PROTECTED] 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] lazily traversing a foreign data structure

2007-10-26 Thread Graham Fawcett
On 10/26/07, Brent Yorgey [EMAIL PROTECTED] wrote:
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.

Beginner's luck. ;-) I see the unfold similarity, but yes, it doesn't
seem a good fit here.

 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...

Not at all -- it's terse but the data flow is clear.

Thanks very much,
Graham
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] lazily traversing a foreign data structure

2007-10-25 Thread Graham Fawcett
Hi folks,

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. I've wrapped the two relevant foreign
functions:

firstKey :: Ptr Db - IO (Maybe String)
nextKey  :: Ptr Db - String - IO (Maybe String)

NextKey takes a key, and returns the next one. Either function could
return Nothing, since the db may have 0 or 1 keys.

Given these, is it possible to write a (simple) function

allKeys :: Ptr Db - IO [String]

that lazily fetches the keys? (Or, an idiomatic way of achieving the
same end?)

Thanks,

Graham
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] lazily traversing a foreign data structure

2007-10-25 Thread Derek Elkins
On Thu, 2007-10-25 at 11:30 -0400, Graham Fawcett wrote:
 Hi folks,
 
 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. I've wrapped the two relevant foreign
 functions:
 
 firstKey :: Ptr Db - IO (Maybe String)
 nextKey  :: Ptr Db - String - IO (Maybe String)
 
 NextKey takes a key, and returns the next one. Either function could
 return Nothing, since the db may have 0 or 1 keys.
 
 Given these, is it possible to write a (simple) function
 
 allKeys :: Ptr Db - IO [String]
 
 that lazily fetches the keys? (Or, an idiomatic way of achieving the
 same end?)

Just use unsafeInterleaveIO in the obvious definition to read all the
keys.  That said, it's not called unsafeInterleaveIO for no reason.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] lazily traversing a foreign data structure

2007-10-25 Thread Graham Fawcett
On 10/25/07, Derek Elkins [EMAIL PROTECTED] 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. I've wrapped the two relevant foreign
  functions:
 Just use unsafeInterleaveIO in the obvious definition to read all the
 keys.  That said, it's not called unsafeInterleaveIO for no reason.


Ah thanks, that's just the thing. Safety warnings duly noted.

Graham
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] lazily traversing a foreign data structure

2007-10-25 Thread Brandon S. Allbery KF8NH


On Oct 25, 2007, at 13:04 , Derek Elkins wrote:


Just use unsafeInterleaveIO in the obvious definition to read all the
keys.  That said, it's not called unsafeInterleaveIO for no reason.


I think it might actually be safe in this case:  if the file changes  
out from under your lazy I/O, far worse things happen in the gdbm  
library layer than in the unsafe-IO Haskell layer.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] lazily traversing a foreign data structure

2007-10-25 Thread Ryan Ingram
On 10/25/07, Brandon S. Allbery KF8NH [EMAIL PROTECTED] wrote:
 I think it might actually be safe in this case:  if the file changes
 out from under your lazy I/O, far worse things happen in the gdbm
 library layer than in the unsafe-IO Haskell layer.

Right, but if you do something like

do
  keys - getKeysLazy db
  [.. some computation A here that may or may not evaluate all the keys ..]
  addRow db newRow
  [.. some other computation B that uses the key list ..]

does B see the new row or not?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] lazily traversing a foreign data structure

2007-10-25 Thread Brandon S. Allbery KF8NH


On Oct 25, 2007, at 14:21 , Ryan Ingram wrote:


On 10/25/07, Brandon S. Allbery KF8NH [EMAIL PROTECTED] wrote:

I think it might actually be safe in this case:  if the file changes
out from under your lazy I/O, far worse things happen in the gdbm
library layer than in the unsafe-IO Haskell layer.


Right, but if you do something like

do
  keys - getKeysLazy db
  [.. some computation A here that may or may not evaluate all the  
keys ..]

  addRow db newRow
  [.. some other computation B that uses the key list ..]

does B see the new row or not?


My point is that there's no promise for that one *even in C*.  (The  
equivalent construct being adding the new row before nextKey has  
failed.)


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] lazily traversing a foreign data structure

2007-10-25 Thread Graham Fawcett
On 10/25/07, Brandon S. Allbery KF8NH [EMAIL PROTECTED] wrote:
 On Oct 25, 2007, at 14:21 , Ryan Ingram wrote:
  Right, but if you do something like
 
  do
keys - getKeysLazy db
[.. some computation A here that may or may not evaluate all the
  keys ..]
addRow db newRow
[.. some other computation B that uses the key list ..]
 
  does B see the new row or not?

 My point is that there's no promise for that one *even in C*.  (The
 equivalent construct being adding the new row before nextKey has
 failed.)

Just so. Deletions, for example, may change the ordering of the
internal hashtable (according to the gdbm manpage), making some keys
unfindable by a series of nextKey calls.

(If I were writing a serious module, and not just noodling around, I
imagine I'd document this, and let the user decide whether strict
evaluation was required.)

Thanks again to all,
Graham
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] lazily traversing a foreign data structure

2007-10-25 Thread Ryan Ingram
On 10/25/07, Brandon S. Allbery KF8NH [EMAIL PROTECTED] wrote:
 My point is that there's no promise for that one *even in C*.  (The
 equivalent construct being adding the new row before nextKey has
 failed.)

Sure, but in C, it's highly likely that the full evaluation of the key
list happens in one place, that's just how code tends to get written.
That said, in C code, I've often seen bugs where code called during
the iteration of a collection modifies that collection; that's
something that has been really refreshing to get away from when
writing Haskell.

With the unsafeInterleaveIO example, the pure keylist could get
deferred indefinitely, stored in a data structure, partially evaluated
at many different times against many different versions of the
database, etc., and it's not necessarily clear to the person who just
has a [Key] that they are doing deferred calls to nextKey like it
tends to be in C.

It's safe if you use it in a predictable fashion, and in a real API
I'd probably provide getKeys and unsafeLazyGetKeys and let the
programmer decide.

  -- ryan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe