# Infinitree Memoization using Lazy Infinite trees indexed by natural numbers ## Considerations Using this data structure comes with trade-offs: - It is impossible to evict data from the cache - The cache is unbound in size - Indexing can be done only using Natural Numbers - Lookup is logarithmic in time and space ## Usage This is a rather constructed example. ```haskell fibonacci = Infinitree.build $ go where go 0 = 0 go 1 = 1 go n = Infinitree.index fibonacci (n - 1) + Infinitree.index fibonacci (n - 2) ``` It is also possible to use multiple levels of infinitrees, you can see an example of this in a solution to a [puzzle from Advent Of Code 2024](https://adventofcode.com/2024/day/11). The code below may be a spoiler if you're trying to do the puzzle linked above. It uses two layers of cache trees and may make a lot more sense after you've read the problem description. ```haskell {-# LANGUAGE MultiWayIf #-} import Control.Arrow ( (>>>), Arrow((&&&)) ) import Data.Infinitree (Infinitree) import Numeric.Natural (Natural) import qualified Data.Infinitree as Infinitree parse :: String -> [StoneNumber] parse = words >>> map read type StoneNumber = Natural type StoneCount = Natural type BlinkCount = Natural lookupStoneCount :: BlinkCount -> StoneNumber -> StoneCount lookupStoneCount i = Infinitree.index (Infinitree.index blinkTree i) blinkTree :: Infinitree (Infinitree StoneCount) blinkTree = Infinitree.build stoneTree stoneTree :: Natural -> Infinitree StoneCount stoneTree = Infinitree.build . countSplit countSplit :: BlinkCount -> StoneNumber -> StoneCount countSplit 0 _ = 1 countSplit i n = if | n == 0 -> lookupStoneCount (pred i) (succ n) | even nDigits -> lookupStoneCount (pred i) firstSplit + lookupStoneCount (pred i) secondSplit | otherwise -> lookupStoneCount (pred i) (n * 2024) where nDigits = digitCount n :: Int secondSplit = n `mod` (10 ^ (nDigits `div` 2)) firstSplit = (n - secondSplit) `div` (10 ^ (nDigits `div` 2)) part1 :: [StoneNumber] -> StoneCount part1 = map (lookupStoneCount 25) >>> sum part2 :: [StoneNumber] -> StoneCount part2 = map (lookupStoneCount 75) >>> sum digitCount :: (Integral a, Integral b) => a -> b digitCount = succ . floor . logBase 10 . fromIntegral main :: IO () main = getContents >>= print . (part1 &&& part2) . parse ```