{-# LANGUAGE BangPatterns #-} module Data.RangeMin.Common.Vector (G.create, vlength, write, read, new, newWith, drop, slice, sliceM, unsafeFreeze, minIndex, (!), getRow, G.Vector, GM.MVector, G.Mutable) where import Control.Monad.Primitive import qualified Data.Vector.Generic as G import qualified Data.Vector.Generic.Mutable as GM import Data.RangeMin.Common.Types import Prelude hiding (read, drop) {-# INLINE vlength #-} vlength :: G.Vector v a => v a -> Int vlength = G.length {-# 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 => Index -> Length -> v s a -> v s a sliceM = GM.unsafeSlice {-# INLINE write #-} write :: (PrimMonad m, GM.MVector v a) => v (PrimState m) a -> Index -> a -> m () write = GM.unsafeWrite {-# INLINE read #-} read :: (PrimMonad m, GM.MVector v a) => v (PrimState m) a -> Index -> m a read = GM.unsafeRead {-# INLINE new #-} new :: (PrimMonad m, GM.MVector v a) => Length -> m (v (PrimState m) a) new = GM.unsafeNew {-# INLINE newWith #-} newWith :: (PrimMonad m, GM.MVector v a) => Length -> a -> m (v (PrimState m) a) newWith = GM.unsafeNewWith {-# INLINE drop #-} drop :: G.Vector v a => Length -> v a -> v a drop = G.unsafeDrop {-# INLINE slice #-} slice :: G.Vector v a => Index -> Length -> v a -> v a slice = G.unsafeSlice {-# INLINE minIndex #-} minIndex :: (G.Vector v a, Ord a) => v a -> Index -> Index -> Index minIndex !xs !i !j | xs ! i <= xs ! j = i | otherwise = j {-# INLINE (!) #-} (!) :: G.Vector v a => v a -> Index -> a (!) = G.unsafeIndex {-# INLINE getRow #-} getRow :: G.Vector v a => Length -> v a -> Index -> Index -> a getRow !cols !vec !i = (!) row where !row = drop (i * cols) vec