----------------------------------------------------------------------------- -- | -- Module : Data.Vector.Dense.Class.Views -- Copyright : Copyright (c) , Patrick Perry -- License : BSD3 -- Maintainer : Patrick Perry -- Stability : experimental -- module Data.Vector.Dense.Class.Views ( -- * Vector views subvector, subvectorWithStride, unsafeSubvector, unsafeSubvectorWithStride, ) where import BLAS.Internal ( checkedSubvector, checkedSubvectorWithStride ) import Data.Vector.Dense.Class.Internal import Foreign -- | @subvector x o n@ creates a subvector view of @x@ starting at index @o@ -- and having length @n@. subvector :: (BaseVector x, Storable e) => x n e -> Int -> Int -> x n' e subvector x = checkedSubvector (dim x) (unsafeSubvector x) {-# INLINE subvector #-} unsafeSubvector :: (BaseVector x, Storable e) => x n e -> Int -> Int -> x n' e unsafeSubvector = unsafeSubvectorWithStride 1 {-# INLINE unsafeSubvector #-} -- | @subvectorWithStride s x o n@ creates a subvector view of @x@ starting -- at index @o@, having length @n@ and stride @s@. subvectorWithStride :: (BaseVector x, Storable e) => Int -> x n e -> Int -> Int -> x n' e subvectorWithStride s x = checkedSubvectorWithStride s (dim x) (unsafeSubvectorWithStride s x) {-# INLINE subvectorWithStride #-} unsafeSubvectorWithStride :: (BaseVector x, Storable e) => Int -> x n e -> Int -> Int -> x n' e unsafeSubvectorWithStride s' x o' n' = let (f,p,_,s,c) = arrayFromVector x in vectorViewArray f (p `advancePtr` (s*o')) n' (s*s') c