99 questions/Solutions/81

From HaskellWiki
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.

(**) Path from one node to another one

Write a function that, given two nodes a and b in a graph, returns all the acyclic paths from a to b.

import List (elem)

paths :: Eq a => a -> a -> [(a,a)] -> [[a]]
paths a b g = paths1 a b g []

paths1 :: Eq a => a -> a -> [(a,a)] -> [a] -> [[a]]
paths1 a b g current = paths2 a b g current [ y | (x,y) <- g, x == a ]

paths2 :: Eq a => a -> a -> [(a,a)] -> [a] -> [a] -> [[a]]
paths2 a b g current []	| a == b = [current++[b]]
			| otherwise = []
paths2 a b g current (x:xs) | a == b = [current++[b]] 
			    | elem a current = []
			    | otherwise = (paths1 x b g (current++[a])) ++ (paths2 a b g current xs)

paths :: Int -> Int -> [(Int , Int)] -> Int paths start end zs = let (xs,ys) = partition (\(_,z) -> z == end ) zs

                     in  map (++ [ end] )  ( concat . map (\(e, _) -> if e == start then start else paths start e  ys) $  xs )

This solution uses a representation of a (directed) graph as a list of arcs (a,b).