Added a type annotation
[advent-of-code-17.git] / src / advent19 / advent19.hs
1 {-# LANGUAGE NegativeLiterals #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE OverloadedStrings #-}
4 {-# LANGUAGE TypeFamilies #-}
5
6 import Prelude hiding (Left, Right)
7 import Data.List
8 import Data.Char
9
10 type Maze = [String]
11
12 data Direction = Up | Down | Left | Right deriving (Show, Eq)
13
14 data Progress = Progress { row :: Int
15 , column :: Int
16 , direction :: Direction
17 , letters :: String
18 , stepCount :: Int
19 } deriving (Show, Eq)
20
21
22 -- Note: assumes the maze comes with a padding border of spaces
23 -- all around it. Makes the "next location" checking much easier!
24
25 main :: IO ()
26 main = do
27 text <- readFile "data/advent19.txt"
28 let maze = lines text
29 let progress = navigate maze
30 print $ letters progress
31 print $ stepCount progress
32
33
34 startProgress :: Maze -> Progress
35 startProgress maze = Progress { row = 0, column = startCol
36 , direction = Down
37 , letters = "", stepCount = 0}
38 where topRow = maze!!0
39 startCol = head $ elemIndices '|' topRow
40
41 delta :: Direction -> (Int, Int)
42 delta Up = (-1, 0)
43 delta Down = ( 1, 0)
44 delta Left = ( 0, -1)
45 delta Right = ( 0, 1)
46
47 isJunction :: Char -> Bool
48 isJunction '+' = True
49 isJunction _ = False
50
51 isFinished :: Maze -> Progress -> Bool
52 isFinished maze progress = isSpace $ location maze (row progress) (column progress)
53
54 location :: Maze -> Int -> Int -> Char
55 location maze r c = (maze!!r)!!c
56
57
58 navigate :: Maze -> Progress
59 navigate maze = navigate' maze progress
60 where progress = startProgress maze
61
62 navigate' :: Maze -> Progress -> Progress
63 navigate' maze progress =
64 if isFinished maze progress
65 then progress
66 else navigate' maze (step maze progress)
67
68
69 step :: Maze -> Progress -> Progress
70 step maze progress = progress {row = r', column = c', direction = d', letters = l', stepCount = sc'}
71 where r = row progress
72 c = column progress
73 thisChar = location maze r c
74 l' = if isAlpha thisChar then (letters progress) ++ [thisChar] else letters progress
75 d' = if isJunction thisChar then newDirection maze progress else direction progress
76 (dr, dc) = delta d'
77 r' = r + dr
78 c' = c + dc
79 sc' = stepCount progress + 1
80
81 newDirection :: Maze -> Progress -> Direction
82 newDirection maze progress =
83 if d == Up || d == Down
84 then if isSpace leftChar then Right else Left
85 else if isSpace upChar then Down else Up
86 where d = direction progress
87 r = row progress
88 c = column progress
89 upChar = location maze (r - 1) c
90 leftChar = location maze r (c - 1)