module Exercise_7 where import Data.List import Data.Maybe import Data.Function (on) import Data.Bifunctor import Control.Applicative import Control.Monad {-WETT-} -- find the distance to vertex x findDist :: Eq a => a -> [(Integer, a)] -> Maybe Integer findDist x = fmap fst . find ((== x) . snd) bellmanFord :: Eq a => [(Integer, (a, a))] -> a -> [(Integer, a)] -> [(Integer, a)] -- All edges have been relaxed once bellmanFord [] _ ds = ds -- if the distance of v is 0 and v is the starting node, then append the updated distance in front of the distance list -- if distv is 0 and vertex v is s, then update the distance -> if there is an edge where s is referencing itself, then it will be added in trancl by optimal_dist, so the smaller edge weight one will be taken bellmanFord ((w, (u, v)):es) s ds = bellmanFord es s $ if isJust newDist && (isNothing distv || (distv == Just 0 && v == s) || maybe False (< fromJust distv) newDist) then (fromJust newDist, v) : ds else ds -- if the vertex u is the starting vertex, then the shortest distance is 0, as we are dealing with non-negative weights where distu = if u == s then Just 0 else findDist u ds distv = findDist v ds -- the new distance from u to v newDist = (+ w) <$> distu trancl :: Eq a => [(Integer,(a,a))] -> [(Integer, (a,a))] trancl [] = [] trancl [x] = [x] -- Remove bigger weight duplicates in the list -- there might be already a shorter edge in the optimal_dist list, so it must be conatenated in front for rmdup to remove the bigger ones trancl rs = nubBy ((==) `on` snd) $ sortOn fst $ optimal_dist ++ concatMap sssp vertices where -- duplicate edges might exist -> find the shortest one optimal_dist = sortOn fst rs -- gather all vertices into a list vertices = nub . uncurry (++) . unzip . map snd $ optimal_dist -- single source shortest path by bellman ford run for each vertex -- the generated list by the iteration has to be reversed, as the updated distance lists are in the back (because of iterate) - the bellman ford algorithm includes a general loop, which is simulated by take and iterate sssp s = map (\(d , t) -> (d , (s, t))) $ concat $ reverse $ take (length vertices) $ iterate (bellmanFord (filter ((== s) . fst . snd) optimal_dist ++ optimal_dist) s) [] -- the distances with format (d, t) where d is the distance to vertex t from s have to be mapped ^^ This filter right here is to insert all edges (u, v) where u = s to calculate the distance in cycles {-TTEW-}