full memoization

This commit is contained in:
Quinten Kock 2021-12-13 03:06:34 +01:00
parent 7f8ce383f9
commit 0721d09f5a
1 changed files with 31 additions and 15 deletions

View File

@ -4,11 +4,16 @@ module Day12 where
import qualified Data.Map as M
import Data.Bits ( Bits(shiftL, (.|.), (.&.)) )
import qualified Data.Array as A
import Data.HashSet (HashSet)
import qualified Data.HashSet as S
import Data.List.Split (splitOn)
import qualified Data.Char
import Debug.Trace ( trace )
import GHC.Base (VecElem(Int16ElemRep))
type Cave = Int
type Path = (Cave,Cave)
type System = M.Map Cave [Cave]
@ -23,20 +28,30 @@ addPath (from,to) = M.unionWith (++) (M.fromList [(from,[to]), (to,[from])])
isUpper :: Cave -> Bool
isUpper x = x < 0
pathFinder :: System -> Cave -> Int -> Int
pathFinder sys (-1) _ = 1
pathFinder sys x visited = sum $ map (\next -> pathFinder sys next (nextmap next)) elig
solve :: System -> (Int, Int)
solve sys = (pf1a A.! (1,1), pf2a A.! (1, 1))
where
nextmap next = if not (isUpper next) then next .|. visited else visited
elig = filter (\cave -> isUpper cave || (cave .&. visited) == 0) (sys M.! x)
caves = concat $ M.elems sys
bounds = ((minimum caves, 0), (maximum caves, maximum caves * 2))
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)
pf1a :: A.Array (Cave,Int) Int
pf1a = A.array bounds [((c,v), pf1 c v) | c <- [minimum caves..maximum caves], v <- [0..maximum caves * 2] ]
pf1 :: Cave -> Int -> Int
pf1 (-1) _ = 1
pf1 x visited = sum $ map (\next -> pf1a A.! (next,nextmap next)) elig
where
nextmap next = if not (isUpper next) then next .|. visited else visited
elig = filter (\cave -> isUpper cave || (cave .&. visited) == 0) (sys M.! x)
pf2a :: A.Array (Cave,Int) Int
pf2a = A.array bounds [((c,v), pf2 c v) | c <- [minimum caves..maximum caves], v <- [0..maximum caves * 2] ]
pf2 :: Cave -> Int -> Int
pf2 (-1) _ = 1
pf2 x visited = sum $ map (\next -> f next A.! (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 pf2a else pf1a
elig = filter (/= 1) (sys M.! x)
convert :: [String] -> M.Map String Int
convert caves = conversion
@ -52,11 +67,12 @@ main = do
input <- map readPath . lines <$> getContents
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
let (p1,p2) = solve integralSystem
putStrLn "part 1: "
print $ pathFinder integralSystem 1 1
print p1
putStrLn "part 2: "
print $ pathFinder2 integralSystem 1 1
print p2