I remembered about foldl1 !
[advent-of-code-19.git] / advent03 / src / advent03.hs
1 import Data.Text (Text)
2 import qualified Data.Text.IO as TIO
3
4 import Data.Void (Void)
5
6 import Text.Megaparsec hiding (State)
7 import Text.Megaparsec.Char
8 import qualified Text.Megaparsec.Char.Lexer as L
9 import qualified Control.Applicative as CA
10
11 import Data.List (foldl', foldl1')
12 import qualified Data.Map as M
13 import Data.Map ((!))
14
15 import Linear (V2(..), (^+^), (^-^), (*^), (*^))
16
17 data Direction = East | South | West | North deriving (Show, Eq)
18
19 type Location = V2 Int -- x, y
20
21 type Visited = M.Map Location Int
22
23 data Path = Path { _visited :: Visited
24 , _tip :: Location
25 , _currentLength :: Int
26 }
27 deriving (Show, Eq)
28
29 data Segment = Segment { _direction :: Direction
30 , _steps :: Int
31 } deriving (Show, Eq)
32
33
34 main :: IO ()
35 main = do
36 text <- TIO.readFile "data/advent03.txt"
37 let segmentss = successfulParse text
38 let paths = travelAllPaths segmentss
39 -- print $ travelPath $ head segmentss
40 print $ part1 paths
41 print $ part2 paths
42
43 part1 :: [Path] -> Int
44 part1 paths = closest $ crossovers paths
45
46 part2 :: [Path] -> Int
47 part2 paths = shortestPaths $ crossovers paths
48
49
50 closest :: Visited -> Int
51 closest points = snd $ M.findMin $ M.mapWithKey (\k _ -> manhattan k) points
52
53 shortestPaths :: Visited -> Int
54 shortestPaths crossings = minimum $ M.elems crossings
55
56
57 crossovers :: [Path] -> Visited
58 crossovers travelledPaths =
59 foldl1' (M.intersectionWith (+)) $ map _visited travelledPaths
60
61 travelAllPaths :: [[Segment]] -> [Path]
62 travelAllPaths = map travelPath
63
64 travelPath :: [Segment] -> Path
65 travelPath segments = foldl' travelSegment path0 segments
66 where path0 = Path { _visited = M.empty, _tip = V2 0 0, _currentLength = 0 }
67
68 travelSegment :: Path -> Segment -> Path
69 travelSegment path segment = path { _tip = tip', _visited = visited', _currentLength = len'}
70 where delta = facing $ _direction segment
71 distance = _steps segment
72 start = _tip path
73 len = _currentLength path
74 len' = len + distance
75 visited = _visited path
76 visited' = foldl' insertStep visited $ take distance $ drop 1 $ zip [len, (len + 1) ..] $ iterate (^+^ delta) start
77 tip' = start ^+^ distance *^ delta
78 insertStep visits (dist, loc) = if loc `M.member` visits
79 then visits
80 else M.insert loc dist visits
81
82 facing :: Direction -> Location
83 facing East = V2 1 0
84 facing South = V2 0 (-1)
85 facing West = V2 (-1) 0
86 facing North = V2 0 1
87
88
89 manhattan (V2 x y) = (abs x) + (abs y)
90
91 -- Parse the input file
92 type Parser = Parsec Void Text
93
94 sc :: Parser ()
95 sc = L.space (skipSome spaceChar) CA.empty CA.empty
96 -- sc = L.space (skipSome (char ' ')) CA.empty CA.empty
97
98 lexeme = L.lexeme sc
99 integer = lexeme L.decimal
100 -- signedInteger = L.signed sc integer
101 symb = L.symbol sc
102 comma = symb ","
103
104 wiresP = some pathP
105 pathP = segmentP `sepBy1` comma
106
107 segmentP = segmentify <$> directionP <*> integer
108 where segmentify direction steps =
109 Segment { _direction = direction, _steps = steps }
110
111
112 directionP = eP <|> sP <|> wP <|> nP
113 eP = (symb "R" *> pure East)
114 sP = (symb "D" *> pure South)
115 wP = (symb "L" *> pure West)
116 nP = (symb "U" *> pure North)
117
118
119 successfulParse :: Text -> [[Segment]]
120 successfulParse input =
121 case parse wiresP "input" input of
122 Left _err -> [] -- TIO.putStr $ T.pack $ parseErrorPretty err
123 Right wires -> wires