{-# LANGUAGE ScopedTypeVariables, GADTs, BangPatterns #-} module Data.RangeMin.Int.Linearithmic.Combinators where import Control.Monad import Data.RangeMin.Common.Vector import qualified Data.RangeMin.Fusion as F {-# INLINE buildRowsUnf #-} buildRowsUnf :: Vector v a => Int -> Int -> Maybe a -> v a -> (Int -> v a -> v a) -> v a buildRowsUnf !rows !cols def firstRow sucRow = create $ do !dest <- maybe (new (rows * cols)) (newWith (rows * cols)) def row0 <- unsafeFreeze =<< F.fill dest (F.stream firstRow) let go !i !prev = when (i < rows) $ let !next = sliceM (cols * i) cols dest in go (i+1) =<< unsafeFreeze =<< F.fill next (F.stream (sucRow i prev)) go 1 row0 return dest