Skip to content

Commit 3b25583

Browse files
Cleanup docs, uncomment some unimplemented signatures
1 parent 4af8b71 commit 3b25583

File tree

1 file changed

+29
-75
lines changed
  • src/Streamly/Internal/Data/Stream/IsStream

1 file changed

+29
-75
lines changed

src/Streamly/Internal/Data/Stream/IsStream/Reduce.hs

Lines changed: 29 additions & 75 deletions
Original file line numberDiff line numberDiff line change
@@ -50,6 +50,7 @@ module Streamly.Internal.Data.Stream.IsStream.Reduce
5050
, splitOn
5151
, splitOnSuffix
5252
, splitOnPrefix
53+
, splitOnAny
5354

5455
-- , splitBy
5556
, splitWithSuffix
@@ -68,7 +69,7 @@ module Streamly.Internal.Data.Stream.IsStream.Reduce
6869

6970
-- Splitting using multiple sequence separators
7071
-- , splitOnAnySeq
71-
-- , splitOnAnySuffixSeq
72+
, splitOnSuffixSeqAny
7273
-- , splitOnAnyPrefixSeq
7374

7475
-- -- *** Splitting By Streams
@@ -125,6 +126,7 @@ module Streamly.Internal.Data.Stream.IsStream.Reduce
125126
-- output stream.
126127

127128
, wordsBy -- stripAndCompactBy
129+
, wordsOn
128130
, groups
129131
, groupsBy
130132
, groupsByRolling
@@ -203,7 +205,7 @@ import Prelude hiding (concatMap, map)
203205
--
204206
-- Space: @O(1)@
205207
--
206-
-- /Unimplemented/ - Help wanted.
208+
-- /Unimplemented/
207209
{-# INLINE dropPrefix #-}
208210
dropPrefix ::
209211
-- (Eq a, IsStream t, Monad m) =>
@@ -215,7 +217,7 @@ dropPrefix = error "Not implemented yet!"
215217
--
216218
-- Space: @O(n)@ where n is the length of the infix.
217219
--
218-
-- /Unimplemented/ - Help wanted.
220+
-- /Unimplemented/
219221
{-# INLINE dropInfix #-}
220222
dropInfix ::
221223
-- (Eq a, IsStream t, Monad m) =>
@@ -227,7 +229,7 @@ dropInfix = error "Not implemented yet!"
227229
--
228230
-- Space: @O(n)@ where n is the length of the suffix.
229231
--
230-
-- /Unimplemented/ - Help wanted.
232+
-- /Unimplemented/
231233
{-# INLINE dropSuffix #-}
232234
dropSuffix ::
233235
-- (Eq a, IsStream t, Monad m) =>
@@ -382,6 +384,10 @@ parseMany
382384
parseMany p m =
383385
fromStreamD $ D.parseMany (PRD.fromParserK p) (toStreamD m)
384386

387+
-- | Same as parseMany but for StreamD streams.
388+
--
389+
-- /Internal/
390+
--
385391
{-# INLINE parseManyD #-}
386392
parseManyD
387393
:: (IsStream t, MonadThrow m)
@@ -394,7 +400,7 @@ parseManyD p m =
394400
-- | Apply a stream of parsers to an input stream and emit the results in the
395401
-- output stream.
396402
--
397-
-- /Pre-release/
403+
-- /Unimplemented/
398404
--
399405
{-# INLINE parseSequence #-}
400406
parseSequence
@@ -446,45 +452,6 @@ parseIterate
446452
parseIterate f i m = fromStreamD $
447453
D.parseIterate (PRD.fromParserK . f) i (toStreamD m)
448454

449-
------------------------------------------------------------------------------
450-
-- Generalized grouping
451-
------------------------------------------------------------------------------
452-
453-
-- This combinator is the most general grouping combinator and can be used to
454-
-- implement all other grouping combinators.
455-
--
456-
-- XXX check if this can implement the splitOn combinator i.e. we can slide in
457-
-- new elements, slide out old elements and incrementally compute the hash.
458-
-- Also, can we implement the windowed classification combinators using this?
459-
--
460-
-- In fact this is a parse. Instead of using a special return value in the fold
461-
-- we are using a mapping function.
462-
--
463-
-- Note that 'scanl'' (usually followed by a map to extract the desired value
464-
-- from the accumulator) can be used to realize many implementations e.g. a
465-
-- sliding window implementation. A scan followed by a mapMaybe is also a good
466-
-- pattern to express many problems where we want to emit a filtered output and
467-
-- not emit an output on every input.
468-
--
469-
-- Passing on of the initial accumulator value to the next fold is equivalent
470-
-- to returning the leftover concept.
471-
472-
{-
473-
-- | @groupScan splitter fold stream@ folds the input stream using @fold@.
474-
-- @splitter@ is applied on the accumulator of the fold every time an item is
475-
-- consumed by the fold. The fold continues until @splitter@ returns a 'Just'
476-
-- value. A 'Just' result from the @splitter@ specifies a result to be emitted
477-
-- in the output stream and the initial value of the accumulator for the next
478-
-- group's fold. This allows us to control whether to start fresh for the next
479-
-- fold or to continue from the previous fold's output.
480-
--
481-
{-# INLINE groupScan #-}
482-
groupScan
483-
:: (IsStream t, Monad m)
484-
=> (x -> m (Maybe (b, x))) -> Fold m a x -> t m a -> t m b
485-
groupScan split fold m = undefined
486-
-}
487-
488455
------------------------------------------------------------------------------
489456
-- Grouping
490457
------------------------------------------------------------------------------
@@ -820,16 +787,16 @@ splitWithSuffix predicate f = foldMany (FL.takeEndBy predicate f)
820787
-- >>> splitList [1,2,3,3,4] [1,2,3,3,4]
821788
-- > [[],[]]
822789

823-
{-
824790
-- This can be implemented easily using Rabin Karp
825791
-- | Split on any one of the given patterns.
792+
--
793+
-- /Unimplemented/
794+
--
826795
{-# INLINE splitOnAny #-}
827-
splitOnAny
828-
:: (IsStream t, Monad m, Storable a, Integral a)
829-
=> [Array a] -> Fold m a b -> t m a -> t m b
830-
splitOnAny subseq f m = undefined
831-
-- fromStreamD $ D.splitOnAny f subseq (toStreamD m)
832-
-}
796+
splitOnAny :: -- (IsStream t, Monad m, Storable a, Integral a) =>
797+
[Array a] -> Fold m a b -> t m a -> t m b
798+
splitOnAny _subseq _f _m =
799+
undefined -- D.fromStreamD $ D.splitOnAny f subseq (D.toStreamD m)
833800

834801
-- XXX use a non-monadic intersperse to remove the MonadAsync constraint.
835802
-- XXX Use two folds, one ring buffer fold for separator sequence and the other
@@ -925,16 +892,14 @@ splitOnSuffixSeq
925892
splitOnSuffixSeq patt f m =
926893
fromStreamD $ D.splitOnSuffixSeq False patt f (toStreamD m)
927894

928-
{-
929895
-- | Like 'splitOn' but drops any empty splits.
930896
--
897+
-- /Unimplemented/
931898
{-# INLINE wordsOn #-}
932-
wordsOn
933-
:: (IsStream t, Monad m, Storable a, Eq a)
934-
=> Array a -> Fold m a b -> t m a -> t m b
935-
wordsOn subseq f m = undefined
936-
-- fromStreamD $ D.wordsOn f subseq (toStreamD m)
937-
-}
899+
wordsOn :: -- (IsStream t, Monad m, Storable a, Eq a) =>
900+
Array a -> Fold m a b -> t m a -> t m b
901+
wordsOn _subseq _f _m =
902+
undefined -- D.fromStreamD $ D.wordsOn f subseq (D.toStreamD m)
938903

939904
-- | Like 'splitOnSuffixSeq' but keeps the suffix intact in the splits.
940905
--
@@ -972,16 +937,15 @@ splitWithSuffixSeq
972937
splitWithSuffixSeq patt f m =
973938
fromStreamD $ D.splitOnSuffixSeq True patt f (toStreamD m)
974939

975-
{-
976940
-- This can be implemented easily using Rabin Karp
977941
-- | Split post any one of the given patterns.
942+
--
943+
-- /Unimplemented/
978944
{-# INLINE splitOnSuffixSeqAny #-}
979-
splitOnSuffixSeqAny
980-
:: (IsStream t, Monad m, Storable a, Integral a)
981-
=> [Array a] -> Fold m a b -> t m a -> t m b
982-
splitOnSuffixSeqAny subseq f m = undefined
983-
-- fromStreamD $ D.splitPostAny f subseq (toStreamD m)
984-
-}
945+
splitOnSuffixSeqAny :: -- (IsStream t, Monad m, Storable a, Integral a) =>
946+
[Array a] -> Fold m a b -> t m a -> t m b
947+
splitOnSuffixSeqAny _subseq _f _m = undefined
948+
-- D.fromStreamD $ D.splitPostAny f subseq (D.toStreamD m)
985949

986950
------------------------------------------------------------------------------
987951
-- Chunking
@@ -1061,16 +1025,6 @@ chunksOfTimeout n timeout f =
10611025
-- Windowed classification
10621026
------------------------------------------------------------------------------
10631027

1064-
-- We divide the stream into windows or chunks in space or time and each window
1065-
-- can be associated with a key, all events associated with a particular key in
1066-
-- the window can be folded to a single result. The stream can be split into
1067-
-- windows by size or by using a split predicate on the elements in the stream.
1068-
-- For example, when we receive a closing flag, we can close the window.
1069-
--
1070-
-- A "chunk" is a space window and a "session" is a time window. Are there any
1071-
-- other better short words to describe them. An alternative is to use
1072-
-- "swindow" and "twindow". Another word for "session" could be "spell".
1073-
--
10741028
-- TODO: To mark the position in space or time we can have Indexed or
10751029
-- TimeStamped types. That can make it easy to deal with the position indices
10761030
-- or timestamps.

0 commit comments

Comments
 (0)