Daniel Fischer wrote:
Am Dienstag, 7. Oktober 2008 20:27 schrieb Andrew Coppin:
Basically, the core code is something like
raw_bind :: (Monad m) => [[x]] -> (x -> m (ResultSet y)) -> m
(ResultSet y)
raw_bind [] f = return empty
raw_bind (xs:xss) f = do
rsYs <- mapM f xs
rsZ <- raw_bind xss f
return (foldr union (cost rsZ) rsYs)
As you can see, this generates all of rsZ before attempting to return
anything to the caller. And I'm really struggling to see any way to
avoid that.
Maybe it is as simple as
raw_bind (xs:xss) f = do
rsYs <- mapM f xs
~rsZ <- raw_bind xss f
return (foldr union (cost rsZ) rsYs)
then rsZ should only be evaluated when it's needed
Ooo... "lazy pattern matching"? Can somebody explain to me, _very
slowy_, exactly what that means?
If I'm doing this right, it seems that
rsZ <- raw_bind xss f
...
desugards to
raw_bind xss f >>= \rsZ -> ...
If I'm not mistaken, the rsZ variable shouldn't be evaluated until
needed *anyway*, so what is lazy pattern matching buying me here?
Also, suppose I stack ResultSetT on top of IO. In that case, "f" is
allowed to perform externally-visible I/O operations. If there really
*is* a way to delay the execution of certain calls until the data is
needed... well that doesn't look right somehow. In fact, it looks like
what I'm trying to do *should* be impossible. :-/ Oh dear...
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe