The Curious Case of the Disappearing PQ

Quite stuck debugging something…

Might anyone know why my priority queue is simply empty in the DijkstraState monad when in the initialState it is most definitely not empty?

This is my first time working with Data.Heap, but everything typechecks; furthermore, when I trace the priority queue as part of the initial state, it looks fine:

initialState: (fromList [(0,(Node {coord = (0,0), weight = 2},0,E))],fromList [((0,0),0)])

But the trace in the monad shows an empty heap :confused: :

pq in modifiedDijkstra: fromList []

What’s weird is the other part of the initial state, the distance map, shows up as expected. :thinking:


Meta-question for the experienced folks: what else would you do to debug this further? I’m thinking maybe some sort of property test, but not quite sure how to formulate something like that.

I wonder if the trace is only working on the last iteration and hence the pq is empty. The lazy state monad is quite counterintuitive.

E.g.

ghci> import Debug.Trace
ghci> import Control.Monad.State
ghci> execState (trace "foo" (pure ()) *> put 1) 0 :: Int
1
ghci> execState (trace "foo" (pure ()) *> pure ()) 0 :: Int
foo
0

Ah, interesting! I did add other traces to subsequent parts of the modifiedDijkstra function (the thinking being some of these will have to get traced, eventually, even if evaluated lazily (?)), but these traces never fire:

modifiedDijkstra :: Grid -> DijkstraState
modifiedDijkstra grid = do
    (pq, dists) <- get
    -- BUG: pq is empty for some reason!
    traceM ("pq in modifiedDijkstra: " ++ show pq)
    case H.view pq of
        Nothing -> do
            traceM "pq is empty!"
            return ()
        Just ((dist, (node, steps, dir)), pq')
            | dist > (dists M.! coord node) -> do
                -- This trace never gets hit!
                traceM "pq is populated!"
                put (pq', dists)
                modifiedDijkstra grid
            | otherwise -> do
                -- This trace never gets hit!
                traceM "pq is populated!"
                let neighborTraversals = traverseNeighbors grid node steps dir
                    (pq'', dists') = foldr (relaxEdge dist) (pq', dists) neighborTraversals
                put (pq'', dists')
                modifiedDijkstra grid

Additionally, the distance map is only populated with the single, initial entry (which is why I was thinking nothing is ever happening in modifiedDijkstra).

Perhaps, I can try switching to the strict version and seeing what happens.

Try making your program smaller. E.g. try removing the recursion and see if the problem persists.

1 Like

Yep, did that earlier – that’s what helped me formulate the hypothesis that the initial iteration is supplied with an empty pq.

When I use Control.Monad.State.Strict, I see the pq populated as I expect! Thank you, @jaror . :pray:

(As a beginner, I have to say…this laziness business is mind-bending! :sweat_smile: )

1 Like

Some light vacation reading:

1 Like

As an expert, it’s mind-bending too! I strongly suggest staying away from the lazy state monad. You will avoid a lot of headaches.

2 Likes

It’s actually the combination of effects and laziness which makes matters awkward:

…as you’ve just discovered, and many others initially did when ST s a was introduced (it was originally lazy). Sometimes that combination is quite potent e.g. the demand-driven implementation of depth-first search described in section 5.2 (page 16 of 51) of State in Haskell (1995).

But the confusion over space leaks, effects not occurring as expected, et al eventually brought forth the change in ST s a from being lazy to strict by default (with the lazy version relegated to a different module). This Lazy/Strict dual-module approach has since appeared in various other Haskell libraries, no doubt for the same reasons.

1 Like