60 lines
		
	
	
	
		
			1.5 KiB
		
	
	
	
		
			Haskell
		
	
	
	
	
	
			
		
		
	
	
			60 lines
		
	
	
	
		
			1.5 KiB
		
	
	
	
		
			Haskell
		
	
	
	
	
	
| module Main where
 | |
| 
 | |
| import System.Environment (getArgs)
 | |
| 
 | |
| import Control.Exception (assert)
 | |
| 
 | |
| import Text.Parsec (parse, many1, char, sepBy, endBy)
 | |
| import Text.Parsec.Char (endOfLine)
 | |
| import Text.ParserCombinators.Parsec (GenParser)
 | |
| import Text.ParserCombinators.Parsec.Number (decimal)
 | |
| 
 | |
| type Report = [Level]
 | |
| type Level = Int
 | |
| 
 | |
| reports :: GenParser Char st [Report]
 | |
| reports = endBy report endOfLine
 | |
| 
 | |
| report :: GenParser Char st Report
 | |
| report = sepBy level (many1 (char ' '))
 | |
| 
 | |
| level :: GenParser Char st Level
 | |
| level = decimal
 | |
| 
 | |
| pairUp :: [a] -> [(a, a)]
 | |
| pairUp (a:b:tl) = (a, b) : pairUp (b:tl)
 | |
| pairUp _ = []
 | |
| 
 | |
| isSafe :: Report -> Bool
 | |
| isSafe (a:b:tl) = a /= b && (==) 0 (
 | |
|     length $ filter (not . (\(l, r) -> let
 | |
|                 dif = abs (l - r)
 | |
|                 cmp = if a < b then (<) else assert (b < a) (>)
 | |
|             in (1 <= dif) && (dif <= 3) && l `cmp` r))
 | |
|         $ pairUp
 | |
|         $ a:b:tl)
 | |
| isSafe _ = True
 | |
| 
 | |
| with1Removed :: Report -> [Report]
 | |
| with1Removed (h:tl) = tl : map (h :) (with1Removed tl)
 | |
| with1Removed [] = []
 | |
| 
 | |
| isKindaSafe :: Report -> Bool
 | |
| isKindaSafe = any isSafe . with1Removed
 | |
| 
 | |
| part1 :: [Report] -> Int
 | |
| part1 = length . filter isSafe
 | |
| 
 | |
| part2 :: [Report] -> Int
 | |
| part2 = length . filter isKindaSafe
 | |
| 
 | |
| main :: IO ()
 | |
| main = do
 | |
|     args <- getArgs
 | |
|     (fp:_) <- return args
 | |
|     content <- readFile fp
 | |
|     case parse reports fp content of
 | |
|         Left e -> putStrLn ("Input file is incorrectly formatted : " ++ show e)
 | |
|         Right r -> do
 | |
|             putStrLn ("Solution (Part 1) : " ++ show (part1 r))
 | |
|             putStrLn ("Solution (Part 2) : " ++ show (part2 r))
 |