{-# LANGUAGE TypeFamilies, CPP #-} module NoSlow.Backend.Vector.Storable ( module Data.Vector.Storable, enumFromTo_Int, index, append, update, zip, zip3, unzip, pair, from2, fst, snd, triple, from3 ) where import NoSlow.Util.Computation import NoSlow.Util.Base ( Unsupported(..) ) import qualified Data.Vector.Storable as V import Data.Vector.Storable import Prelude hiding ( fst, snd, zip, zip3, unzip ) instance DeepSeq (V.Vector a) instance (TestData a, V.Storable a) => TestData (V.Vector a) where testData = testList instance V.Storable a => ListLike V.Vector a where fromList = V.fromList enumFromTo_Int :: Int -> Int -> V.Vector Int {-# INLINE enumFromTo_Int #-} enumFromTo_Int = V.enumFromTo index :: V.Storable a => V.Vector a -> Int -> a {-# INLINE index #-} index = (V.!) append :: V.Storable a => V.Vector a -> V.Vector a -> V.Vector a {-# INLINE append #-} append = (V.++) update = Unsupported zip = Unsupported zip3 = Unsupported unzip = Unsupported pair = Unsupported from2 = Unsupported fst = Unsupported snd = Unsupported triple = Unsupported from3 = Unsupported