Day 8
This commit is contained in:
parent
171d11f532
commit
82f519da96
|
@ -0,0 +1,18 @@
|
|||
module Day8 where
|
||||
import System.IO (openFile, IOMode (ReadMode), hClose, hGetContents)
|
||||
import Data.Text (splitOn, unpack, pack)
|
||||
import Prelude hiding (splitAt)
|
||||
|
||||
splitAt :: String -> String -> [String]
|
||||
splitAt delimiter str = map unpack $ splitOn (pack delimiter) $ pack str
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
input <- openFile "inputs/8.txt" ReadMode
|
||||
contents <- hGetContents input
|
||||
|
||||
let patterns = map (splitAt " ") . splitAt " | " <$> lines contents
|
||||
|
||||
print . sum . map (length . filter (\x -> length x `elem` [2,3,4,7])) $ (!! 1) <$> patterns
|
||||
|
||||
hClose input
|
|
@ -0,0 +1,45 @@
|
|||
module Day8_1 where
|
||||
import System.IO (openFile, IOMode (ReadMode), hClose, hGetContents)
|
||||
import Data.Text (splitOn, unpack, pack)
|
||||
import Prelude hiding (splitAt)
|
||||
import Data.List (sort, (\\))
|
||||
|
||||
splitAt :: String -> String -> [String]
|
||||
splitAt delimiter str = map unpack $ splitOn (pack delimiter) $ pack str
|
||||
|
||||
decode :: [String] -> [(String, Int)]
|
||||
decode nums = zip (head <$> [zero, one, two, three, four, five, six, seven, eight, nine]) [0..9]
|
||||
where
|
||||
one = withLength 2
|
||||
two = filter (not . all (`elem` head nine)) $ withLength 5
|
||||
three = withLength 5 \\ [head two, head five]
|
||||
four = withLength 4
|
||||
five = filter (all (`elem` head six)) $ withLength 5
|
||||
six = filter (\x -> not $ all (`elem` x) (head seven)) $ withLength 6
|
||||
seven = withLength 3
|
||||
eight = withLength 7
|
||||
nine = filter (\x -> all (`elem` x) (head four)) $ withLength 6
|
||||
zero = withLength 6 \\ [head nine, head six]
|
||||
--
|
||||
withLength y = filter ((== y) . length) nums
|
||||
|
||||
decodeDigit :: [(String, Int)] -> String -> Int
|
||||
decodeDigit [] d = error "oh no"
|
||||
decodeDigit (x:xs) d
|
||||
| fst x == d = snd x
|
||||
| otherwise = decodeDigit xs d
|
||||
|
||||
applyDecode :: [(String, Int)] -> [String] -> String
|
||||
applyDecode codes = concatMap (show . decodeDigit codes)
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
input <- openFile "inputs/8.txt" ReadMode
|
||||
contents <- hGetContents input
|
||||
|
||||
let patterns = map (map sort . splitAt " ") . splitAt " | " <$> lines contents
|
||||
let pairs = zip (head <$> patterns) ((!! 1) <$> patterns)
|
||||
|
||||
print $ sum (read <$> map (\x -> applyDecode (decode $ fst x) (snd x)) pairs :: [Int])
|
||||
|
||||
hClose input
|
Loading…
Reference in New Issue