{-# LANGUAGE TypeFamilies #-} module NoSlow.Backend.StorableVector ( module Data.StorableVector, sum, enumFromTo_Int, zip, pair, fst, snd ) where import NoSlow.Util.Computation import NoSlow.Util.Base ( Unsupported(..) ) import qualified Data.StorableVector as V import Data.StorableVector hiding ( zip ) import Foreign ( Storable ) import Prelude hiding ( sum, fst, snd, zip ) instance DeepSeq (V.Vector a) instance (TestData a, Storable a) => TestData (V.Vector a) where testData n = V.pack (testData n) instance Computation (V.Vector a) where type Arg (V.Vector a) = Nil type Res (V.Vector a) = V.Vector a apply x _ = x sum :: (Num a, Storable a) => V.Vector a -> a {-# INLINE sum #-} sum xs = V.foldl' (+) 0 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) zip = Unsupported pair = Unsupported fst = Unsupported snd = Unsupported