Merge pull request #228 from composewell/hide-modules

Hide modules whose apis have not yet been finalised for 0.7.0
This commit is contained in:
Harendra Kumar 2019-07-31 02:34:48 +05:30 committed by GitHub
commit 82c090d6ab
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
8 changed files with 65 additions and 55 deletions

View File

@ -35,16 +35,9 @@ multiple folds without breaking the stream. Combinators are provided for
temporal and spatial window based fold operations, for example, to support temporal and spatial window based fold operations, for example, to support
folding and aggregating data for timeout or inactivity based sessions. folding and aggregating data for timeout or inactivity based sessions.
#### Composable Pipes
`Streamly.Pipes` module provides composable pipes (stream consumers and
producers). Pipes can partition, split or distribute a stream into multiple
streams, apply transformations on each stream and merge back the results into a
single stream.
#### Streaming File IO #### Streaming File IO
`Streamly.FileSystem.File` provides handle based streaming file IO `Streamly.FileSystem.Handle` provides handle based streaming file IO
operations. operations.
#### Streaming Network IO #### Streaming Network IO

View File

@ -20,7 +20,7 @@ import qualified LinearOps as Ops
import Streamly import Streamly
import qualified Streamly.Fold as FL import qualified Streamly.Fold as FL
import qualified Streamly.Pipe as Pipe --import qualified Streamly.Pipe as Pipe
import qualified Streamly.Mem.Array as A import qualified Streamly.Mem.Array as A
import qualified Streamly.Prelude as S import qualified Streamly.Prelude as S
-- import qualified Streamly.Sink as Sink -- import qualified Streamly.Sink as Sink
@ -242,15 +242,15 @@ main =
, bgroup "folds-transforms" , bgroup "folds-transforms"
[ benchIOSink "drain" (FL.foldl' FL.drain) [ benchIOSink "drain" (FL.foldl' FL.drain)
, benchIOSink "lmap" (FL.foldl' (FL.lmap (+1) FL.drain)) , benchIOSink "lmap" (FL.foldl' (FL.lmap (+1) FL.drain))
, benchIOSink "pipe-mapM" {-, benchIOSink "pipe-mapM"
(FL.foldl' (FL.transform (Pipe.mapM (\x -> return $ x + 1)) FL.drain)) (FL.foldl' (FL.transform (Pipe.mapM (\x -> return $ x + 1)) FL.drain))-}
] ]
, bgroup "folds-compositions" -- Applicative , bgroup "folds-compositions" -- Applicative
[ [
benchIOSink "all,any" (FL.foldl' ((,) <$> FL.all (<= Ops.maxValue) benchIOSink "all,any" (FL.foldl' ((,) <$> FL.all (<= Ops.maxValue)
<*> FL.any (> Ops.maxValue))) <*> FL.any (> Ops.maxValue)))
, benchIOSink "sum,length" (FL.foldl' ((,) <$> FL.sum <*> FL.length)) , benchIOSink "sum,length" (FL.foldl' ((,) <$> FL.sum <*> FL.length))
] ] {-
, bgroup "pipes" , bgroup "pipes"
[ benchIOSink "mapM" (Ops.transformMapM serially 1) [ benchIOSink "mapM" (Ops.transformMapM serially 1)
, benchIOSink "compose" (Ops.transformComposeMapM serially 1) , benchIOSink "compose" (Ops.transformComposeMapM serially 1)
@ -262,7 +262,7 @@ main =
, benchIOSink "compose" (Ops.transformComposeMapM serially 4) , benchIOSink "compose" (Ops.transformComposeMapM serially 4)
, benchIOSink "tee" (Ops.transformTeeMapM serially 4) , benchIOSink "tee" (Ops.transformTeeMapM serially 4)
, benchIOSink "zip" (Ops.transformZipMapM serially 4) , benchIOSink "zip" (Ops.transformZipMapM serially 4)
] ] -}
, bgroup "transformation" , bgroup "transformation"
[ benchIOSink "scanl" (Ops.scan 1) [ benchIOSink "scanl" (Ops.scan 1)
, benchIOSink "scanl1'" (Ops.scanl1' 1) , benchIOSink "scanl1'" (Ops.scanl1' 1)

View File

@ -30,7 +30,7 @@ import GHC.Generics (Generic)
import qualified Streamly as S hiding (foldMapWith, runStream) import qualified Streamly as S hiding (foldMapWith, runStream)
import qualified Streamly.Prelude as S import qualified Streamly.Prelude as S
import qualified Streamly.Pipe as Pipe -- import qualified Streamly.Pipe as Pipe
value, maxValue, value2 :: Int value, maxValue, value2 :: Int
#ifdef LINEAR_ASYNC #ifdef LINEAR_ASYNC
@ -370,14 +370,9 @@ scan, scanl1', map, fmap, mapMaybe, filterEven, filterAllOut,
mapMaybeM, intersperse :: S.MonadAsync m => Int -> Stream m Int -> m () mapMaybeM, intersperse :: S.MonadAsync m => Int -> Stream m Int -> m ()
{-# INLINE mapM #-} {-# INLINE mapM #-}
{-# INLINE transformMapM #-}
{-# INLINE transformComposeMapM #-}
{-# INLINE transformTeeMapM #-}
{-# INLINE transformZipMapM #-}
{-# INLINE map' #-} {-# INLINE map' #-}
{-# INLINE fmap' #-} {-# INLINE fmap' #-}
mapM, map', transformMapM, transformComposeMapM, transformTeeMapM, mapM, map' :: (S.IsStream t, S.MonadAsync m)
transformZipMapM :: (S.IsStream t, S.MonadAsync m)
=> (t m Int -> S.SerialT m Int) -> Int -> t m Int -> m () => (t m Int -> S.SerialT m Int) -> Int -> t m Int -> m ()
fmap' :: (S.IsStream t, S.MonadAsync m, P.Functor (t m)) fmap' :: (S.IsStream t, S.MonadAsync m, P.Functor (t m))
@ -395,6 +390,18 @@ map n = composeN n $ S.map (+1)
map' t n = composeN' n $ t . S.map (+1) map' t n = composeN' n $ t . S.map (+1)
mapM t n = composeN' n $ t . S.mapM return mapM t n = composeN' n $ t . S.mapM return
-- Temporarily commented these ops as they depend on the hidden
-- Pipe module.
{-
{-# INLINE transformMapM #-}
{-# INLINE transformComposeMapM #-}
{-# INLINE transformTeeMapM #-}
{-# INLINE transformZipMapM #-}
transformMapM, transformComposeMapM, transformTeeMapM,
transformZipMapM :: (S.IsStream t, S.MonadAsync m)
=> (t m Int -> S.SerialT m Int) -> Int -> t m Int -> m ()
transformMapM t n = composeN' n $ t . S.transform (Pipe.mapM return) transformMapM t n = composeN' n $ t . S.transform (Pipe.mapM return)
transformComposeMapM t n = composeN' n $ t . S.transform transformComposeMapM t n = composeN' n $ t . S.transform
(Pipe.mapM (\x -> return (x + 1)) (Pipe.mapM (\x -> return (x + 1))
@ -405,6 +412,7 @@ transformTeeMapM t n = composeN' n $ t . S.transform
transformZipMapM t n = composeN' n $ t . S.transform transformZipMapM t n = composeN' n $ t . S.transform
(Pipe.zipWith (+) (Pipe.mapM (\x -> return (x + 1))) (Pipe.zipWith (+) (Pipe.mapM (\x -> return (x + 1)))
(Pipe.mapM (\x -> return (x + 2)))) (Pipe.mapM (\x -> return (x + 2))))
-}
mapMaybe n = composeN n $ S.mapMaybe mapMaybe n = composeN n $ S.mapMaybe
(\x -> if Prelude.odd x then Nothing else Just x) (\x -> if Prelude.odd x then Nothing else Just x)

View File

@ -9,21 +9,24 @@ import System.Environment (getArgs)
import Streamly import Streamly
import Streamly.String import Streamly.String
import qualified Streamly.FileSystem.File as File import qualified Streamly.FileSystem.Handle as FH
import qualified Streamly.Fold as FL import qualified Streamly.Fold as FL
import qualified Streamly.Mem.Array as A import qualified Streamly.Mem.Array as A
import qualified Streamly.Network.Socket as NS import qualified Streamly.Network.Socket as NS
import qualified Streamly.Network.Server as NS import qualified Streamly.Network.Server as NS
import qualified Streamly.Prelude as S import qualified Streamly.Prelude as S
import System.IO (withFile, IOMode(..))
main :: IO () main :: IO ()
main = do main = do
file <- fmap head getArgs file <- fmap head getArgs
File.append file withFile file AppendMode
(\src -> FH.write src
$ encodeChar8Unchecked $ encodeChar8Unchecked
$ S.concatMap A.read $ S.concatMap A.read
$ S.concatMapBy parallel (flip NS.withSocketS recv) $ S.concatMapBy parallel (flip NS.withSocketS recv)
$ NS.connectionsOnAllAddrs 8090 $ NS.connectionsOnAllAddrs 8090)
where where

View File

@ -7,10 +7,14 @@ import System.Environment (getArgs)
import Streamly import Streamly
import qualified Streamly.Prelude as S import qualified Streamly.Prelude as S
import qualified Streamly.FileSystem.File as File import qualified Streamly.FileSystem.Handle as FH
import qualified Streamly.Network.Client as Client import qualified Streamly.Network.Client as Client
import System.IO (withFile, IOMode(..))
main :: IO () main :: IO ()
main = main =
let sendFile = Client.writeArrays (127,0,0,1) 8090 . File.readArrays let sendFile file =
in getArgs >>= S.drain . parallely . S.mapM sendFile . S.fromList withFile file ReadMode $ \src ->
Client.writeArrays (127, 0, 0, 1) 8090 $ FH.readArrays src
in getArgs >>= S.drain . parallely . S.mapM sendFile . S.fromList

View File

@ -136,7 +136,7 @@ module Streamly.Fold
, mapM , mapM
-- ** Mapping -- ** Mapping
, transform --, transform
, lmap , lmap
--, lsequence --, lsequence
, lmapM , lmapM
@ -320,6 +320,7 @@ module Streamly.Fold
-- , chunksOf -- , chunksOf
, duplicate -- experimental , duplicate -- experimental
{-
-- * Windowed Classification -- * Windowed Classification
-- | Split the stream into windows or chunks in space or time. Each window -- | Split the stream into windows or chunks in space or time. Each window
-- can be associated with a key, all events associated with a particular -- can be associated with a key, all events associated with a particular
@ -333,13 +334,13 @@ module Streamly.Fold
-- ** Tumbling Windows -- ** Tumbling Windows
-- | A new window starts after the previous window is finished. -- | A new window starts after the previous window is finished.
-- , classifyChunksOf -- , classifyChunksOf
, classifySessionsOf -- , classifySessionsOf
-- ** Keep Alive Windows -- ** Keep Alive Windows
-- | The window size is extended if an event arrives within the specified -- | The window size is extended if an event arrives within the specified
-- window size. This can represent sessions with idle or inactive timeout. -- window size. This can represent sessions with idle or inactive timeout.
-- , classifyKeepAliveChunks -- , classifyKeepAliveChunks
, classifyKeepAliveSessions -- , classifyKeepAliveSessions
{- {-
-- ** Sliding Windows -- ** Sliding Windows
@ -351,6 +352,7 @@ module Streamly.Fold
-- ** Sliding Window Buffers -- ** Sliding Window Buffers
-- , slidingChunkBuffer -- , slidingChunkBuffer
-- , slidingSessionBuffer -- , slidingSessionBuffer
-}
) )
where where
@ -492,9 +494,9 @@ mapM f = sequence . fmap f
-- | Apply a transformation on a 'Fold' using a 'Pipe'. -- | Apply a transformation on a 'Fold' using a 'Pipe'.
-- --
-- @since 0.7.0 -- @since 0.7.0
{-# INLINE transform #-} {-# INLINE _transform #-}
transform :: Monad m => Pipe m a b -> Fold m b c -> Fold m a c _transform :: Monad m => Pipe m a b -> Fold m b c -> Fold m a c
transform (Pipe pstep1 pstep2 pinitial) (Fold fstep finitial fextract) = _transform (Pipe pstep1 pstep2 pinitial) (Fold fstep finitial fextract) =
Fold step initial extract Fold step initial extract
where where
@ -2636,14 +2638,14 @@ classifySessionsBy tick timeout reset (Fold step initial extract) str =
-- only if no event is received within the specified session window size. -- only if no event is received within the specified session window size.
-- --
-- @since 0.7.0 -- @since 0.7.0
{-# INLINABLE classifyKeepAliveSessions #-} {-# INLINABLE _classifyKeepAliveSessions #-}
classifyKeepAliveSessions _classifyKeepAliveSessions
:: (IsStream t, MonadAsync m, Ord k) :: (IsStream t, MonadAsync m, Ord k)
=> Double -- ^ session inactive timeout => Double -- ^ session inactive timeout
-> Fold m a b -- ^ Fold to be applied to session payload data -> Fold m a b -- ^ Fold to be applied to session payload data
-> t m (k, a, Bool, AbsTime) -- ^ session key, data, close flag, timestamp -> t m (k, a, Bool, AbsTime) -- ^ session key, data, close flag, timestamp
-> t m (k, b) -> t m (k, b)
classifyKeepAliveSessions timeout = classifySessionsBy 1 timeout True _classifyKeepAliveSessions timeout = classifySessionsBy 1 timeout True
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
-- Keyed tumbling windows -- Keyed tumbling windows
@ -2685,11 +2687,11 @@ classifyChunksOf wsize = classifyChunksBy wsize False
-- the timestamps with a clock resolution of 1 second. -- the timestamps with a clock resolution of 1 second.
-- --
-- @since 0.7.0 -- @since 0.7.0
{-# INLINABLE classifySessionsOf #-} {-# INLINABLE _classifySessionsOf #-}
classifySessionsOf _classifySessionsOf
:: (IsStream t, MonadAsync m, Ord k) :: (IsStream t, MonadAsync m, Ord k)
=> Double -- ^ time window size => Double -- ^ time window size
-> Fold m a b -- ^ Fold to be applied to window events -> Fold m a b -- ^ Fold to be applied to window events
-> t m (k, a, Bool, AbsTime) -- ^ window key, data, close flag, timestamp -> t m (k, a, Bool, AbsTime) -- ^ window key, data, close flag, timestamp
-> t m (k, b) -> t m (k, b)
classifySessionsOf interval = classifySessionsBy 1 interval False _classifySessionsOf interval = classifySessionsBy 1 interval False

View File

@ -240,7 +240,7 @@ module Streamly.Prelude
-- * Transformation -- * Transformation
, transform --, transform
-- ** Mapping -- ** Mapping
-- | In imperative terms a map operation can be considered as a loop over -- | In imperative terms a map operation can be considered as a loop over
@ -1581,9 +1581,9 @@ toHandle h m = go m
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
-- | Use a 'Pipe' to transform a stream. -- | Use a 'Pipe' to transform a stream.
{-# INLINE transform #-} {-# INLINE _transform #-}
transform :: (IsStream t, Monad m) => Pipe m a b -> t m a -> t m b _transform :: (IsStream t, Monad m) => Pipe m a b -> t m a -> t m b
transform pipe xs = fromStreamD $ D.transform pipe (toStreamD xs) _transform pipe xs = fromStreamD $ D.transform pipe (toStreamD xs)
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
-- Transformation by Folding (Scans) -- Transformation by Folding (Scans)

View File

@ -204,28 +204,28 @@ library
, Streamly.Sink.Types , Streamly.Sink.Types
, Streamly.Sink , Streamly.Sink
, Streamly.Pipe.Types , Streamly.Pipe.Types
, Streamly.Pipe
, Streamly.FileSystem.IOVec , Streamly.FileSystem.IOVec
, Streamly.FileSystem.FDIO , Streamly.FileSystem.FDIO
exposed-modules: Streamly.Prelude
, Streamly.Time
, Streamly
, Streamly.Fold
, Streamly.Pipe
, Streamly.String
-- IO devices
, Streamly.Mem.Array
, Streamly.FileSystem.FD , Streamly.FileSystem.FD
, Streamly.FileSystem.Handle
, Streamly.FileSystem.File , Streamly.FileSystem.File
-- Time -- Time
, Streamly.Time.Units , Streamly.Time.Units
, Streamly.Time.Clock , Streamly.Time.Clock
exposed-modules: Streamly.Prelude
, Streamly.Time
, Streamly
, Streamly.Fold
, Streamly.String
-- IO devices
, Streamly.Mem.Array
, Streamly.FileSystem.Handle
, Streamly.Tutorial , Streamly.Tutorial
, Streamly.Internal , Streamly.Internal
if !impl(ghcjs) if !impl(ghcjs)
@ -1041,7 +1041,7 @@ executable FileIOExamples
hs-source-dirs: examples hs-source-dirs: examples
ghc-options: -Wall ghc-options: -Wall
if flag(examples) || flag(examples-sdl) if flag(examples) || flag(examples-sdl)
buildable: True buildable: False
build-Depends: build-Depends:
streamly streamly
, base >= 4.8 && < 5 , base >= 4.8 && < 5