Repository : ssh://g...@git.haskell.org/vector On branch : ghc-head Link : http://git.haskell.org/packages/vector.git/commitdiff/7f29cf73fdd8b8183f00ddffb9d765e09c2a5817
>--------------------------------------------------------------- commit 7f29cf73fdd8b8183f00ddffb9d765e09c2a5817 Author: Roman Leshchinskiy <r...@cse.unsw.edu.au> Date: Tue Jan 31 23:22:47 2012 +0000 fromVectorStream -> concatVectors >--------------------------------------------------------------- 7f29cf73fdd8b8183f00ddffb9d765e09c2a5817 Data/Vector/Fusion/Stream.hs | 8 ++++---- Data/Vector/Fusion/Stream/Monadic.hs | 8 ++++---- Data/Vector/Generic.hs | 2 +- 3 files changed, 9 insertions(+), 9 deletions(-) diff --git a/Data/Vector/Fusion/Stream.hs b/Data/Vector/Fusion/Stream.hs index 0740abd..fdadd9d 100644 --- a/Data/Vector/Fusion/Stream.hs +++ b/Data/Vector/Fusion/Stream.hs @@ -68,7 +68,7 @@ module Data.Vector.Fusion.Stream ( -- * Conversions toList, fromList, fromListN, unsafeFromList, liftStream, - fromVector, reVector, fromVectors, fromVectorStream, + fromVector, reVector, fromVectors, concatVectors, -- * Monadic combinators mapM, mapM_, zipWithM, zipWithM_, filterM, foldM, fold1M, foldM', fold1M', @@ -618,9 +618,9 @@ fromVectors :: Vector v a => [v a] -> Facets v a {-# INLINE fromVectors #-} fromVectors = M.fromVectors -fromVectorStream :: Vector v a => Facets u (v a) -> Facets v a -{-# INLINE fromVectorStream #-} -fromVectorStream = M.fromVectorStream +concatVectors :: Vector v a => Facets u (v a) -> Facets v a +{-# INLINE concatVectors #-} +concatVectors = M.concatVectors -- | Create a 'Facets' of values from a 'Facets' of streamable things flatten :: (a -> s) -> (s -> Step s b) -> Size -> Facets v a -> Facets v b diff --git a/Data/Vector/Fusion/Stream/Monadic.hs b/Data/Vector/Fusion/Stream/Monadic.hs index 4f788df..8f6f5ab 100644 --- a/Data/Vector/Fusion/Stream/Monadic.hs +++ b/Data/Vector/Fusion/Stream/Monadic.hs @@ -76,7 +76,7 @@ module Data.Vector.Fusion.Stream.Monadic ( -- * Conversions toList, fromList, fromListN, unsafeFromList, - fromVector, reVector, fromVectors, fromVectorStream + fromVector, reVector, fromVectors, concatVectors ) where import Data.Vector.Generic.Base @@ -1706,9 +1706,9 @@ fromVectors vs = Facets (Unf pstep (Left vs)) (\mv -> basicUnsafeCopy mv v)) vs -fromVectorStream :: (Monad m, Vector v a) => Facets m u (v a) -> Facets m v a -{-# INLINE_STREAM fromVectorStream #-} -fromVectorStream Facets{sElems = Unf step s} +concatVectors :: (Monad m, Vector v a) => Facets m u (v a) -> Facets m v a +{-# INLINE_STREAM concatVectors #-} +concatVectors Facets{sElems = Unf step s} = Facets (Unf pstep (Left s)) (Unf vstep s) Nothing diff --git a/Data/Vector/Generic.hs b/Data/Vector/Generic.hs index 397d8d0..9172377 100644 --- a/Data/Vector/Generic.hs +++ b/Data/Vector/Generic.hs @@ -1001,7 +1001,7 @@ concatMap f = unstream -- This seems to be fastest now concatMap f = unstream - . Stream.fromVectorStream + . Stream.concatVectors . Stream.map f . stream _______________________________________________ ghc-commits mailing list ghc-commits@haskell.org http://www.haskell.org/mailman/listinfo/ghc-commits