Done day 3 part 2
authorNeil Smith <neil.git@njae.me.uk>
Tue, 3 Dec 2019 16:44:13 +0000 (16:44 +0000)
committerNeil Smith <neil.git@njae.me.uk>
Tue, 3 Dec 2019 16:44:13 +0000 (16:44 +0000)
advent03/package.yaml
advent03/src/advent03.hs
advent03/src/advent03part1.hs [new file with mode: 0644]
data/advent03a.txt [new file with mode: 0644]

index 2706725d30b6e533bb345d474308c9743d71d44f..5b3587019c196553670350fb4aed3f96d5b86daa 100644 (file)
@@ -59,3 +59,12 @@ executables:
     - megaparsec
     - containers
     - linear
+  advent03part1:
+    main: advent03part1.hs
+    source-dirs: src
+    dependencies:
+    - base >= 2 && < 6
+    - text
+    - megaparsec
+    - containers
+    - linear
index a541f23b926d4c26edb315041ebf226db60c7473..2d1eef51f4e7d82af73fa819613adfefc184abfc 100644 (file)
@@ -1,6 +1,3 @@
--- Some code taken from [AoC 2017 day 5](https://adventofcode.com/2017/day/5), 
---    and some from [AoC 2018 day 21](https://adventofcode.com/2018/day/21)
-
 import Data.Text (Text)
 import qualified Data.Text.IO as TIO
 
@@ -13,6 +10,8 @@ import qualified Control.Applicative as CA
 
 import Data.List (foldl')
 import qualified Data.Set as S
+import qualified Data.Map as M
+import Data.Map ((!))
 
 import Linear (V2(..), (^+^), (^-^), (*^), (*^))
 
@@ -22,8 +21,11 @@ type Location = V2 Int -- x, y
 
 type Visited = S.Set Location
 
-data Path = Path { _visited :: Visited
+type TrackedVisited = M.Map Location Int
+
+data Path = Path { _visited :: TrackedVisited
                  , _tip :: Location
+                 , _currentLength :: Int
                  } 
                deriving (Show, Eq)
 
@@ -36,38 +38,53 @@ main :: IO ()
 main = do 
         text <- TIO.readFile "data/advent03.txt"
         let segmentss = successfulParse text
-        print segmentss
+        let paths = travelAllPaths segmentss
         -- print $ travelPath $ head segmentss
-        print $ part1 segmentss
-        -- print $ part2 machine
+        print $ part1 paths
+        print $ part2 paths
+
+part1 :: [Path] -> Int
+part1 paths = closest $ crossovers paths
+
+part2 :: [Path] -> Int
+part2 paths = shortestPaths paths $ crossovers paths
 
-part1 :: [[Segment]] -> Int
-part1 segmentss = closest $ crossovers $ travelAllPaths segmentss
 
 closest :: Visited -> Int
 closest points = S.findMin $ S.map manhattan points
 
+
+shortestPaths :: [Path] -> Visited -> Int
+shortestPaths paths crossings = minimum $ S.map crossingPathLengths crossings
+    where crossingPathLengths crossing = sum $ map (\p -> (_visited p)!crossing) paths
+
+
 crossovers :: [Path] -> Visited
 crossovers travelledPaths = 
       foldl' S.intersection
-             (_visited $ head travelledPaths)
-             (map _visited $ drop 1 travelledPaths)
+             (M.keysSet $ _visited $ head travelledPaths)
+             (map (M.keysSet . _visited) $ drop 1 travelledPaths)
 
 travelAllPaths :: [[Segment]] -> [Path]
 travelAllPaths = map travelPath
 
 travelPath :: [Segment] -> Path
 travelPath segments = foldl' travelSegment path0 segments
-    where   path0 = Path { _visited = S.empty, _tip = V2 0 0 }
+    where   path0 = Path { _visited = M.empty, _tip = V2 0 0, _currentLength = 0 }
 
 travelSegment :: Path -> Segment -> Path
-travelSegment path segment = path { _tip = tip', _visited = visited' }
+travelSegment path segment = path { _tip = tip', _visited = visited', _currentLength = len'}
     where   delta = facing $ _direction segment
             distance = _steps segment
             start = _tip path
+            len = _currentLength path
+            len' = len + distance
             visited = _visited path
-            visited' = foldl' (flip S.insert) visited $ take distance $ drop 1 $ iterate (^+^ delta) start
+            visited' = foldl' insertStep visited $ take distance $ drop 1 $ zip [len, (len + 1) ..] $ iterate (^+^ delta) start
             tip' = start ^+^ distance *^ delta
+            insertStep visits (dist, loc) = if loc `M.member` visits
+                                            then visits
+                                            else M.insert loc dist visits
 
 facing :: Direction -> Location
 facing East = V2 1 0
diff --git a/advent03/src/advent03part1.hs b/advent03/src/advent03part1.hs
new file mode 100644 (file)
index 0000000..3702943
--- /dev/null
@@ -0,0 +1,110 @@
+import Data.Text (Text)
+import qualified Data.Text.IO as TIO
+
+import Data.Void (Void)
+
+import Text.Megaparsec hiding (State)
+import Text.Megaparsec.Char
+import qualified Text.Megaparsec.Char.Lexer as L
+import qualified Control.Applicative as CA
+
+import Data.List (foldl')
+import qualified Data.Set as S
+
+import Linear (V2(..), (^+^), (^-^), (*^), (*^))
+
+data Direction = East | South | West | North deriving (Show, Eq)
+
+type Location = V2 Int -- x, y
+
+type Visited = S.Set Location
+
+data Path = Path { _visited :: Visited
+                 , _tip :: Location
+                 } 
+               deriving (Show, Eq)
+
+data Segment = Segment { _direction :: Direction
+                       , _steps :: Int
+                       } deriving (Show, Eq)
+
+
+main :: IO ()
+main = do 
+        text <- TIO.readFile "data/advent03.txt"
+        let segmentss = successfulParse text
+        -- print segmentss
+        -- print $ travelPath $ head segmentss
+        print $ part1 segmentss
+        -- print $ part2 machine
+
+part1 :: [[Segment]] -> Int
+part1 segmentss = closest $ crossovers $ travelAllPaths segmentss
+
+closest :: Visited -> Int
+closest points = S.findMin $ S.map manhattan points
+
+crossovers :: [Path] -> Visited
+crossovers travelledPaths = 
+      foldl' S.intersection
+             (_visited $ head travelledPaths)
+             (map _visited $ drop 1 travelledPaths)
+
+travelAllPaths :: [[Segment]] -> [Path]
+travelAllPaths = map travelPath
+
+travelPath :: [Segment] -> Path
+travelPath segments = foldl' travelSegment path0 segments
+    where   path0 = Path { _visited = S.empty, _tip = V2 0 0 }
+
+travelSegment :: Path -> Segment -> Path
+travelSegment path segment = path { _tip = tip', _visited = visited' }
+    where   delta = facing $ _direction segment
+            distance = _steps segment
+            start = _tip path
+            visited = _visited path
+            visited' = foldl' (flip S.insert) visited $ take distance $ drop 1 $ iterate (^+^ delta) start
+            tip' = start ^+^ distance *^ delta
+
+facing :: Direction -> Location
+facing East = V2 1 0
+facing South = V2 0 (-1)
+facing West = V2 (-1) 0
+facing North = V2 0 1
+
+
+manhattan (V2 x y) = (abs x) + (abs y)
+
+-- Parse the input file
+type Parser = Parsec Void Text
+
+sc :: Parser ()
+sc = L.space (skipSome spaceChar) CA.empty CA.empty
+-- sc = L.space (skipSome (char ' ')) CA.empty CA.empty
+
+lexeme  = L.lexeme sc
+integer = lexeme L.decimal
+-- signedInteger = L.signed sc integer
+symb = L.symbol sc
+comma = symb ","
+
+wiresP = some pathP
+pathP = segmentP `sepBy1` comma
+
+segmentP = segmentify <$> directionP <*> integer
+    where segmentify direction steps = 
+              Segment { _direction = direction, _steps = steps }
+
+
+directionP = eP <|> sP <|> wP <|> nP
+eP = (symb "R" *> pure East)
+sP = (symb "D" *> pure South)
+wP = (symb "L" *> pure West)
+nP = (symb "U" *> pure North)
+
+
+successfulParse :: Text -> [[Segment]]
+successfulParse input = 
+        case parse wiresP "input" input of
+                Left  _err -> [] -- TIO.putStr $ T.pack $ parseErrorPretty err
+                Right wires -> wires
\ No newline at end of file
diff --git a/data/advent03a.txt b/data/advent03a.txt
new file mode 100644 (file)
index 0000000..b823edd
--- /dev/null
@@ -0,0 +1,2 @@
+R8,U5,L5,D3
+U7,R6,D4,L4
\ No newline at end of file