Is there a route between these two nodes in this directed graph?

Question 4.2 of Cracking the Coding Interview:

Given a directed graph, design an algorithm to find out whether there is a route between two nodes.

Given any node in the graph, we can generate a full list of nodes reachable from that node, by exploring the graph from that node outwards. We can then determine whether a route exists from node n1 to node n2 by generating the full list of nodes reachable from n1, and asking whether n2 is in that list.

To generate the “reachable set” from a node, we partition the graph into three sets: explored nodes, boundary nodes, and the rest. We repeatedly look for new nodes by looking at outgoing edges from nodes in the boundary set. When we’ve looked at all the outgoing edges of a node, we move that node to explored so we don’t look at its edges again. Eventually, our boundary set becomes empty, there are no new nodes to explore, and the explored set is all the reachable nodes.

Here’s an implementation in Haskell:

module DirectedGraphRoute where

import qualified Data.Set as Set
import Data.Set (Set)

type Node = Int
type Edge = (Node,Node)
type Graph = Set Edge

isRoute :: Graph -> Node -> Node -> Bool
isRoute g n1 n2 = Set.member n2 $ reachableSet g n1

reachableSet :: Graph -> Node -> Set Node
reachableSet g n = go Set.empty (Set.singleton n) where
  go explored boundary
    | Set.null boundary = explored
    | otherwise = go newExplored $ Set.fromList [ t | 
                    (f,t) <- Set.toList g, 
                    Set.member f boundary, 
                    not (Set.member t newExplored)
                  ]
                  where newExplored = Set.union explored boundary

One optimization could be to stop as soon as we find n2 while exploring. Another optimization could be to expand from n1 and n2 concurrently (exploring edges in the reverse direction from n2), and stopping as soon as the explored sets overlap.

Tagged #ctci, #programming, #haskell.
👋 I'm Jim, a full-stack product engineer. Want to build an amazing product and a profitable business? Read more about me or Get in touch!

More by Jim

This page copyright James Fisher 2020. Content is not associated with my employer. Found an error? Edit this page.