{-# 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 = inlineCreate $ 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 -- {-# INLINE unfoldrInto #-} -- unfoldrInto :: (Vector v a, PrimMonad m) => Mutable v (PrimState m) a -> (Int -> b -> (a, b)) -> b -> m (v a) -- unfoldrInto !xs suc s0 = do -- filler 0 s0 -- unsafeFreeze xs -- where !n = GM.length xs -- filler !i s = when (i < n) $ case suc i s of -- (x, s') -> do write xs i x -- filler (i+1) s' -- -- {-# INLINE [1] generateInto #-} -- generateInto :: (Vector v a, PrimMonad m) => Mutable v (PrimState m) a -> (Int -> a) -> m (v a) -- generateInto !xs f = do -- let go i = if i < n then write xs i (f i) >> go (i+1) else return () -- go 0 -- unsafeFreeze xs -- where !n = GM.length xs