Skip to content

Commit

Permalink
Legalize scanl1/scanr1 over an empty vector
Browse files Browse the repository at this point in the history
Now scanl1, scanl1', scanr1, scanr1' gives an empty vector for an
empty input.
The definitions of these functions working on vectors,
bundles and streams, the documentations attached to these
definitions, and the related tests are correspondingly modified.

In the former definition, the functions scanl1 and scanr1 refused to
process empty vector and simply errorred.
However these functions could, and now they do, simply return an empty
vector in case of the absence of elements, as the corresponding
functions in Data.List in base do.
With this modification,
@ postscanl' (<>) mempty @
can be rewritten to more generally applicable
@ scanl1' (<>) @.
  • Loading branch information
gksato committed Apr 24, 2021
1 parent 6b024a0 commit 0a9f106
Show file tree
Hide file tree
Showing 9 changed files with 42 additions and 42 deletions.
8 changes: 4 additions & 4 deletions vector/src/Data/Vector.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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 <x1,...,xn> = <y1,...,yn>
-- > where y1 = x1
Expand All @@ -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'
Expand Down Expand Up @@ -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' #-}
Expand Down
4 changes: 2 additions & 2 deletions vector/src/Data/Vector/Fusion/Bundle.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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'
Expand Down
10 changes: 5 additions & 5 deletions vector/src/Data/Vector/Fusion/Bundle/Monadic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
14 changes: 7 additions & 7 deletions vector/src/Data/Vector/Fusion/Stream/Monadic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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)
Expand All @@ -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
Expand All @@ -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)
Expand All @@ -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
Expand Down
8 changes: 4 additions & 4 deletions vector/src/Data/Vector/Generic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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 <x1,...,xn> = <y1,...,yn>
-- > where y1 = x1
Expand All @@ -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
Expand Down Expand Up @@ -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' #-}
Expand Down
8 changes: 4 additions & 4 deletions vector/src/Data/Vector/Primitive.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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 <x1,...,xn> = <y1,...,yn>
-- > where y1 = x1
Expand All @@ -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'
Expand Down Expand Up @@ -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' #-}
Expand Down
8 changes: 4 additions & 4 deletions vector/src/Data/Vector/Storable.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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 <x1,...,xn> = <y1,...,yn>
-- > where y1 = x1
Expand All @@ -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'
Expand Down Expand Up @@ -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' #-}
Expand Down
8 changes: 4 additions & 4 deletions vector/src/Data/Vector/Unboxed.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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 <x1,...,xn> = <y1,...,yn>
-- > where y1 = x1
Expand All @@ -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'
Expand Down Expand Up @@ -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' #-}
Expand Down
16 changes: 8 additions & 8 deletions vector/tests/Tests/Vector/Property.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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)
Expand All @@ -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
Expand Down

0 comments on commit 0a9f106

Please sign in to comment.