Skip to content

Instantly share code, notes, and snippets.

@meooow25
Last active October 1, 2022 05:52
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save meooow25/b74f2baea73879611786758a83acbff4 to your computer and use it in GitHub Desktop.
Save meooow25/b74f2baea73879611786758a83acbff4 to your computer and use it in GitHub Desktop.
Kattis Infinite 2D Array
{-# LANGUAGE BangPatterns, TypeApplications #-}
import Data.Array.Unboxed
import Data.List
-- Solution to Infinite 2D Array
-- https://open.kattis.com/problems/infinite2darray
main :: IO ()
main = do
[x, y] <- map read . words <$> getLine
print $ solve x y
solve :: Int -> Int -> Int
solve 0 y | y > 0 = solve y 0
solve x y = foldl' plusmod (fib (x + 2 * y)) (map contrib [1..y]) where
contrib i = (fib i `minusmod` fib (2 * i)) `mulmod` binom (y - i + x - 1) (y - i)
mx :: Int
mx = 3000000
fib :: Int -> Int
fib = (fibs!) where
fibs = listArray @UArray (0, mx) $ unfoldr (\(!a, !b) -> Just (a, (b, plusmod a b))) (0, 1)
binom :: Int -> Int -> Int
binom = go where
go n k | k < 0 || n < k = 0
go n k = fac!n `mulmod` ifac!k `mulmod` ifac!(n - k)
fac = listArray @UArray (0, mx) $ unfoldr (\(!i, !x) -> Just (x, (i + 1, mulmod i x))) (1, 1)
ifac = array @UArray (0, mx) $ unfoldr (\(!i, !x) -> if i < 0 then Nothing else Just ((i, x), (i - 1, mulmod x i))) (mx, inv (fac!mx))
mm :: Int
mm = 1000000007
infixl 6 `plusmod`
infixl 6 `minusmod`
infixl 7 `mulmod`
plusmod, minusmod, mulmod :: Int -> Int -> Int
plusmod a b = let c = a + b in if c >= mm then c - mm else c
minusmod a b = let c = a - b in if c < 0 then c + mm else c
mulmod a b = mod (a * b) mm
inv :: Int -> Int
inv x = go x (mm - 2) where
go _ 0 = 1
go x y | even y = go (mulmod x x) (div y 2)
| otherwise = mulmod x (go x (y - 1))

$$ F_{x,y} = f_{x+2y} + \sum_{i=1}^y (f_i - f_{2i}) \binom{y-i+x-1}{y-i} $$

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment