99 questions/Solutions/81: Difference between revisions
< 99 questions | Solutions
No edit summary |
(yet another solution using monadic behavior of lists) |
||
(6 intermediate revisions by 5 users not shown) | |||
Line 21: | Line 21: | ||
This solution uses a representation of a (directed) graph as a list of arcs (a,b). | This solution uses a representation of a (directed) graph as a list of arcs (a,b). | ||
---- | |||
Here is another implementation using List's monadic behavior | |||
<haskell> | |||
import Data.List (partition) | |||
pathsImpl :: Eq a => [a] -> a -> a -> [(a, a)] -> [[a]] | |||
pathsImpl trail src dest clauses | |||
| src == dest = [src:trail] | |||
| otherwise = do | |||
let (nexts, rest) = partition ((==src) . fst) clauses | |||
next <- nexts | |||
pathsImpl (src:trail) (snd next) dest rest | |||
paths :: Eq a => a -> a -> [(a, a)] -> [[a]] | |||
paths src dest clauses = map reverse (pathsImpl [] src dest clauses) | |||
</haskell> | |||
---- | |||
Here is another recursive implementation | |||
<haskell> | |||
paths :: Eq a =>a -> a -> [(a,a)] -> [[a]] | |||
paths source sink edges | |||
| source == sink = [[sink]] | |||
| otherwise = [ | |||
source:path | edge<-edges, (fst edge) == source, | |||
path<-(paths (snd edge) sink [e|e<-edges, e/=edge]) | |||
]; | |||
</haskell> | |||
---- | |||
yet another solution using monadic behavior of lists | |||
<haskell> | |||
paths :: (Eq a) => a -> a -> [Arc a] -> [[a]] | |||
paths source sink arcs | |||
| source == sink = [[source]] | |||
| otherwise = map (map fst) $ aux source [] | |||
where | |||
aux current pathSoFar = | |||
let nextEdges = filter ((== current) . fst) arcs | |||
notCyclic = not . (\(_,t) -> (t == source) || (elem t $ map snd pathSoFar)) | |||
noCycles = filter notCyclic nextEdges | |||
in noCycles >>= \(f,t) -> do | |||
if (t == sink) then return $ pathSoFar ++ (f,t):[(t,t)] | |||
else aux t (pathSoFar ++ [(f,t)]) | |||
</haskell> | |||
[[Category:Programming exercise spoilers]] |
Latest revision as of 20:50, 30 July 2021
(**) 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)
This solution uses a representation of a (directed) graph as a list of arcs (a,b).
Here is another implementation using List's monadic behavior
import Data.List (partition)
pathsImpl :: Eq a => [a] -> a -> a -> [(a, a)] -> [[a]]
pathsImpl trail src dest clauses
| src == dest = [src:trail]
| otherwise = do
let (nexts, rest) = partition ((==src) . fst) clauses
next <- nexts
pathsImpl (src:trail) (snd next) dest rest
paths :: Eq a => a -> a -> [(a, a)] -> [[a]]
paths src dest clauses = map reverse (pathsImpl [] src dest clauses)
Here is another recursive implementation
paths :: Eq a =>a -> a -> [(a,a)] -> [[a]]
paths source sink edges
| source == sink = [[sink]]
| otherwise = [
source:path | edge<-edges, (fst edge) == source,
path<-(paths (snd edge) sink [e|e<-edges, e/=edge])
];
yet another solution using monadic behavior of lists
paths :: (Eq a) => a -> a -> [Arc a] -> [[a]]
paths source sink arcs
| source == sink = [[source]]
| otherwise = map (map fst) $ aux source []
where
aux current pathSoFar =
let nextEdges = filter ((== current) . fst) arcs
notCyclic = not . (\(_,t) -> (t == source) || (elem t $ map snd pathSoFar))
noCycles = filter notCyclic nextEdges
in noCycles >>= \(f,t) -> do
if (t == sink) then return $ pathSoFar ++ (f,t):[(t,t)]
else aux t (pathSoFar ++ [(f,t)])