least reachable city

master
nihonium 2 years ago
parent 74f5dbb620
commit a31509d093
No known key found for this signature in database
GPG Key ID: 0251623741027CFC

@ -1,15 +1,25 @@
module LeastReachableCity where module LeastReachableCity(dijkstra, leastReachableCity) where
import Types import Types
import qualified Data.Map as Map import qualified Data.Map as Map
import qualified Data.Set as Set import qualified Data.Set as Set
-- Well, it's just a magic number, because it's too much hassle to implement type like "Len val | Infinity"
-- TODO: get graph radius and use this number as infinity
infinity :: Len infinity :: Len
infinity = 999999 :: Len infinity = 999999 :: Len
leastReachableCity :: Graph -> Len -> (Point, Int)
leastReachableCity graph mileage = foldl (\(p, n) (p', n') ->
if n' < n then (p',n')
else (p, n))
(-1, infinity) [(city, countReachableCities $ dijkstra city graph) | city <- Set.toList $ fst $ countVertices graph] where
countReachableCities :: Distances -> Int
countReachableCities distances = Map.foldl (\n val -> if (val <= mileage) && (val /= 0) then n + 1 else n) 0 distances
dijkstra :: Point -> Graph -> Distances dijkstra :: Point -> Graph -> Distances
dijkstra start graph = dijkstra' start graph visited_init to_visit_init distances_init where dijkstra start graph = dijkstra' start graph visited_init to_visit_init distances_init where
-- Helper -- Helper (so we don' need to call dijkstra initializing empty visited, to_visit etc)
dijkstra' :: Point -> Graph -> Vertices -> Vertices -> Distances -> Distances dijkstra' :: Point -> Graph -> Vertices -> Vertices -> Distances -> Distances
dijkstra' start graph visited to_visit distances = if Set.null to_visit dijkstra' start graph visited to_visit distances = if Set.null to_visit
then then
@ -22,9 +32,9 @@ dijkstra start graph = dijkstra' start graph visited_init to_visit_init distance
(Set.union (Set.delete start to_visit) $ findNotVisitedNeighbours graph visited start) (Set.union (Set.delete start to_visit) $ findNotVisitedNeighbours graph visited start)
(updateDistances graph start distances) (updateDistances graph start distances)
-- Other -- Other
to_visit_init = (Set.insert start $ Set.empty :: Set.Set Point) to_visit_init = (Set.insert start $ Set.empty :: Vertices)
distances_init = (infinityDistances start $ countVertices graph) distances_init = (infinityDistances start $ snd $ countVertices graph)
visited_init = (Set.empty :: Set.Set Point) visited_init = (Set.empty :: Vertices)
updateDistances :: Graph -> Point -> Distances -> Distances updateDistances :: Graph -> Point -> Distances -> Distances
updateDistances graph point distances = snd $ Map.foldrWithKey decideMin ((point, Map.findWithDefault (-1) point distances), Map.empty :: Distances) distances where updateDistances graph point distances = snd $ Map.foldrWithKey decideMin ((point, Map.findWithDefault (-1) point distances), Map.empty :: Distances) distances where
@ -42,13 +52,13 @@ findMinNotVisited to_visit distances = fst $ Set.foldl (\(p, l) p' -> case Map.l
(Just l') -> if l' < l then (Just l') -> if l' < l then
(p', l') (p', l')
else (p,l)) else (p,l))
(-1, maxBound) to_visit (-1, infinity) to_visit
infinityDistances :: Point -> Int -> Distances infinityDistances :: Point -> Int -> Distances
infinityDistances point n = Map.fromList $ (point, 0) : [(x, infinity) | x <- [1..n], x /= point] infinityDistances point n = Map.fromList $ (point, 0) : [(x, infinity) | x <- [1..n], x /= point]
countVertices :: Graph -> Int countVertices :: Graph -> (Vertices, Int)
countVertices graph = snd $ foldl f (Set.empty :: Set.Set Point, 0) graph where countVertices graph = foldl f (Set.empty :: Vertices, 0) graph where
f :: (Vertices, Int) -> Node -> (Vertices, Int) f :: (Vertices, Int) -> Node -> (Vertices, Int)
f (vertices, n) (Node (a, b, _)) = f (vertices, n) (Node (a, b, _)) =
let aIsNotMember = not $ Set.member a vertices let aIsNotMember = not $ Set.member a vertices

@ -0,0 +1,9 @@
4
1 2 10
1 4 2
1 3 3
3 2 5
2 4 6
4 5 4
5 3 1

@ -2,7 +2,7 @@ module Main where
import System.IO import System.IO
import System.Environment import System.Environment
import System.Directory
import qualified Data.Map as Map import qualified Data.Map as Map
import qualified Data.Set as Set import qualified Data.Set as Set
@ -21,21 +21,16 @@ main = do
argv <- getArgs argv <- getArgs
filename <- if not $ null argv then do filename <- if not $ null argv then do
putStrLn $ "Trying to read file " ++ "\"" ++ head argv ++ "\""
head <$> getArgs head <$> getArgs
else do else do
error "Not enough arguments,\nusage: main [filename]" putStrLn "Usage: ./lrc [filename]\nNow defaulting to file \"data\""
return "data"
content <- readFile filename content <- readFile filename
let mileage = read $ head $ lines content :: Len let mileage = read $ head $ lines content :: Len
let graph = readGraph $ tail content let graph = readGraph $ tail content
--let dist = findNeighbours 1 graph let (city, n) = leastReachableCity graph mileage
--print $ findNotVisitedNeighbours graph (Set.fromList [1,3]) 2 putStrLn $ "The least reachable city is " ++ (show city) ++ " (" ++ (show n) ++ " city/ies is/are reachable)"
print $ dijkstra 1 graph
--print $ updateDistances graph 2 (Map.fromList [(1, 100), (2, 1), (3, 200)])
--print $ infinityDistances 1 4
--print $ findMinNotVisited (Set.fromList [1, 2, 3] :: Set.Set Int) (Map.fromList [(1, 123), (2, 114), (3, 115)])
{- For parsing graph using content of the file -} {- For parsing graph using content of the file -}
parseStrNode :: [String] -> Node parseStrNode :: [String] -> Node