a8a3ccbba0e00b22dafa6129764285c140e14a68
[summerofcode2018soln.git] / src / task1 / task1-mpc.hs
1 {-# LANGUAGE OverloadedStrings #-}
2
3 import Data.List (foldl') -- import the strict fold
4
5 import Data.Text (Text)
6 -- import qualified Data.Text as T
7 import qualified Data.Text.IO as TIO
8
9 import Data.Void (Void)
10
11 import Text.Megaparsec -- hiding (State)
12 import Text.Megaparsec.Char
13 import qualified Text.Megaparsec.Char.Lexer as L
14 import qualified Control.Applicative as CA
15
16
17 -- number of steps
18 type Distance = Int
19 type Position = (Int, Int)
20
21 -- the directions. See below for functions for turning
22 data Direction = North | East | South | West
23 deriving (Enum, Show, Bounded, Eq)
24
25 -- direction, easting, northing
26 data Mowmaster = Mowmaster { direction :: Direction
27 , position :: Position
28 } deriving (Show, Eq)
29
30 -- one instruction for the mowmaster
31 data Instruction = Forward Distance
32 | Clockwise
33 | Anticlockwise
34 | Comment String
35 deriving (Show, Eq)
36
37
38 main :: IO ()
39 main = do
40 instruction_text <- TIO.readFile "data/01-mowmaster.txt"
41 let instructions = successfulParse instruction_text
42 print $ part1 instructions
43 print $ part2 instructions
44
45 part1 :: [Instruction] -> Int
46 part1 = length
47
48 part2 :: [Instruction] -> Int
49 part2 instructions = finalDistance $ executeAll instructions
50 where executeAll = foldl' execute initialMowmaster
51
52 initialMowmaster = Mowmaster North (0, 0)
53
54
55 -- Calculate manhattan distance from start to this state
56 finalDistance :: Mowmaster -> Int
57 finalDistance m = (abs e) + (abs n)
58 where (e, n) = position m
59
60
61 -- Make one move
62 execute :: Mowmaster -> Instruction -> Mowmaster
63 execute m (Forward s) = m {position = forward s (direction m) (position m)}
64 execute m Clockwise = m {direction = turnCW (direction m)}
65 execute m Anticlockwise = m {direction = turnACW (direction m)}
66 execute m _ = m
67
68 -- Move in the current direction
69 forward :: Int -> Direction -> Position -> Position
70 forward s North (e, n) = (e, n+s)
71 forward s South (e, n) = (e, n-s)
72 forward s West (e, n) = (e-s, n)
73 forward s East (e, n) = (e+s, n)
74
75
76 -- | a `succ` that wraps
77 turnCW :: (Bounded a, Enum a, Eq a) => a -> a
78 turnCW dir | dir == maxBound = minBound
79 | otherwise = succ dir
80
81 -- | a `pred` that wraps
82 turnACW :: (Bounded a, Enum a, Eq a) => a -> a
83 turnACW dir | dir == minBound = maxBound
84 | otherwise = pred dir
85
86
87 -- Parse the input file
88
89 type Parser = Parsec Void Text
90
91 -- treat comment lines as whitespace
92 sc :: Parser ()
93 sc = L.space space1 lineComment CA.empty
94 where lineComment = L.skipLineComment "#"
95
96 lexeme = L.lexeme sc
97 integer = lexeme L.decimal
98 symb = L.symbol sc
99
100 -- instructions is some optional space followed by many instructions
101 instrsP = optional sc *> many instrP
102 instrP = forwardP <|> cwP <|> acwP
103
104 -- parse each instruction
105 forwardP = Forward <$> (symb "F" *> integer)
106 cwP = Clockwise <$ symb "C"
107 acwP = Anticlockwise <$ symb "A"
108
109 successfulParse :: Text -> [Instruction]
110 successfulParse input =
111 case parse instrsP "input" input of
112 Left _error -> [] -- TIO.putStr $ T.pack $ parseErrorPretty err
113 Right instrs -> instrs