module Data.RangeMin.Int.Catalan.Table where import Data.RangeMin.Common.Unf.Slice import Data.RangeMin.Common.Unf import Data.RangeMin.Common.Vector.Utils import qualified Data.Vector.Unboxed as UV maxLog :: Int maxLog = 17 {-# NOINLINE catalans #-} catalans :: UV.Vector Int catalans = buildRowsUnf maxLog maxLog (Just 0) (generateUnf maxLog (const 1)) $ const (postscanlUnf' (+) 0 . toUnf . UV.unsafeTail) catalan :: Int -> Int -> Int catalan = getRow (maxLog - 1) catalans