Skip to content

Commit fbf0526

Browse files
committed
Add foldr' and document the laziness of foldr
1 parent 577d1b6 commit fbf0526

File tree

3 files changed

+37
-0
lines changed

3 files changed

+37
-0
lines changed

src/Data/Text.hs

Lines changed: 24 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -98,6 +98,7 @@ module Data.Text
9898
, foldl1
9999
, foldl1'
100100
, foldr
101+
, foldr'
101102
, foldr1
102103

103104
-- ** Special folds
@@ -988,6 +989,22 @@ foldl1' f t = S.foldl1' f (stream t)
988989
-- | /O(n)/ 'foldr', applied to a binary operator, a starting value
989990
-- (typically the right-identity of the operator), and a 'Text',
990991
-- reduces the 'Text' using the binary operator, from right to left.
992+
--
993+
-- If the binary operator is strict in its second argument, use 'foldr''
994+
-- instead.
995+
--
996+
-- 'foldr' is lazy like 'Data.List.foldr' for lists: evaluation actually
997+
-- traverses the 'Text' from left to right, only as far as it needs to.
998+
--
999+
-- For example, 'head' can be defined with /O(1)/ complexity using 'foldr':
1000+
--
1001+
-- @
1002+
-- head :: Text -> Char
1003+
-- head = foldr const (error "head empty")
1004+
-- @
1005+
--
1006+
-- Searches from left to right with short-circuiting behavior can
1007+
-- also be defined using 'foldr' (/e.g./, 'any', 'all', 'find', 'elem').
9911008
foldr :: (Char -> a -> a) -> a -> Text -> a
9921009
foldr f z t = S.foldr f z (stream t)
9931010
{-# INLINE foldr #-}
@@ -998,6 +1015,13 @@ foldr1 :: HasCallStack => (Char -> Char -> Char) -> Text -> Char
9981015
foldr1 f t = S.foldr1 f (stream t)
9991016
{-# INLINE foldr1 #-}
10001017

1018+
-- | /O(n)/ A strict version of 'foldr'.
1019+
--
1020+
-- 'foldr'' evaluates as a right-to-left traversal using constant stack space.
1021+
foldr' :: (Char -> a -> a) -> a -> Text -> a
1022+
foldr' f z t = S.foldl' (P.flip f) z (reverseStream t)
1023+
{-# INLINE foldr' #-}
1024+
10011025
-- -----------------------------------------------------------------------------
10021026
-- ** Special folds
10031027

src/Data/Text/Lazy.hs

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -780,6 +780,16 @@ foldl1' f t = S.foldl1' f (stream t)
780780
-- | /O(n)/ 'foldr', applied to a binary operator, a starting value
781781
-- (typically the right-identity of the operator), and a 'Text',
782782
-- reduces the 'Text' using the binary operator, from right to left.
783+
--
784+
-- 'foldr' is lazy like 'Data.List.foldr' for lists: evaluation actually
785+
-- traverses the 'Text' from left to right, only as far as it needs to.
786+
--
787+
-- For example, 'head' can be defined with /O(1)/ complexity using 'foldr':
788+
--
789+
-- @
790+
-- head :: Text -> Char
791+
-- head = foldr const (error "head empty")
792+
-- @
783793
foldr :: (Char -> a -> a) -> a -> Text -> a
784794
foldr f z t = S.foldr f z (stream t)
785795
{-# INLINE foldr #-}

tests/Tests/Properties/Folds.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -47,6 +47,8 @@ sf_foldr (applyFun -> p) (applyFun2 -> f) z =
4747
where _types = f :: Char -> Char -> Char
4848
t_foldr (applyFun2 -> f) z = L.foldr f z `eqP` T.foldr f z
4949
where _types = f :: Char -> Char -> Char
50+
t_foldr' (applyFun2 -> f) z = L.foldr f z `eqP` T.foldr' f z
51+
where _types = f :: Char -> Char -> Char
5052
tl_foldr (applyFun2 -> f) z = L.foldr f z `eqPSqrt` TL.foldr f z
5153
where _types = f :: Char -> Char -> Char
5254
sf_foldr1 (applyFun -> p) (applyFun2 -> f) =
@@ -187,6 +189,7 @@ testFolds =
187189
testProperty "tl_foldl1'" tl_foldl1',
188190
testProperty "sf_foldr" sf_foldr,
189191
testProperty "t_foldr" t_foldr,
192+
testProperty "t_foldr'" t_foldr',
190193
testProperty "tl_foldr" tl_foldr,
191194
testProperty "sf_foldr1" sf_foldr1,
192195
testProperty "t_foldr1" t_foldr1,

0 commit comments

Comments
 (0)