35 lines
1.0 KiB
Haskell
35 lines
1.0 KiB
Haskell
module Day3 where
|
|
import System.IO (openFile, IOMode (ReadMode), hClose, hGetContents)
|
|
import Data.List ( maximumBy, minimumBy, group, sort )
|
|
import Data.Function (on)
|
|
import Data.Char (digitToInt)
|
|
|
|
column :: String -> Int -> String
|
|
column str i = map (!! i) $ lines str
|
|
|
|
columns :: String -> Int
|
|
columns str = maximum $ map length $ lines str
|
|
|
|
mostCommon :: String -> Char
|
|
mostCommon str = head . maximumBy (compare `on` length) . group $ sort str
|
|
|
|
leastCommon :: String -> Char
|
|
leastCommon str = head . minimumBy (compare `on` length) . group $ sort str
|
|
|
|
binaryToDecimal :: Int -> Int
|
|
binaryToDecimal = foldl1 ((+) . (2 *)) . map digitToInt . show
|
|
|
|
main :: IO ()
|
|
main = do
|
|
input <- openFile "inputs/3.txt" ReadMode
|
|
contents <- hGetContents input
|
|
|
|
let gamma = mostCommon . column contents <$> [0..(columns contents - 1)]
|
|
let epsilon = leastCommon . column contents <$> [0..(columns contents - 1)]
|
|
|
|
let energy = product (binaryToDecimal . read <$> [gamma, epsilon] :: [Int])
|
|
|
|
print energy
|
|
|
|
hClose input
|