{-# LANGUAGE TypeFamilies #-} module NoSlow.Backend.StorableVector ( module Data.StorableVector, imap, slice, sum, and, enumFromTo_Int, prescanl', prescanr', backpermute, update, update_, minIndex, maxIndex, unstablePartition, zip, zip3, unzip, pair, from2, fst, snd, triple, from3 ) where import NoSlow.Util.Computation import NoSlow.Util.Base ( Unsupported(..) ) import qualified Data.StorableVector as V import Data.StorableVector hiding ( zip, unzip ) import Foreign ( Storable ) import Prelude hiding ( sum, and, fst, snd, zip, zip3, unzip ) instance DeepSeq (V.Vector a) instance (TestData a, Storable a) => TestData (V.Vector a) where testData = testList instance Storable a => ListLike V.Vector a where fromList = V.pack imap :: (Storable a, Storable b) => (Int -> a -> b) -> V.Vector a -> V.Vector b {-# INLINE imap #-} imap = V.mapIndexed slice :: Storable a => V.Vector a -> Int -> Int -> V.Vector a {-# INLINE slice #-} slice xs i n = V.take n (V.drop i xs) sum :: (Num a, Storable a) => V.Vector a -> a {-# INLINE sum #-} sum xs = V.foldl' (+) 0 xs and :: V.Vector Bool -> Bool {-# INLINE and #-} and xs = V.foldl' (&&) True xs enumFromTo_Int :: Int -> Int -> V.Vector Int {-# INLINE enumFromTo_Int #-} enumFromTo_Int m n = V.sample len (\i -> i+m) where len = max 0 (n-m+1) prescanl' :: (Storable a, Storable b) => (a -> b -> a) -> a -> V.Vector b -> V.Vector a {-# INLINE prescanl' #-} prescanl' f z v = V.init (V.scanl f z v) prescanr' :: (Storable a, Storable b) => (a -> b -> b) -> b -> V.Vector a -> V.Vector b {-# INLINE prescanr' #-} prescanr' f z v = V.tail (V.scanr f z v) backpermute :: Storable a => V.Vector a -> V.Vector Int -> V.Vector a {-# INLINE backpermute #-} backpermute xs is = xs `seq` V.map (V.index xs) is update = Unsupported update_ = Unsupported minIndex = Unsupported maxIndex = Unsupported unstablePartition :: Storable a => (a -> Bool) -> V.Vector a -> (V.Vector a, V.Vector a) {-# INLINE unstablePartition #-} unstablePartition f xs = (V.filter f xs, V.filter (not . f) xs) zip = Unsupported zip3 = Unsupported unzip = Unsupported pair = Unsupported from2 = Unsupported fst = Unsupported snd = Unsupported triple = Unsupported from3 = Unsupported