use bitsets
This commit is contained in:
parent
27551fcc2f
commit
7f8ce383f9
|
|
@ -2,7 +2,7 @@ module Day12 where
|
||||||
-- import Data.HashSet (HashSet, member, insert, fromList)
|
-- import Data.HashSet (HashSet, member, insert, fromList)
|
||||||
-- import Data.Map ( Map, fromList, unionWith, empty, (!), insert, elems) qualified (map)
|
-- import Data.Map ( Map, fromList, unionWith, empty, (!), insert, elems) qualified (map)
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
import qualified Data.Bits
|
import Data.Bits ( Bits(shiftL, (.|.), (.&.)) )
|
||||||
|
|
||||||
import Data.HashSet (HashSet)
|
import Data.HashSet (HashSet)
|
||||||
import qualified Data.HashSet as S
|
import qualified Data.HashSet as S
|
||||||
|
|
@ -23,16 +23,19 @@ addPath (from,to) = M.unionWith (++) (M.fromList [(from,[to]), (to,[from])])
|
||||||
isUpper :: Cave -> Bool
|
isUpper :: Cave -> Bool
|
||||||
isUpper x = x < 0
|
isUpper x = x < 0
|
||||||
|
|
||||||
pathFinder :: System -> Cave -> HashSet Cave -> Int
|
pathFinder :: System -> Cave -> Int -> Int
|
||||||
pathFinder sys (-1) _ = 1
|
pathFinder sys (-1) _ = 1
|
||||||
pathFinder sys x visited = sum $ map (\next -> pathFinder sys next (next `S.insert` visited)) elig
|
pathFinder sys x visited = sum $ map (\next -> pathFinder sys next (nextmap next)) elig
|
||||||
where elig = filter (\cave -> isUpper cave || not (cave `S.member` visited)) (sys M.! x)
|
|
||||||
|
|
||||||
pathFinder2 :: System -> Cave -> HashSet Cave -> Int
|
|
||||||
pathFinder2 sys (-1) _ = 1
|
|
||||||
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 `S.member` visited) then pathFinder2 else pathFinder
|
nextmap next = if not (isUpper next) then next .|. visited else visited
|
||||||
|
elig = filter (\cave -> isUpper cave || (cave .&. visited) == 0) (sys M.! x)
|
||||||
|
|
||||||
|
pathFinder2 :: System -> Cave -> Int -> Int
|
||||||
|
pathFinder2 sys (-1) _ = 1
|
||||||
|
pathFinder2 sys x visited = sum $ map (\next -> f next sys next (nextmap next)) elig
|
||||||
|
where
|
||||||
|
nextmap next = if not (isUpper next) then next .|. visited else visited
|
||||||
|
f cave = if isUpper cave || (cave .&. visited) == 0 then pathFinder2 else pathFinder
|
||||||
elig = filter (/= 1) (sys M.! x)
|
elig = filter (/= 1) (sys M.! x)
|
||||||
|
|
||||||
convert :: [String] -> M.Map String Int
|
convert :: [String] -> M.Map String Int
|
||||||
|
|
@ -53,7 +56,7 @@ main = do
|
||||||
let integralSystem = M.mapKeys (conversion M.!) $ M.map (map (conversion M.!)) system
|
let integralSystem = M.mapKeys (conversion M.!) $ M.map (map (conversion M.!)) system
|
||||||
|
|
||||||
putStrLn "part 1: "
|
putStrLn "part 1: "
|
||||||
print $ pathFinder integralSystem 1 (S.fromList [1])
|
print $ pathFinder integralSystem 1 1
|
||||||
|
|
||||||
putStrLn "part 2: "
|
putStrLn "part 2: "
|
||||||
print $ pathFinder2 integralSystem 1 (S.fromList [1])
|
print $ pathFinder2 integralSystem 1 1
|
||||||
|
|
|
||||||
Loading…
Reference in New Issue