day13: speed up with hashset and dead code removal

This commit is contained in:
Quinten Kock 2021-12-13 07:02:19 +01:00
parent c26ae17d4c
commit 414cb602af
1 changed files with 8 additions and 9 deletions

View File

@ -1,6 +1,7 @@
module Day13 where
import Data.List.Split (splitOn)
import Data.List (nub, sort)
import qualified Data.HashSet as S
import Debug.Trace (trace)
type Dot = (Int,Int)
@ -20,23 +21,21 @@ main :: IO ()
main = do
input <- lines <$> getContents
let [dots',folds'] = splitOn [""] input
let dots = nub $ map parse dots'
let dots = map parse dots'
let folds = map parseFold folds'
putStr "part 1: "
let dots1 = nub $ sort $ map (fold (head folds)) dots
print $ length dots1
let dots1 = S.fromList $ map (fold (head folds)) dots
print $ S.size dots1
putStr "part 2: "
let dots2 = nub $ sort $ map (\d -> foldl (flip fold) d folds) dots
print dots2
putStrLn "part 2: "
let dots2 = map (\d -> foldl (flip fold) d folds) dots
let dots2' = S.fromList dots2
let min_x = minimum $ map fst dots2
let max_x = maximum $ map fst dots2
let min_y = minimum $ map snd dots2
let max_y = maximum $ map snd dots2
mapM_ (\y -> do
mapM_ (\x -> putChar (if (x,y) `elem` dots2 then '#' else '.')) [0..max_x]
mapM_ (\x -> putChar (if (x,y) `S.member` dots2' then '#' else '.')) [0..max_x]
putStrLn ""
) [0..max_y]
-- print dots2
-- print $ length dots2