diff --git a/vector/src/Data/Vector.hs b/vector/src/Data/Vector.hs index 34568234..f7abb860 100644 --- a/vector/src/Data/Vector.hs +++ b/vector/src/Data/Vector.hs @@ -1929,7 +1929,7 @@ iscanl' :: (Int -> a -> b -> a) -> a -> Vector b -> Vector a {-# INLINE iscanl' #-} iscanl' = G.iscanl' --- | /O(n)/ Scan over a non-empty vector +-- | /O(n)/ Initial-value free scan over a vector -- -- > scanl f = -- > where y1 = x1 @@ -1939,7 +1939,7 @@ scanl1 :: (a -> a -> a) -> Vector a -> Vector a {-# INLINE scanl1 #-} scanl1 = G.scanl1 --- | /O(n)/ Scan over a non-empty vector with a strict accumulator +-- | /O(n)/ Initial-value free scan over a vector with a strict accumulator scanl1' :: (a -> a -> a) -> Vector a -> Vector a {-# INLINE scanl1' #-} scanl1' = G.scanl1' @@ -1993,12 +1993,12 @@ iscanr' :: (Int -> a -> b -> b) -> b -> Vector a -> Vector b {-# INLINE iscanr' #-} iscanr' = G.iscanr' --- | /O(n)/ Right-to-left scan over a non-empty vector +-- | /O(n)/ Right-to-left, initial-value free scan over a vector scanr1 :: (a -> a -> a) -> Vector a -> Vector a {-# INLINE scanr1 #-} scanr1 = G.scanr1 --- | /O(n)/ Right-to-left scan over a non-empty vector with a strict +-- | /O(n)/ Right-to-left, initial-value free scan over a vector with a strict -- accumulator scanr1' :: (a -> a -> a) -> Vector a -> Vector a {-# INLINE scanr1' #-} diff --git a/vector/src/Data/Vector/Fusion/Bundle.hs b/vector/src/Data/Vector/Fusion/Bundle.hs index 6c4f1414..75af55d2 100644 --- a/vector/src/Data/Vector/Fusion/Bundle.hs +++ b/vector/src/Data/Vector/Fusion/Bundle.hs @@ -475,12 +475,12 @@ scanl' :: (a -> b -> a) -> a -> Bundle v b -> Bundle v a {-# INLINE scanl' #-} scanl' = M.scanl' --- | Scan over a non-empty 'Bundle' +-- | Initial-value free scan over a 'Bundle' scanl1 :: (a -> a -> a) -> Bundle v a -> Bundle v a {-# INLINE scanl1 #-} scanl1 = M.scanl1 --- | Scan over a non-empty 'Bundle' with a strict accumulator +-- | Initial-value free scan over a 'Bundle' with a strict accumulator scanl1' :: (a -> a -> a) -> Bundle v a -> Bundle v a {-# INLINE scanl1' #-} scanl1' = M.scanl1' diff --git a/vector/src/Data/Vector/Fusion/Bundle/Monadic.hs b/vector/src/Data/Vector/Fusion/Bundle/Monadic.hs index 6b6b8133..beedcf83 100644 --- a/vector/src/Data/Vector/Fusion/Bundle/Monadic.hs +++ b/vector/src/Data/Vector/Fusion/Bundle/Monadic.hs @@ -749,23 +749,23 @@ scanlM' :: Monad m => (a -> b -> m a) -> a -> Bundle m v b -> Bundle m v a {-# INLINE scanlM' #-} scanlM' f z s = z `seq` (z `cons` postscanlM f z s) --- | Scan over a non-empty 'Bundle' +-- | Initial-value free scan over a 'Bundle' scanl1 :: Monad m => (a -> a -> a) -> Bundle m v a -> Bundle m v a {-# INLINE scanl1 #-} scanl1 f = scanl1M (\x y -> return (f x y)) --- | Scan over a non-empty 'Bundle' with a monadic operator +-- | Initial-value free scan over a 'Bundle' with a monadic operator scanl1M :: Monad m => (a -> a -> m a) -> Bundle m v a -> Bundle m v a {-# INLINE_FUSED scanl1M #-} scanl1M f Bundle{sElems = s, sSize = sz} = fromStream (S.scanl1M f s) sz --- | Scan over a non-empty 'Bundle' with a strict accumulator +-- | Initial-value free scan over a 'Bundle' with a strict accumulator scanl1' :: Monad m => (a -> a -> a) -> Bundle m v a -> Bundle m v a {-# INLINE scanl1' #-} scanl1' f = scanl1M' (\x y -> return (f x y)) --- | Scan over a non-empty 'Bundle' with a strict accumulator and a monadic --- operator +-- | Initial-value free scan over a 'Bundle' with a strict accumulator +-- and a monadic operator scanl1M' :: Monad m => (a -> a -> m a) -> Bundle m v a -> Bundle m v a {-# INLINE_FUSED scanl1M' #-} scanl1M' f Bundle{sElems = s, sSize = sz} = fromStream (S.scanl1M' f s) sz diff --git a/vector/src/Data/Vector/Fusion/Stream/Monadic.hs b/vector/src/Data/Vector/Fusion/Stream/Monadic.hs index b081af60..599e4a40 100644 --- a/vector/src/Data/Vector/Fusion/Stream/Monadic.hs +++ b/vector/src/Data/Vector/Fusion/Stream/Monadic.hs @@ -1262,12 +1262,12 @@ scanlM' :: Monad m => (a -> b -> m a) -> a -> Stream m b -> Stream m a {-# INLINE scanlM' #-} scanlM' f z s = z `seq` (z `cons` postscanlM f z s) --- | Scan over a non-empty 'Stream' +-- | Initial-value free scan over a 'Stream' scanl1 :: Monad m => (a -> a -> a) -> Stream m a -> Stream m a {-# INLINE scanl1 #-} scanl1 f = scanl1M (\x y -> return (f x y)) --- | Scan over a non-empty 'Stream' with a monadic operator +-- | Initial-value free scan over a 'Stream' with a monadic operator scanl1M :: Monad m => (a -> a -> m a) -> Stream m a -> Stream m a {-# INLINE_FUSED scanl1M #-} scanl1M f (Stream step t) = Stream step' (t, Nothing) @@ -1278,7 +1278,7 @@ scanl1M f (Stream step t) = Stream step' (t, Nothing) case r of Yield x s' -> return $ Yield x (s', Just x) Skip s' -> return $ Skip (s', Nothing) - Done -> EMPTY_STREAM "scanl1M" + Done -> return Done step' (s, Just x) = do r <- step s @@ -1289,13 +1289,13 @@ scanl1M f (Stream step t) = Stream step' (t, Nothing) Skip s' -> return $ Skip (s', Just x) Done -> return Done --- | Scan over a non-empty 'Stream' with a strict accumulator +-- | Initial-value free scan over a 'Stream' with a strict accumulator scanl1' :: Monad m => (a -> a -> a) -> Stream m a -> Stream m a {-# INLINE scanl1' #-} scanl1' f = scanl1M' (\x y -> return (f x y)) --- | Scan over a non-empty 'Stream' with a strict accumulator and a monadic --- operator +-- | Initial-value free scan over a 'Stream' with a strict accumulator +-- and a monadic operator scanl1M' :: Monad m => (a -> a -> m a) -> Stream m a -> Stream m a {-# INLINE_FUSED scanl1M' #-} scanl1M' f (Stream step t) = Stream step' (t, Nothing) @@ -1306,7 +1306,7 @@ scanl1M' f (Stream step t) = Stream step' (t, Nothing) case r of Yield x s' -> x `seq` return (Yield x (s', Just x)) Skip s' -> return $ Skip (s', Nothing) - Done -> EMPTY_STREAM "scanl1M" + Done -> return Done step' (s, Just x) = x `seq` do diff --git a/vector/src/Data/Vector/Generic.hs b/vector/src/Data/Vector/Generic.hs index 286f2d96..9c740dfe 100644 --- a/vector/src/Data/Vector/Generic.hs +++ b/vector/src/Data/Vector/Generic.hs @@ -2111,7 +2111,7 @@ iscanl' f z = . stream --- | /O(n)/ Scan over a non-empty vector +-- | /O(n)/ Initial-value free scan over a vector -- -- > scanl f = -- > where y1 = x1 @@ -2121,7 +2121,7 @@ scanl1 :: Vector v a => (a -> a -> a) -> v a -> v a {-# INLINE scanl1 #-} scanl1 f = unstream . inplace (S.scanl1 f) id . stream --- | /O(n)/ Scan over a non-empty vector with a strict accumulator +-- | /O(n)/ Initial-value free scan over a vector with a strict accumulator scanl1' :: Vector v a => (a -> a -> a) -> v a -> v a {-# INLINE scanl1' #-} scanl1' f = unstream . inplace (S.scanl1' f) id . stream @@ -2181,12 +2181,12 @@ iscanr' f z v = $ v where n = length v --- | /O(n)/ Right-to-left scan over a non-empty vector +-- | /O(n)/ Right-to-left, initial-value free scan over a vector scanr1 :: Vector v a => (a -> a -> a) -> v a -> v a {-# INLINE scanr1 #-} scanr1 f = unstreamR . inplace (S.scanl1 (flip f)) id . streamR --- | /O(n)/ Right-to-left scan over a non-empty vector with a strict +-- | /O(n)/ Right-to-left, initial-value free scan over a vector with a strict -- accumulator scanr1' :: Vector v a => (a -> a -> a) -> v a -> v a {-# INLINE scanr1' #-} diff --git a/vector/src/Data/Vector/Primitive.hs b/vector/src/Data/Vector/Primitive.hs index d9c5b16a..7f562fb2 100644 --- a/vector/src/Data/Vector/Primitive.hs +++ b/vector/src/Data/Vector/Primitive.hs @@ -1582,7 +1582,7 @@ iscanl' :: (Prim a, Prim b) => (Int -> a -> b -> a) -> a -> Vector b -> Vector a iscanl' = G.iscanl' --- | /O(n)/ Scan over a non-empty vector +-- | /O(n)/ Initial-value free scan over a vector -- -- > scanl f = -- > where y1 = x1 @@ -1592,7 +1592,7 @@ scanl1 :: Prim a => (a -> a -> a) -> Vector a -> Vector a {-# INLINE scanl1 #-} scanl1 = G.scanl1 --- | /O(n)/ Scan over a non-empty vector with a strict accumulator +-- | /O(n)/ Initial-value free scan over a vector with a strict accumulator scanl1' :: Prim a => (a -> a -> a) -> Vector a -> Vector a {-# INLINE scanl1' #-} scanl1' = G.scanl1' @@ -1646,12 +1646,12 @@ iscanr' :: (Prim a, Prim b) => (Int -> a -> b -> b) -> b -> Vector a -> Vector b {-# INLINE iscanr' #-} iscanr' = G.iscanr' --- | /O(n)/ Right-to-left scan over a non-empty vector +-- | /O(n)/ Right-to-left, initial-value free scan over a vector scanr1 :: Prim a => (a -> a -> a) -> Vector a -> Vector a {-# INLINE scanr1 #-} scanr1 = G.scanr1 --- | /O(n)/ Right-to-left scan over a non-empty vector with a strict +-- | /O(n)/ Right-to-left, initial-value free scan over a vector with a strict -- accumulator scanr1' :: Prim a => (a -> a -> a) -> Vector a -> Vector a {-# INLINE scanr1' #-} diff --git a/vector/src/Data/Vector/Storable.hs b/vector/src/Data/Vector/Storable.hs index 8df04b7e..b2a62619 100644 --- a/vector/src/Data/Vector/Storable.hs +++ b/vector/src/Data/Vector/Storable.hs @@ -1628,7 +1628,7 @@ iscanl' :: (Storable a, Storable b) => (Int -> a -> b -> a) -> a -> Vector b -> {-# INLINE iscanl' #-} iscanl' = G.iscanl' --- | /O(n)/ Scan over a non-empty vector +-- | /O(n)/ Initial-value free scan over a vector -- -- > scanl f = -- > where y1 = x1 @@ -1638,7 +1638,7 @@ scanl1 :: Storable a => (a -> a -> a) -> Vector a -> Vector a {-# INLINE scanl1 #-} scanl1 = G.scanl1 --- | /O(n)/ Scan over a non-empty vector with a strict accumulator +-- | /O(n)/ Initial-value free scan over a vector with a strict accumulator scanl1' :: Storable a => (a -> a -> a) -> Vector a -> Vector a {-# INLINE scanl1' #-} scanl1' = G.scanl1' @@ -1692,12 +1692,12 @@ iscanr' :: (Storable a, Storable b) => (Int -> a -> b -> b) -> b -> Vector a -> {-# INLINE iscanr' #-} iscanr' = G.iscanr' --- | /O(n)/ Right-to-left scan over a non-empty vector +-- | /O(n)/ Right-to-left, initial-value free scan over a vector scanr1 :: Storable a => (a -> a -> a) -> Vector a -> Vector a {-# INLINE scanr1 #-} scanr1 = G.scanr1 --- | /O(n)/ Right-to-left scan over a non-empty vector with a strict +-- | /O(n)/ Right-to-left, initial-value free scan over a vector with a strict -- accumulator scanr1' :: Storable a => (a -> a -> a) -> Vector a -> Vector a {-# INLINE scanr1' #-} diff --git a/vector/src/Data/Vector/Unboxed.hs b/vector/src/Data/Vector/Unboxed.hs index 707117c4..d4072863 100644 --- a/vector/src/Data/Vector/Unboxed.hs +++ b/vector/src/Data/Vector/Unboxed.hs @@ -1678,7 +1678,7 @@ iscanl' :: (Unbox a, Unbox b) => (Int -> a -> b -> a) -> a -> Vector b -> Vector {-# INLINE iscanl' #-} iscanl' = G.iscanl' --- | /O(n)/ Scan over a non-empty vector +-- | /O(n)/ Initial-value free scan over a vector -- -- > scanl f = -- > where y1 = x1 @@ -1688,7 +1688,7 @@ scanl1 :: Unbox a => (a -> a -> a) -> Vector a -> Vector a {-# INLINE scanl1 #-} scanl1 = G.scanl1 --- | /O(n)/ Scan over a non-empty vector with a strict accumulator +-- | /O(n)/ Initial-value free scan over a vector with a strict accumulator scanl1' :: Unbox a => (a -> a -> a) -> Vector a -> Vector a {-# INLINE scanl1' #-} scanl1' = G.scanl1' @@ -1742,12 +1742,12 @@ iscanr' :: (Unbox a, Unbox b) => (Int -> a -> b -> b) -> b -> Vector a -> Vector {-# INLINE iscanr' #-} iscanr' = G.iscanr' --- | /O(n)/ Right-to-left scan over a non-empty vector +-- | /O(n)/ Right-to-left, initial-value free scan over a vector scanr1 :: Unbox a => (a -> a -> a) -> Vector a -> Vector a {-# INLINE scanr1 #-} scanr1 = G.scanr1 --- | /O(n)/ Right-to-left scan over a non-empty vector with a strict +-- | /O(n)/ Right-to-left, initial-value free scan over a vector with a strict -- accumulator scanr1' :: Unbox a => (a -> a -> a) -> Vector a -> Vector a {-# INLINE scanr1' #-} diff --git a/vector/tests/Tests/Vector/Property.hs b/vector/tests/Tests/Vector/Property.hs index 0367b47f..797abea0 100644 --- a/vector/tests/Tests/Vector/Property.hs +++ b/vector/tests/Tests/Vector/Property.hs @@ -395,10 +395,10 @@ testPolymorphicFunctions _ = $(testProperties [ = V.scanl `eq` scanl prop_scanl' :: P ((a -> a -> a) -> a -> v a -> v a) = V.scanl' `eq` scanl - prop_scanl1 :: P ((a -> a -> a) -> v a -> v a) = notNull2 ===> - V.scanl1 `eq` scanl1 - prop_scanl1' :: P ((a -> a -> a) -> v a -> v a) = notNull2 ===> - V.scanl1' `eq` scanl1 + prop_scanl1 :: P ((a -> a -> a) -> v a -> v a) + = V.scanl1 `eq` scanl1 + prop_scanl1' :: P ((a -> a -> a) -> v a -> v a) + = V.scanl1' `eq` scanl1 prop_iscanl :: P ((Int -> a -> a -> a) -> a -> v a -> v a) = V.iscanl `eq` iscanl prop_iscanl' :: P ((Int -> a -> a -> a) -> a -> v a -> v a) @@ -420,10 +420,10 @@ testPolymorphicFunctions _ = $(testProperties [ = V.iscanr `eq` iscanr prop_iscanr' :: P ((Int -> a -> a -> a) -> a -> v a -> v a) = V.iscanr' `eq` iscanr - prop_scanr1 :: P ((a -> a -> a) -> v a -> v a) = notNull2 ===> - V.scanr1 `eq` scanr1 - prop_scanr1' :: P ((a -> a -> a) -> v a -> v a) = notNull2 ===> - V.scanr1' `eq` scanr1 + prop_scanr1 :: P ((a -> a -> a) -> v a -> v a) + = V.scanr1 `eq` scanr1 + prop_scanr1' :: P ((a -> a -> a) -> v a -> v a) + = V.scanr1' `eq` scanr1 prop_concatMap = forAll arbitrary $ \xs -> forAll (sized (\n -> resize (n `div` V.length xs) arbitrary)) $ \f -> unP prop f xs