day12: use ints

This commit is contained in:
Quinten Kock 2021-12-13 02:04:02 +01:00
parent 8031b0327a
commit 27551fcc2f
1 changed files with 35 additions and 18 deletions

View File

@ -1,42 +1,59 @@
module Day12 where module Day12 where
import Data.HashSet (HashSet, member, insert, fromList) -- import Data.HashSet (HashSet, member, insert, fromList)
import Data.Map ( Map, fromList, unionWith, empty, (!) ) -- import Data.Map ( Map, fromList, unionWith, empty, (!), insert, elems) qualified (map)
import qualified Data.Map as M
import qualified Data.Bits
import Data.HashSet (HashSet)
import qualified Data.HashSet as S
import Data.List.Split (splitOn) import Data.List.Split (splitOn)
import qualified Data.Char import qualified Data.Char
type Cave = String type Cave = Int
type Path = (Cave,Cave) type Path = (Cave,Cave)
type System = Map Cave [Cave] type System = M.Map Cave [Cave]
readPath :: String -> Path readPath :: String -> (String,String)
readPath s = (from,to) where [from,to] = splitOn "-" s readPath s = (from,to) where [from,to] = splitOn "-" s
addPath :: Path -> System -> System addPath :: (String,String) -> M.Map String [String] -> M.Map String [String]
addPath (from,to) = unionWith (++) (Data.Map.fromList [(from,[to]), (to,[from])]) addPath (from,to) = M.unionWith (++) (M.fromList [(from,[to]), (to,[from])])
isUpper :: Cave -> Bool isUpper :: Cave -> Bool
isUpper = Data.Char.isUpper . head isUpper x = x < 0
pathFinder :: System -> Cave -> HashSet Cave -> Int pathFinder :: System -> Cave -> HashSet Cave -> Int
pathFinder sys "end" _ = 1 pathFinder sys (-1) _ = 1
pathFinder sys x visited = sum $ map (\next -> pathFinder sys next (next `insert` visited)) elig pathFinder sys x visited = sum $ map (\next -> pathFinder sys next (next `S.insert` visited)) elig
where elig = filter (\cave -> isUpper cave || not (cave `member` visited)) (sys ! x) where elig = filter (\cave -> isUpper cave || not (cave `S.member` visited)) (sys M.! x)
pathFinder2 :: System -> Cave -> HashSet Cave -> Int pathFinder2 :: System -> Cave -> HashSet Cave -> Int
pathFinder2 sys "end" _ = 1 pathFinder2 sys (-1) _ = 1
pathFinder2 sys x visited = sum $ map (\next -> f next sys next (next `insert` visited)) elig pathFinder2 sys x visited = sum $ map (\next -> f next sys next (next `S.insert` visited)) elig
where where
f cave = if isUpper cave || not (cave `member` visited) then pathFinder2 else pathFinder f cave = if isUpper cave || not (cave `S.member` visited) then pathFinder2 else pathFinder
elig = filter (/= "start") (sys ! x) elig = filter (/= 1) (sys M.! x)
convert :: [String] -> M.Map String Int
convert caves = conversion
where
(conversion, numhi, numlo) = foldr go (M.fromList [("end", -1), ("start", 1)], 2, 1) caves
go cave (map,upper,lower)
| cave `M.member` map = (map,upper,lower)
| Data.Char.isUpper (head cave) = (M.insert cave (-upper) map, upper+1, lower)
| otherwise = (M.insert cave (1 `Data.Bits.shiftL` lower) map, upper, lower+1)
main :: IO () main :: IO ()
main = do main = do
input <- map readPath . lines <$> getContents input <- map readPath . lines <$> getContents
let system = foldr addPath Data.Map.empty input let system = foldr addPath M.empty input
let conversion = convert $ concat $ M.elems system
print conversion
let integralSystem = M.mapKeys (conversion M.!) $ M.map (map (conversion M.!)) system
putStrLn "part 1: " putStrLn "part 1: "
print $ pathFinder system "start" (Data.HashSet.fromList ["start"]) print $ pathFinder integralSystem 1 (S.fromList [1])
putStrLn "part 2: " putStrLn "part 2: "
print $ pathFinder2 system "start" (Data.HashSet.fromList ["start"]) print $ pathFinder2 integralSystem 1 (S.fromList [1])