Rename Fold.ltake to Fold.takeLE

This commit is contained in:
Adithya Kumar 2021-01-15 15:22:54 +05:30 committed by Adithya Kumar
parent bdedb6949b
commit 084cdea601
12 changed files with 54 additions and 54 deletions

View File

@ -64,9 +64,9 @@ any value = IP.fold (FL.any (> value))
all :: (Monad m, Ord a) => a -> SerialT m a -> m Bool
all value = IP.fold (FL.all (<= value))
{-# INLINE take #-}
take :: Monad m => Int -> SerialT m a -> m ()
take value = IP.fold (FL.ltake value FL.drain)
{-# INLINE takeLE #-}
takeLE :: Monad m => Int -> SerialT m a -> m ()
takeLE value = IP.fold (FL.takeLE value FL.drain)
-------------------------------------------------------------------------------
-- Splitting by serial application
@ -78,7 +78,7 @@ sliceSepBy value = IP.fold (FL.sliceSepBy (>= value) FL.drain)
{-# INLINE many #-}
many :: Monad m => SerialT m Int -> m ()
many = IP.fold (FL.many FL.drain (FL.ltake 1 FL.drain))
many = IP.fold (FL.many FL.drain (FL.takeLE 1 FL.drain))
{-# INLINE splitAllAny #-}
splitAllAny :: Monad m => Int -> SerialT m Int -> m (Bool, Bool)
@ -229,7 +229,7 @@ o_1_space_serial_elimination value =
, benchIOSink value "notElem" (S.fold (FL.notElem (value + 1)))
, benchIOSink value "all" $ all value
, benchIOSink value "any" $ any value
, benchIOSink value "take" $ take value
, benchIOSink value "takeLE" $ takeLE value
, benchIOSink value "sliceSepBy" $ sliceSepBy value
, benchIOSink value "and" (S.fold FL.and . S.map (<= (value + 1)))
, benchIOSink value "or" (S.fold FL.or . S.map (> (value + 1)))
@ -265,7 +265,7 @@ o_1_space_serial_composition value =
[ benchIOSink value "splitWith (all, any)" $ splitAllAny value
, benchIOSink value "teeApplicative (all, any)"
$ teeApplicative value
, benchIOSink value "many drain (take 1)" many
, benchIOSink value "many drain (takeLE 1)" many
, benchIOSink value "tee (sum, length)" teeSumLength
, benchIOSink value "distribute [sum, length]" distribute
, benchIOSink value "partition (sum, length)" partition

View File

@ -256,7 +256,7 @@ parseMany :: MonadCatch m => SerialT m Int -> m ()
parseMany =
S.drain
. S.map getSum
. IP.parseMany (PR.fromFold $ FL.ltake 2 FL.mconcat)
. IP.parseMany (PR.fromFold $ FL.takeLE 2 FL.mconcat)
. S.map Sum
{-# INLINE parseIterate #-}
@ -264,7 +264,7 @@ parseIterate :: MonadCatch m => SerialT m Int -> m ()
parseIterate =
S.drain
. S.map getSum
. IP.parseIterate (PR.fromFold . FL.ltake 2 . FL.sconcat) (Sum 0)
. IP.parseIterate (PR.fromFold . FL.takeLE 2 . FL.sconcat) (Sum 0)
. S.map Sum
-------------------------------------------------------------------------------

View File

@ -311,12 +311,12 @@ chunksOfSum n inh = S.length $ S.chunksOf n FL.sum (S.unfold FH.read inh)
foldManyChunksOfSum :: Int -> Handle -> IO Int
foldManyChunksOfSum n inh =
S.length $ IP.foldMany (FL.ltake n FL.sum) (S.unfold FH.read inh)
S.length $ IP.foldMany (FL.takeLE n FL.sum) (S.unfold FH.read inh)
parseManyChunksOfSum :: Int -> Handle -> IO Int
parseManyChunksOfSum n inh =
S.length
$ IP.parseMany (PR.fromFold $ FL.ltake n FL.sum) (S.unfold FH.read inh)
$ IP.parseMany (PR.fromFold $ FL.takeLE n FL.sum) (S.unfold FH.read inh)
-- XXX investigate why we need an INLINE in this case (GHC)
-- Even though allocations remain the same in both cases inlining improves time

View File

@ -137,7 +137,7 @@ foldMany :: Monad m => SerialT m Int -> m ()
foldMany =
S.drain
. S.map getSum
. Internal.foldMany (FL.ltake 2 FL.mconcat)
. Internal.foldMany (FL.takeLE 2 FL.mconcat)
. S.map Sum
{-# INLINE _foldIterate #-}
@ -145,7 +145,7 @@ _foldIterate :: Monad m => SerialT m Int -> m ()
_foldIterate =
S.drain
. S.map getSum
. Internal.foldIterate (FL.ltake 2 . FL.sconcat) (Sum 0)
. Internal.foldIterate (FL.takeLE 2 . FL.sconcat) (Sum 0)
. S.map Sum
o_1_space_grouping :: Int -> [Benchmark]

View File

@ -173,7 +173,7 @@ module Streamly.Data.Fold
{-
-- ** Trimming
, ltake
, takeLE
-- takeByTime
, ldrop
, ldropWhile

View File

@ -137,7 +137,7 @@ module Streamly.Internal.Data.Fold
-}
-- ** Trimming
, ltake
, takeLE
, takeByTime
-- By elements
, sliceSepBy
@ -715,10 +715,10 @@ rollingHash = rollingHashWithSalt defaultSalt
-- | Compute an 'Int' sized polynomial rolling hash of the first n elements of
-- a stream.
--
-- > rollingHashFirstN = ltake n rollingHash
-- > rollingHashFirstN = takeLE n rollingHash
{-# INLINABLE rollingHashFirstN #-}
rollingHashFirstN :: (Monad m, Enum a) => Int -> Fold m a Int64
rollingHashFirstN n = ltake n rollingHash
rollingHashFirstN n = takeLE n rollingHash
------------------------------------------------------------------------------
-- Monoidal left folds
@ -826,7 +826,7 @@ toListRevF = mkAccum_ (flip (:)) []
-- and discarding the results.
{-# INLINABLE drainN #-}
drainN :: Monad m => Int -> Fold m a ()
drainN n = ltake n drain
drainN n = takeLE n drain
------------------------------------------------------------------------------
-- To Elements
@ -1056,7 +1056,7 @@ or = any (== True)
-- >>> splitAt_ 4 [1,2,3]
-- > ([1,2,3],[])
--
-- > splitAt n f1 f2 = splitWith (,) (ltake n f1) f2
-- > splitAt n f1 f2 = splitWith (,) (takeLE n f1) f2
--
-- /Internal/
@ -1067,7 +1067,7 @@ splitAt
-> Fold m a b
-> Fold m a c
-> Fold m a (b, c)
splitAt n fld = splitWith (,) (ltake n fld)
splitAt n fld = splitWith (,) (takeLE n fld)
------------------------------------------------------------------------------
-- Element Aware APIs
@ -1176,7 +1176,7 @@ sliceSepBy predicate (Fold fstep finitial fextract) =
{-# INLINABLE sliceSepByMax #-}
sliceSepByMax :: Monad m
=> (a -> Bool) -> Int -> Fold m a b -> Fold m a b
sliceSepByMax p n = sliceSepBy p . ltake n
sliceSepByMax p n = sliceSepBy p . takeLE n
-- | Collect stream elements until an element succeeds the predicate. Also take
-- the element on which the predicate succeeded. The succeeding element is

View File

@ -184,7 +184,7 @@ module Streamly.Internal.Data.Fold.Types
, lfilter
, lfilterM
, lcatMaybes
, ltake
, takeLE
, takeByTime
-- * Distributing
@ -704,18 +704,18 @@ lcatMaybes = lfilter isJust . lmap fromJust
-- | Take at most @n@ input elements and fold them using the supplied fold.
--
-- >>> Stream.fold (Fold.ltake 1 Fold.toList) $ Stream.fromList [1]
-- >>> Stream.fold (Fold.takeLE 1 Fold.toList) $ Stream.fromList [1]
-- [1]
--
-- >>> Stream.fold (Fold.ltake (-1) Fold.toList) $ Stream.fromList [1]
-- >>> Stream.fold (Fold.takeLE (-1) Fold.toList) $ Stream.fromList [1]
-- []
--
-- /Internal/
--
-- @since 0.7.0
{-# INLINE ltake #-}
ltake :: Monad m => Int -> Fold m a b -> Fold m a b
ltake n (Fold fstep finitial fextract) = Fold step initial extract
{-# INLINE takeLE #-}
takeLE :: Monad m => Int -> Fold m a b -> Fold m a b
takeLE n (Fold fstep finitial fextract) = Fold step initial extract
where
@ -862,7 +862,7 @@ many (Fold cstep cinitial cextract) (Fold sstep sinitial sextract) =
-- of @n@ items in the input stream and supplies the result to the @collect@
-- fold.
--
-- > lchunksOf n split collect = many collect (ltake n split)
-- > lchunksOf n split collect = many collect (takeLE n split)
--
-- Stops when @collect@ stops.
--
@ -870,7 +870,7 @@ many (Fold cstep cinitial cextract) (Fold sstep sinitial sextract) =
--
{-# INLINE lchunksOf #-}
lchunksOf :: Monad m => Int -> Fold m a b -> Fold m b c -> Fold m a c
lchunksOf n split collect = many collect (ltake n split)
lchunksOf n split collect = many collect (takeLE n split)
{-# INLINE lchunksOf2 #-}
lchunksOf2 :: Monad m => Int -> Fold m a b -> Fold2 m x b c -> Fold2 m x a c

View File

@ -382,7 +382,7 @@ drain = P.drain
-- |
-- > drainN n = drain . take n
-- > drainN n = fold (Fold.ltake n Fold.drain)
-- > drainN n = fold (Fold.takeLE n Fold.drain)
--
-- Run maximum up to @n@ iterations of a stream.
--

View File

@ -877,7 +877,7 @@ iterateMapLeftsWith combine f = iterateMapWith combine (either f (const K.nil))
-- This is the streaming dual of the 'Streamly.Internal.Data.Fold.many'
-- parse combinator.
--
-- >>> f = Fold.ltake 2 Fold.sum
-- >>> f = Fold.takeLE 2 Fold.sum
-- >>> Stream.toList $ Stream.foldMany f $ Stream.fromList [1..10]
-- > [3,7,11,15,19]
--
@ -912,7 +912,7 @@ foldSequence _f _m = undefined
-- generate the first fold, the fold is applied on the stream and the result of
-- the fold is used to generate the next fold and so on.
--
-- >>> f x = Fold.ltake 2 (Fold.mconcatTo x)
-- >>> f x = Fold.takeLE 2 (Fold.mconcatTo x)
-- >>> s = Stream.map Sum $ Stream.fromList [1..10]
-- >>> Stream.toList $ Stream.map getSum $ Stream.foldIterate f 0 s
-- > [3,10,21,36,55,55]
@ -1535,15 +1535,15 @@ splitOnSuffixSeqAny subseq f m = undefined
-- >> S.toList $ S.chunksOf 2 FL.sum (S.enumerateFromTo 1 10)
-- > [3,7,11,15,19]
--
-- This can be considered as an n-fold version of 'ltake' where we apply
-- 'ltake' repeatedly on the leftover stream until the stream exhausts.
-- This can be considered as an n-fold version of 'takeLE' where we apply
-- 'takeLE' repeatedly on the leftover stream until the stream exhausts.
--
-- @since 0.7.0
{-# INLINE chunksOf #-}
chunksOf
:: (IsStream t, Monad m)
=> Int -> Fold m a b -> t m a -> t m b
chunksOf n f = foldMany (FL.ltake n f)
chunksOf n f = foldMany (FL.takeLE n f)
-- |
--

View File

@ -215,10 +215,10 @@ and ls = S.fold FL.and (S.fromList ls) `shouldReturn` Prelude.and ls
or :: [Bool] -> Expectation
or ls = S.fold FL.or (S.fromList ls) `shouldReturn` Prelude.or ls
ltake :: [Int] -> Property
ltake ls =
takeLE :: [Int] -> Property
takeLE ls =
forAll (chooseInt (-1, Prelude.length ls + 2)) $ \n ->
S.fold (F.ltake n FL.toList) (S.fromList ls)
S.fold (F.takeLE n FL.toList) (S.fromList ls)
`shouldReturn` Prelude.take n ls
sliceSepBy :: Property
@ -443,7 +443,7 @@ main = hspec $
prop "And" Main.and
prop "Or" Main.or
prop "mapMaybe" mapMaybe
prop "ltake" ltake
prop "takeLE" takeLE
prop "sliceSepBy" sliceSepBy
prop "sliceSepByMax" sliceSepByMax
prop "drain" Main.drain

View File

@ -535,8 +535,8 @@ applicative =
forAll (listOf (chooseAny :: Gen Int)) $ \ list2 ->
let parser =
(,)
<$> P.fromFold (FL.ltake (length list1) FL.toList)
<*> P.fromFold (FL.ltake (length list2) FL.toList)
<$> P.fromFold (FL.takeLE (length list1) FL.toList)
<*> P.fromFold (FL.takeLE (length list2) FL.toList)
in monadicIO $ do
(olist1, olist2) <-
run $ S.parse parser (S.fromList $ list1 ++ list2)
@ -546,7 +546,7 @@ applicative =
sequence :: Property
sequence =
forAll (vectorOf 11 (listOf (chooseAny :: Gen Int))) $ \ ins ->
let p xs = P.fromFold (FL.ltake (length xs) FL.toList)
let p xs = P.fromFold (FL.takeLE (length xs) FL.toList)
in monadicIO $ do
outs <- run $
S.parse
@ -559,8 +559,8 @@ monad =
forAll (listOf (chooseAny :: Gen Int)) $ \ list1 ->
forAll (listOf (chooseAny :: Gen Int)) $ \ list2 ->
let parser = do
olist1 <- P.fromFold (FL.ltake (length list1) FL.toList)
olist2 <- P.fromFold (FL.ltake (length list2) FL.toList)
olist1 <- P.fromFold (FL.takeLE (length list1) FL.toList)
olist2 <- P.fromFold (FL.takeLE (length list2) FL.toList)
return (olist1, olist2)
in monadicIO $ do
(olist1, olist2) <-
@ -578,7 +578,7 @@ parseMany =
forAll (listOf (vectorOf len (chooseAny :: Gen Int))) $ \ ins ->
monadicIO $ do
outs <- do
let p = P.fromFold $ FL.ltake len FL.toList
let p = P.fromFold $ FL.takeLE len FL.toList
run
$ S.toList
$ S.parseMany p (S.fromList $ concat ins)

View File

@ -182,7 +182,7 @@ take :: Property
take =
forAll (chooseInt (min_value, max_value)) $ \n ->
forAll (listOf (chooseInt (min_value, max_value))) $ \ls ->
case S.parseD (P.fromFold $ FL.ltake n FL.toList) (S.fromList ls) of
case S.parseD (P.fromFold $ FL.takeLE n FL.toList) (S.fromList ls) of
Right parsed_list -> checkListEqual parsed_list (Prelude.take n ls)
Left _ -> property False
@ -263,7 +263,7 @@ lookAheadPass :: Property
lookAheadPass =
forAll (chooseInt (min_value, max_value)) $ \n ->
let
takeWithoutConsume = P.lookAhead $ P.fromFold $ FL.ltake n FL.toList
takeWithoutConsume = P.lookAhead $ P.fromFold $ FL.takeLE n FL.toList
parseTwice = do
parsed_list_1 <- takeWithoutConsume
parsed_list_2 <- takeWithoutConsume
@ -279,7 +279,7 @@ lookAhead :: Property
lookAhead =
forAll (chooseInt (min_value, max_value)) $ \n ->
let
takeWithoutConsume = P.lookAhead $ P.fromFold $ FL.ltake n FL.toList
takeWithoutConsume = P.lookAhead $ P.fromFold $ FL.takeLE n FL.toList
parseTwice = do
parsed_list_1 <- takeWithoutConsume
parsed_list_2 <- takeWithoutConsume
@ -396,7 +396,7 @@ teeWithPass =
forAll (chooseInt (min_value, max_value)) $ \n ->
forAll (listOf (chooseInt (0, 1))) $ \ls ->
let
prsr = P.fromFold $ FL.ltake n FL.toList
prsr = P.fromFold $ FL.takeLE n FL.toList
in
case S.parseD (P.teeWith (,) prsr prsr) (S.fromList ls) of
Right (ls_1, ls_2) -> checkListEqual (Prelude.take n ls) ls_1 .&&. checkListEqual ls_1 ls_2
@ -536,8 +536,8 @@ applicative =
forAll (listOf (chooseAny :: Gen Int)) $ \ list2 ->
let parser =
(,)
<$> P.fromFold (FL.ltake (length list1) FL.toList)
<*> P.fromFold (FL.ltake (length list2) FL.toList)
<$> P.fromFold (FL.takeLE (length list1) FL.toList)
<*> P.fromFold (FL.takeLE (length list2) FL.toList)
in monadicIO $ do
(olist1, olist2) <-
run $ S.parseD parser (S.fromList $ list1 ++ list2)
@ -547,7 +547,7 @@ applicative =
sequence :: Property
sequence =
forAll (vectorOf 11 (listOf (chooseAny :: Gen Int))) $ \ ins ->
let parsers = fmap (\xs -> P.fromFold $ FL.ltake (length xs) FL.toList) ins
let parsers = fmap (\xs -> P.fromFold $ FL.takeLE (length xs) FL.toList) ins
in monadicIO $ do
outs <- run $
S.parseD
@ -560,8 +560,8 @@ monad =
forAll (listOf (chooseAny :: Gen Int)) $ \ list1 ->
forAll (listOf (chooseAny :: Gen Int)) $ \ list2 ->
let parser = do
olist1 <- P.fromFold (FL.ltake (length list1) FL.toList)
olist2 <- P.fromFold (FL.ltake (length list2) FL.toList)
olist1 <- P.fromFold (FL.takeLE (length list1) FL.toList)
olist2 <- P.fromFold (FL.takeLE (length list2) FL.toList)
return (olist1, olist2)
in monadicIO $ do
(olist1, olist2) <-
@ -582,7 +582,7 @@ parseMany =
( run
$ S.toList
$ S.parseManyD
(P.fromFold $ FL.ltake len FL.toList) (S.fromList $ concat ins)
(P.fromFold $ FL.takeLE len FL.toList) (S.fromList $ concat ins)
)
listEquals (==) outs ins