Space leak? Was: [Haskell] Queues / Lists with unbound tails

Claus Reinke claus.reinke at talk21.com
Wed May 12 17:04:33 EDT 2004


>   shiftQ front q = let q' = q . (front:)
>                    in (head (q' []), trace "tail" . tail . q' )

the problem with this was that new queues get constructed under 
lambda-abstractions (binding the not yet available input), but current
Haskell implementations do not reduce under lambdas. the reductions 
involved in those constructions are thus repeated every time the 
queue is shifted/inspected (the trace shows the repeated applications 
of the nested tail operations in a sequence of shiftQs).

[[from the "don't try this at home" (nor anywhere else) category:-]]

if we're certain that our queue will be used single-threadedly, we
can get around this limitation using single-read variables.

first, here's a way to "open" an abstraction without applying it to
a concrete argument - we just apply it  to a hole which we promise 
to fill with an argument later on. openFct f returns both the body
of f (possibly with holes) and a variant of f that will fill the holes
and reuse the body:

{-# NOINLINE openFct #-}
openFct f = unsafePerformIO $ do
            mv <- newEmptyMVar
            let arg  = unsafePerformIO $ takeMVar mv
                body = f arg
            return ( body
                   , \arg->unsafePerformIO $ do
                           putMVar mv arg
                           return body)

using this, we can modify shiftQ - we can't apply a queue twice 
anymore, but we know that q' is non-empty, so the back end of q' 
does not depend on the missing front end, and we can use head
on the open body of q:

shiftQ'' front q = let (body,q') = openFct $ q . (front:)
                   in (head body,trace "tail" . tail . q')

this way, the evaluation of the construction operations is shared
(as the trace confirms).

just in case you hadn't noticed ;-) this construction is "unsafe"!

in particular, once we've opened an abstraction, we should only
apply it once. here's an example of what can happen otherwise:

    Prelude Main> let (_,f) = openFct tail
    Prelude Main> f "hihi"
    "ihi"
    Prelude Main> f "hoho"
    "ihi"
    Prelude Main> f "huhu"
    "*** Exception: thread blocked indefinitely

cheers,
claus

ps. using tryPutMVar would be a bit nicer, but still problematic.




More information about the Haskell mailing list