{-# LANGUAGE BangPatterns #-} module Data.RangeMin.Common.Vector.Utils (write, read, new, newWith, drop, slice, sliceM, unsafeFreeze, minIndex, streamM, (!), getRow, G.Vector, GM.MVector, G.Mutable, G.stream) where import Control.Monad.Primitive import qualified Data.Vector.Generic as G import qualified Data.Vector.Generic.Mutable as GM import qualified Data.Vector.Fusion.Stream as S import Prelude hiding (read, drop) {-# INLINE unsafeFreeze #-} unsafeFreeze :: (PrimMonad m, G.Vector v a) => G.Mutable v (PrimState m) a -> m (v a) unsafeFreeze = G.unsafeFreeze sliceM :: GM.MVector v a => Int -> Int -> v s a -> v s a sliceM = GM.unsafeSlice {-# INLINE write #-} write :: (PrimMonad m, GM.MVector v a) => v (PrimState m) a -> Int -> a -> m () write = GM.unsafeWrite {-# INLINE read #-} read :: (PrimMonad m, GM.MVector v a) => v (PrimState m) a -> Int -> m a read = GM.unsafeRead {-# INLINE new #-} new :: (PrimMonad m, GM.MVector v a) => Int -> m (v (PrimState m) a) new = GM.unsafeNew {-# INLINE newWith #-} newWith :: (PrimMonad m, GM.MVector v a) => Int -> a -> m (v (PrimState m) a) newWith = GM.unsafeNewWith {-# INLINE drop #-} drop :: G.Vector v a => Int -> v a -> v a drop = G.unsafeDrop {-# INLINE slice #-} slice :: G.Vector v a => Int -> Int -> v a -> v a slice = G.unsafeSlice {-# INLINE minIndex #-} minIndex :: (G.Vector v a, Ord a) => v a -> Int -> Int -> Int minIndex !xs !i !j | xs ! i <= xs ! j = i | otherwise = j {-# INLINE streamM #-} streamM :: (G.Vector v a, Monad m) => v a -> S.MStream m a streamM = S.liftStream . G.stream {-# INLINE (!) #-} (!) :: G.Vector v a => v a -> Int -> a (!) = G.unsafeIndex {-# INLINE getRow #-} getRow :: G.Vector v a => Int -> v a -> Int -> Int -> a getRow !cols !vec !i = (!) row where !row = drop (i * cols) vec