never executed always true always false
    1 {-|
    2 Module:      Y2015.D09
    3 Description: Advent of Code Day 09 Solutions.
    4 License:     MIT
    5 Maintainer:  @tylerjl
    6 
    7 Solutions to the day 09 set of problems for <adventofcode.com>.
    8 -}
    9 
   10 {-# LANGUAGE FlexibleContexts #-}
   11 
   12 module Y2015.D09
   13     ( longestRoute
   14     , routeParser
   15     , shortestRoute
   16     )
   17 where
   18 
   19 import Y2015.Util (intParser)
   20 
   21 import           Data.List           (permutations)
   22 import           Data.Map            ((!), Map, fromListWith, keys, singleton, union)
   23 import qualified Data.Map as         Map
   24 import           Data.Maybe          (mapMaybe)
   25 import           Safe                (maximumMay, minimumMay)
   26 import           Text.Parsec         (many1, optional, skipMany1, string)
   27 import           Text.Parsec.Char    (endOfLine, letter, space)
   28 import           Text.Parsec.String  (Parser)
   29 
   30 type City     = String
   31 type Distance = Int
   32 data Route    = Route City City Distance
   33               deriving (Show, Eq)
   34 
   35 -- |Parsec parser for the 'Route' type
   36 routeParser :: Parser [Route] -- ^ 'Route' parser
   37 routeParser = many1 (parseRoute <* optional endOfLine)
   38 
   39 parseRoute :: Parser Route
   40 parseRoute = Route <$> many1 letter <* pSep "to"
   41                    <*> many1 letter <* pSep "="
   42                    <*> intParser
   43     where pSep s = many1 space *> string s *> skipMany1 space
   44 
   45 -- Each key represents the start, with possible destination values,
   46 -- which are keys to the distance to that destination.
   47 -- We flip destinations to fully express all available routes.
   48 drawMap :: [Route] -> Map City (Map City Distance)
   49 drawMap = fromListWith union . map toMap . concatMap backTrack
   50     where toMap (Route x y d) = (x, singleton y d)
   51           backTrack (Route x y d) = [ Route x y d
   52                                     , Route y x d ]
   53 
   54 -- |Finds the shortest route given a list of routes
   55 shortestRoute :: [Route]        -- ^ List of route flight paths
   56               -> Maybe Distance -- ^ Possibly shortest distance
   57 shortestRoute = minimumMay . chart
   58 
   59 -- |Finds the longest route given a list of routes
   60 longestRoute :: [Route]        -- ^ List of route flight paths
   61              -> Maybe Distance -- ^ Possibly longest distance
   62 longestRoute = maximumMay . chart
   63 
   64 -- Create the map structure, gather a permutation of all cities,
   65 -- and build the distance for each permutation. There's a chance
   66 -- some cities will be unroutable (a partition on the routes), so
   67 -- there's a possibility we may return an empty list (this is an internal
   68 -- function though, so we account for that in the above wrapper
   69 -- functions.)
   70 chart :: [Route] -> [Distance]
   71 chart routes = mapMaybe (plot . (zip <*> tail)) . permutations . keys $ worldMap
   72     where worldMap      = drawMap routes
   73           plot          = fmap sum . mapM travel
   74           travel (a, b) | a `Map.member` worldMap = Map.lookup b (worldMap ! a)
   75                         | otherwise               = Nothing