Deprecate Streamly.Prelude & S.Internal.Data.Stream.IsStream.*

This commit is contained in:
Adithya Kumar 2022-10-19 22:55:46 +05:30
parent 326b05570e
commit 5327f181db
87 changed files with 223 additions and 38 deletions

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-------------------------------------------------------------------------------
-- Investigate specific benchmarks more closely in isolation, possibly looking
-- at GHC generated code for optimizing specific problematic cases.

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
{-# LANGUAGE CPP #-}
#include "Streamly/Benchmark/Data/Array/CommonImports.hs"

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
{-# LANGUAGE CPP #-}
#include "Streamly/Benchmark/Data/Array/CommonImports.hs"

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Benchmark.Data.ParserD
-- Copyright : (c) 2020 Composewell Technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
{-# LANGUAGE CPP #-}
#include "Streamly/Benchmark/Data/Array/CommonImports.hs"

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Benchmark.Data.Array.Unboxed.Mut
-- Copyright : (c) 2021 Composewell Technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
module Main (main) where
import Control.DeepSeq (NFData)

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Benchmark.Data.Parser
-- Copyright : (c) 2020 Composewell Technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Benchmark.Data.ParserD
-- Copyright : (c) 2020 Composewell Technologies

View File

@ -9,6 +9,10 @@
-- License : BSD-3-Clause
-- Maintainer : streamly@composewell.com
#ifdef USE_PRELUDE
{-# OPTIONS_GHC -Wno-deprecations #-}
#endif
module Stream.Common
( MonadAsync

View File

@ -9,6 +9,10 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE RankNTypes #-}
#ifdef USE_PRELUDE
{-# OPTIONS_GHC -Wno-deprecations #-}
#endif
#ifdef __HADDOCK_VERSION__
#undef INSPECTION
#endif

View File

@ -10,6 +10,10 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}
#ifdef USE_PRELUDE
{-# OPTIONS_GHC -Wno-deprecations #-}
#endif
#ifdef __HADDOCK_VERSION__
#undef INSPECTION
#endif

View File

@ -10,6 +10,10 @@
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TupleSections #-}
#ifdef USE_PRELUDE
{-# OPTIONS_GHC -Wno-deprecations #-}
#endif
#ifdef __HADDOCK_VERSION__
#undef INSPECTION
#endif

View File

@ -9,6 +9,10 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE RankNTypes #-}
#ifdef USE_PRELUDE
{-# OPTIONS_GHC -Wno-deprecations #-}
#endif
module Stream.Generate (benchmarks) where
import Data.Functor.Identity (Identity)

View File

@ -9,6 +9,10 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE RankNTypes #-}
#ifdef USE_PRELUDE
{-# OPTIONS_GHC -Wno-deprecations #-}
#endif
module Stream.Lift (benchmarks) where
import Control.DeepSeq (NFData(..))

View File

@ -11,6 +11,10 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE RankNTypes #-}
#ifdef USE_PRELUDE
{-# OPTIONS_GHC -Wno-deprecations #-}
#endif
module Stream.Reduce (benchmarks) where
import Control.DeepSeq (NFData(..))

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Stream.Split
-- Copyright : (c) 2019 Composewell Technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Benchmark.Data.Stream.StreamDK
-- Copyright : (c) 2018 Composewell Technologies

View File

@ -9,6 +9,10 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE RankNTypes #-}
#ifdef USE_PRELUDE
{-# OPTIONS_GHC -Wno-deprecations #-}
#endif
#ifdef __HADDOCK_VERSION__
#undef INSPECTION
#endif

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Benchmark.FileSystem.Handle
-- Copyright : (c) 2019 Composewell Technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Benchmark.FileSystem.Handle
-- Copyright : (c) 2019 Composewell Technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Main
-- Copyright : (c) 2018 Composewell Technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Main
-- Copyright : (c) 2018 Composewell Technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Main
-- Copyright : (c) 2018 Composewell Technologies

View File

@ -1,3 +1,4 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE RankNTypes #-}
-- |

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Main
-- Copyright : (c) 2018 Composewell Technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Main
-- Copyright : (c) 2018 Composewell Technologies

View File

@ -1,3 +1,4 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
{-# LANGUAGE FlexibleContexts #-}
-- |

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Main
-- Copyright : (c) 2018 Composewell Technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Main
-- Copyright : (c) 2018 Composewell Technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Main
-- Copyright : (c) 2018 Composewell Technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Main
-- Copyright : (c) 2018 Composewell Technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
--
-- Module : Streamly.Unicode.Char
-- Copyright : (c) 2021 Composewell Technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
--
-- Module : Streamly.Unicode.Stream
-- Copyright : (c) 2019 Composewell Technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Benchmark.Prelude
-- Copyright : (c) 2018 Composewell Technologies

View File

@ -146,10 +146,10 @@ import qualified Streamly.Internal.Data.Stream.StreamK.Type as K (mkStream)
-- >>> import qualified Streamly.Data.Array.Unboxed as Array
-- >>> import qualified Streamly.Data.Fold as Fold
-- >>> import qualified Streamly.Data.Unfold as Unfold
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import qualified Streamly.Data.Stream as Stream
--
-- >>> import qualified Streamly.Internal.Data.Array.Unboxed.Type as Array (writeNUnsafe)
-- >>> import qualified Streamly.Internal.Data.Stream.IsStream as Stream
-- >>> import qualified Streamly.Internal.Data.Stream as Stream
-- >>> import qualified Streamly.Internal.Data.Unfold as Unfold (first)
-- >>> import qualified Streamly.Internal.FileSystem.Handle as Handle
-- >>> import qualified Streamly.Internal.System.IO as IO (defaultChunkSize)
@ -410,7 +410,7 @@ putChunk h arr = A.asPtrUnsafe arr $ \ptr ->
-- XXX use an unfold to fromObjects or fromUnfold so that we can put any object
-- | Write a stream of arrays to a handle.
--
-- >>> putChunks h = Stream.mapM_ (Handle.putChunk h)
-- >>> putChunks h = Stream.fold (Fold.drainBy (Handle.putChunk h))
--
-- @since 0.7.0
{-# INLINE putChunks #-}

View File

@ -30,7 +30,8 @@ import Prelude hiding (String, lines, words, unlines, unwords)
-- >>> :m
-- >>> :set -XOverloadedStrings
-- >>> import Prelude hiding (String, lines, words, unlines, unwords)
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import qualified Streamly.Data.Stream as Stream
-- >>> import qualified Streamly.Data.Fold as Fold
-- >>> import qualified Streamly.Internal.Unicode.Array.Char as Unicode
-- | Break a string up into a stream of strings at newline characters.
@ -38,7 +39,7 @@ import Prelude hiding (String, lines, words, unlines, unwords)
--
-- > lines = S.lines A.write
--
-- >>> Stream.toList $ Unicode.lines $ Stream.fromList "lines\nthis\nstring\n\n\n"
-- >>> Stream.fold Fold.toList $ Unicode.lines $ Stream.fromList "lines\nthis\nstring\n\n\n"
-- ["lines","this","string","",""]
--
{-# INLINE lines #-}
@ -50,7 +51,7 @@ lines = S.lines A.write
--
-- > words = S.words A.write
--
-- >>> Stream.toList $ Unicode.words $ Stream.fromList "A newline\nis considered white space?"
-- >>> Stream.fold Fold.toList $ Unicode.words $ Stream.fromList "A newline\nis considered white space?"
-- ["A","newline","is","considered","white","space?"]
--
{-# INLINE words #-}
@ -62,7 +63,7 @@ words = S.words A.write
--
-- 'unlines' is an inverse operation to 'lines'.
--
-- >>> Stream.toList $ Unicode.unlines $ Stream.fromList ["lines", "this", "string"]
-- >>> Stream.fold Fold.toList $ Unicode.unlines $ Stream.fromList ["lines", "this", "string"]
-- "lines\nthis\nstring\n"
--
-- > unlines = S.unlines A.read
@ -79,7 +80,7 @@ unlines = S.unlines A.reader
--
-- 'unwords' is an inverse operation to 'words'.
--
-- >>> Stream.toList $ Unicode.unwords $ Stream.fromList ["unwords", "this", "string"]
-- >>> Stream.fold Fold.toList $ Unicode.unwords $ Stream.fromList ["unwords", "this", "string"]
-- "unwords this string"
--
-- > unwords = S.unwords A.read

View File

@ -128,7 +128,7 @@ import Prelude hiding (lines, words, unlines, unwords)
-- >>> :m
-- >>> :set -XMagicHash
-- >>> import Prelude hiding (lines, words, unlines, unwords)
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import qualified Streamly.Data.Stream as Stream
-- >>> import qualified Streamly.Data.Fold as Fold
-- >>> import qualified Streamly.Internal.Unicode.Stream as Unicode
-- >>> import Streamly.Internal.Unicode.Stream
@ -1066,7 +1066,7 @@ stripHead = Stream.dropWhile isSpace
-- | Fold each line of the stream using the supplied 'Fold'
-- and stream the result.
--
-- >>> Stream.toList $ lines Fold.toList (Stream.fromList "lines\nthis\nstring\n\n\n")
-- >>> Stream.fold Fold.toList $ lines Fold.toList (Stream.fromList "lines\nthis\nstring\n\n\n")
-- ["lines","this","string","",""]
--
-- > lines = Stream.splitOnSuffix (== '\n')
@ -1097,7 +1097,7 @@ isSpace c
-- | Fold each word of the stream using the supplied 'Fold'
-- and stream the result.
--
-- >>> Stream.toList $ words Fold.toList (Stream.fromList "fold these words")
-- >>> Stream.fold Fold.toList $ words Fold.toList (Stream.fromList "fold these words")
-- ["fold","these","words"]
--
-- > words = Stream.wordsBy isSpace

View File

@ -87,7 +87,7 @@ module User.Tutorials.ConcurrentStreams
)
where
import Streamly.Prelude
import Streamly.Data.Stream
import Data.Semigroup
import Control.Applicative
import Control.Monad
@ -96,8 +96,11 @@ import Control.Monad.Trans.Class (MonadTrans (lift))
-- CAUTION: please keep setup and imports sections in sync
-- XXX This tutorial has to be rewritten.
-- $setup
-- >>> :m
-- >>> :set -fno-warn-deprecations
-- >>> import Data.Function ((&))
-- >>> import Streamly.Prelude ((|:), (|&))
-- >>> import qualified Streamly.Prelude as Stream

View File

@ -20,7 +20,7 @@ module User.Tutorials.ReactiveProgramming
)
where
import Streamly.Prelude
import Streamly.Data.Stream
import Data.Semigroup
import Control.Applicative
import Control.Monad

View File

@ -74,7 +74,7 @@ module User.Tutorials.Tutorial
)
where
import Streamly.Prelude
import Streamly.Data.Stream
import Data.Semigroup
import Control.Applicative
import Control.Monad
@ -83,8 +83,11 @@ import Control.Monad.Trans.Class (MonadTrans (lift))
-- CAUTION: please keep setup and imports sections in sync
-- XXX This tutorial has to be re-written.
-- $setup
-- >>> :m
-- >>> :set -fno-warn-deprecations
-- >>> import Data.Function ((&))
-- >>> import Streamly.Prelude ((|:), (|&))
-- >>> import qualified Streamly.Prelude as Stream

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly
-- Copyright : (c) 2017 Composewell Technologies

View File

@ -97,6 +97,7 @@ import Streamly.Internal.Data.Array.Unboxed as A
-- $setup
-- >>> :m
-- >>> :set -fno-warn-deprecations
-- >>> :set -XFlexibleContexts
-- >>> :set -package streamly
-- >>> import Streamly.Internal.Data.Stream (Stream)

View File

@ -28,6 +28,7 @@ import Streamly.Internal.Data.Tuple.Strict (Tuple3'(..))
-- $setup
-- >>> :m
-- >>> :set -fno-warn-deprecations
-- >>> :set -XFlexibleContexts
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import qualified Streamly.Data.Fold as Fold

View File

@ -64,6 +64,7 @@ import Prelude hiding (map)
#include "Instances.hs"
-- $setup
-- >>> :set -fno-warn-deprecations
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import Control.Concurrent (threadDelay)
-- >>> :{

View File

@ -73,6 +73,7 @@ import Streamly.Internal.Data.SVar
#include "Instances.hs"
-- $setup
-- >>> :set -fno-warn-deprecations
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import Control.Concurrent (threadDelay)
-- >>> :{

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Internal.Data.Stream.IsStream
-- Copyright : (c) 2017 Composewell Technologies
@ -10,7 +12,7 @@
-- module "Streamly.Prelude". It contains some additional unreleased or
-- experimental APIs.
module Streamly.Internal.Data.Stream.IsStream
module Streamly.Internal.Data.Stream.IsStream {-# DEPRECATED "Please use \"Streamly.Data.Stream\", \"Streamly.Data.Stream.Concurrent\", & \"Streamly.Data.Stream.Time\" instead." #-}
( module Streamly.Internal.Data.Stream.IsStream.Type
, module Streamly.Internal.Data.Stream.IsStream.Generate
, module Streamly.Internal.Data.Stream.IsStream.Eliminate

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Internal.Data.Stream.Combinators
-- Copyright : (c) 2017 Composewell Technologies
@ -7,7 +9,7 @@
-- Portability : GHC
--
--
module Streamly.Internal.Data.Stream.IsStream.Combinators
module Streamly.Internal.Data.Stream.IsStream.Combinators {-# DEPRECATED "Please use \"Streamly.Data.Stream.*\" instead." #-}
( maxThreads
, maxBuffer
, maxYields

View File

@ -1,3 +1,4 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
{-# OPTIONS_GHC -Wno-orphans #-}
-- |
@ -11,7 +12,7 @@
-- Bottom level IsStream module that can be used by all other upper level
-- IsStream modules.
module Streamly.Internal.Data.Stream.IsStream.Common
module Streamly.Internal.Data.Stream.IsStream.Common {-# DEPRECATED "Please use \"Streamly.Data.Stream.*\" instead." #-}
(
-- * Generation
fromPure
@ -98,6 +99,7 @@ import Prelude hiding (take, takeWhile, drop, reverse, concatMap, map, zipWith)
--
-- $setup
-- >>> :m
-- >>> :set -fno-warn-deprecations
-- >>> import Control.Concurrent (threadDelay)
-- >>> import Control.Monad (join)
-- >>> import Control.Monad.Trans.Class (lift)

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Internal.Data.Stream.IsStream.Eliminate
-- Copyright : (c) 2017 Composewell Technologies
@ -15,7 +17,7 @@
-- We call them stream folding functions, they reduce a stream @t m a@ to a
-- monadic value @m b@.
module Streamly.Internal.Data.Stream.IsStream.Eliminate
module Streamly.Internal.Data.Stream.IsStream.Eliminate {-# DEPRECATED "Please use \"Streamly.Data.Stream.*\" instead." #-}
(
-- * Running Examples
-- $setup
@ -188,6 +190,7 @@ import Prelude hiding
-- $setup
-- >>> :m
-- >>> :set -fno-warn-deprecations
-- >>> import Streamly.Prelude (SerialT)
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import qualified Streamly.Internal.Data.Stream.IsStream as Stream

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Internal.Data.Stream.Enumeration
-- Copyright : (c) 2018 Composewell Technologies
@ -20,7 +22,7 @@
-- in this module can be used to define them. Alternatively, these functions
-- can be used directly.
module Streamly.Internal.Data.Stream.IsStream.Enumeration
module Streamly.Internal.Data.Stream.IsStream.Enumeration {-# DEPRECATED "Please use \"Streamly.Data.Stream.*\" instead." #-}
(
Enumerable (..)
@ -77,6 +79,7 @@ import qualified Streamly.Internal.Data.Stream.StreamD as D
import qualified Streamly.Internal.Data.Stream.Serial as Serial (map)
-- $setup
-- >>> :set -fno-warn-deprecations
-- >>> import Streamly.Prelude as Stream
-- >>> import Streamly.Internal.Data.Stream.IsStream.Enumeration as Stream

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Internal.Data.Stream.IsStream.Exception
-- Copyright : (c) 2019 Composewell Technologies
@ -6,7 +8,7 @@
-- Stability : experimental
-- Portability : GHC
module Streamly.Internal.Data.Stream.IsStream.Exception
module Streamly.Internal.Data.Stream.IsStream.Exception {-# DEPRECATED "Please use \"Streamly.Data.Stream.*\" instead." #-}
(
before
, after_
@ -46,6 +48,7 @@ import qualified Streamly.Internal.Data.Stream.StreamD.Exception as D
-- $setup
-- >>> :m
-- >>> :set -fno-warn-deprecations
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import qualified Streamly.Internal.Data.Stream.IsStream as Stream (nilM)

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Internal.Data.Stream.IsStream.Expand
-- Copyright : (c) 2017 Composewell Technologies
@ -9,7 +11,7 @@
-- Expand a stream by combining two or more streams or by combining streams
-- with unfolds.
module Streamly.Internal.Data.Stream.IsStream.Expand
module Streamly.Internal.Data.Stream.IsStream.Expand {-# DEPRECATED "Please use \"Streamly.Data.Stream.*\" instead." #-}
(
-- * Binary Combinators (Linear)
-- | Functions ending in the shape:
@ -190,6 +192,7 @@ import Prelude hiding (concat, concatMap, zipWith)
-- $setup
-- >>> :m
-- >>> :set -fno-warn-deprecations
-- >>> import Control.Concurrent (threadDelay)
-- >>> import Data.IORef
-- >>> import Prelude hiding (zipWith, concatMap, concat)

View File

@ -1,3 +1,4 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
{-# OPTIONS_GHC -Wno-orphans #-}
-- |
@ -15,7 +16,7 @@
-- as StreamK when StreamK is used, avoiding conversion to StreamD. Will that
-- help? Are there any other reasons to keep these and not use unfolds?
module Streamly.Internal.Data.Stream.IsStream.Generate
module Streamly.Internal.Data.Stream.IsStream.Generate {-# DEPRECATED "Please use \"Streamly.Data.Stream.*\" instead." #-}
(
-- * Primitives
IsStream.nil
@ -124,6 +125,7 @@ import Prelude hiding (iterate, replicate, repeat)
-- $setup
-- >>> :m
-- >>> :set -fno-warn-deprecations
-- >>> import Data.Function ((&))
-- >>> import Prelude hiding (iterate, replicate, repeat)
-- >>> import qualified Streamly.Prelude as Stream

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Internal.Data.Stream.IsStream.Lift
-- Copyright : (c) 2019 Composewell Technologies
@ -6,7 +8,7 @@
-- Stability : experimental
-- Portability : GHC
module Streamly.Internal.Data.Stream.IsStream.Lift
module Streamly.Internal.Data.Stream.IsStream.Lift {-# DEPRECATED "Please use \"Streamly.Data.Stream.*\" instead." #-}
(
-- * Generalize Inner Monad
hoist

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Internal.Data.Stream.IsStream.Reduce
-- Copyright : (c) 2017 Composewell Technologies
@ -8,7 +10,7 @@
--
-- Reduce streams by streams, folds or parsers.
module Streamly.Internal.Data.Stream.IsStream.Reduce
module Streamly.Internal.Data.Stream.IsStream.Reduce {-# DEPRECATED "Please use \"Streamly.Data.Stream.*\" instead." #-}
(
-- * Reduce By Streams
dropPrefix
@ -211,6 +213,7 @@ import Prelude hiding (concatMap, map)
-- $setup
-- >>> :m
-- >>> :set -fno-warn-deprecations
-- >>> import Prelude hiding (zipWith, concatMap, concat)
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import Streamly.Internal.Data.Stream.IsStream as Stream

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Internal.Data.Stream.IsStream.Top
-- Copyright : (c) 2020 Composewell Technologies
@ -9,7 +11,7 @@
-- Top level IsStream module that can use all other lower level IsStream
-- modules.
module Streamly.Internal.Data.Stream.IsStream.Top
module Streamly.Internal.Data.Stream.IsStream.Top {-# DEPRECATED "Please use \"Streamly.Data.Stream.*\" instead." #-}
(
-- * Transformation
-- ** Sampling
@ -87,6 +89,7 @@ import Prelude hiding (filter, zipWith, concatMap, concat)
-- $setup
-- >>> :m
-- >>> :set -fno-warn-deprecations
-- >>> import Prelude hiding (filter, zipWith, concatMap, concat)
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import qualified Streamly.Internal.Data.Stream.IsStream as Stream

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Internal.Data.Stream.IsStream.Transform
-- Copyright : (c) 2017 Composewell Technologies
@ -6,7 +8,7 @@
-- Stability : experimental
-- Portability : GHC
module Streamly.Internal.Data.Stream.IsStream.Transform
module Streamly.Internal.Data.Stream.IsStream.Transform {-# DEPRECATED "Please use \"Streamly.Data.Stream.*\" instead." #-}
(
-- * Piping
-- | Pass through a 'Pipe'.
@ -272,6 +274,7 @@ import Prelude hiding
--
-- $setup
-- >>> :m
-- >>> :set -fno-warn-deprecations
-- >>> import Control.Concurrent (threadDelay)
-- >>> import Data.Function ((&))
-- >>> import Streamly.Prelude ((|$))

View File

@ -1,3 +1,4 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-orphans #-}
@ -10,7 +11,7 @@
-- Portability : GHC
--
--
module Streamly.Internal.Data.Stream.IsStream.Type
module Streamly.Internal.Data.Stream.IsStream.Type {-# DEPRECATED "Please use \"Streamly.Data.Stream.*\" instead." #-}
(
-- * IsStream Type Class
IsStream (..)

View File

@ -79,6 +79,7 @@ import Prelude hiding (map, mapM, repeat, filter)
#include "inline.hs"
-- $setup
-- >>> :set -fno-warn-deprecations
-- >>> import qualified Streamly.Data.Stream as Stream
-- >>> import qualified Streamly.Prelude as IsStream

View File

@ -9,7 +9,8 @@
--
-- To run examples in this module:
--
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import qualified Streamly.Internal.Data.Stream as Stream
-- >>> import qualified Streamly.Data.Fold as Fold
--
module Streamly.Internal.Data.Stream.Zip.Concurrent
(

View File

@ -39,6 +39,7 @@ import Prelude hiding (map, repeat, zipWith, errorWithoutStackTrace)
#include "Instances.hs"
-- $setup
-- >>> :set -fno-warn-deprecations
-- >>> import qualified Streamly.Prelude as Stream
-- >>> import Control.Concurrent (threadDelay)
-- >>> :{

View File

@ -124,7 +124,7 @@ import qualified Streamly.Internal.Data.Unfold as UF (bracket, first)
import qualified Streamly.Internal.Data.Array.Unboxed.Stream as AS
import qualified Streamly.Internal.Data.Fold.Type as FL
(initialize, snoc, Step(..))
import qualified Streamly.Internal.Data.Stream.IsStream as S
import qualified Streamly.Internal.Data.Stream as S
import qualified Streamly.Internal.Network.Socket as ISK
-------------------------------------------------------------------------------
@ -346,7 +346,8 @@ putChunks
-> Stream m (Array Word8)
-> m ()
putChunks addr port xs =
S.drain $ withConnection addr port (\sk -> S.fromEffect $ ISK.putChunks sk xs)
S.fold FL.drain
$ withConnection addr port (\sk -> S.fromEffect $ ISK.putChunks sk xs)
-- | Write a stream of arrays to the supplied IPv4 host address and port
-- number.

View File

@ -30,10 +30,11 @@ where
import Data.Char (isAsciiUpper, isAsciiLower, chr, ord)
import Unicode.Char (DecomposeMode(..))
import Streamly.Internal.Data.Stream.IsStream.Type
(IsStream, fromStreamD, toStreamD)
import Streamly.Internal.Data.Stream (fromStreamD, toStreamD)
import Streamly.Internal.Data.Stream.StreamD (Stream(..), Step (..))
import qualified Streamly.Internal.Data.Stream as Stream (Stream)
import qualified Unicode.Char as Char
-------------------------------------------------------------------------------
@ -313,5 +314,9 @@ normalizeD NFKD = decomposeD True Kompat
normalizeD NFC = partialComposeD . decomposeD False Canonical
normalizeD NFKC = partialComposeD . decomposeD False Kompat
normalize :: (IsStream t, Monad m) => NormalizationMode -> t m Char -> t m Char
normalize ::
Monad m
=> NormalizationMode
-> Stream.Stream m Char
-> Stream.Stream m Char
normalize mode = fromStreamD . normalizeD mode . toStreamD

View File

@ -27,9 +27,12 @@ import Data.Word (Word8)
import Streamly.Data.Array.Unboxed (Array)
import System.IO.Unsafe (unsafePerformIO)
import qualified Streamly.Internal.Data.Array.Unboxed as Array
(fromStreamN, read)
import qualified Streamly.Internal.Data.Stream.IsStream as Stream
import qualified Streamly.Data.Fold as Fold
import qualified Streamly.Data.Stream as Stream
import qualified Streamly.Internal.Data.Array.Unboxed as Array
( fromStreamN
, read
)
import qualified Streamly.Internal.Unicode.Stream as Unicode
--------------------------------------------------------------------------------
@ -65,4 +68,4 @@ pack s =
unpack :: Utf8 -> String
unpack u =
unsafePerformIO
$ Stream.toList $ Unicode.decodeUtf8' $ Array.read $ toArray u
$ Stream.fold Fold.toList $ Unicode.decodeUtf8' $ Array.read $ toArray u

View File

@ -1,3 +1,4 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
{-# OPTIONS_GHC -Wno-orphans #-}
#include "inline.hs"
@ -317,7 +318,7 @@
-- documentation for illustration. The actual implementation may differ for
-- performance reasons.
module Streamly.Prelude
module Streamly.Prelude {-# DEPRECATED "Please use \"Streamly.Data.Stream\", \"Streamly.Data.Stream.Concurrent\", & \"Streamly.Data.Stream.Time\" instead." #-}
(
-- * Construction
-- | Functions ending in the general shape @b -> t m a@.
@ -945,6 +946,7 @@ import Prelude
import Streamly.Internal.Data.Stream.IsStream
-- $setup
-- >>> :set -fno-warn-deprecations
-- >>> import qualified Streamly.Data.Fold as Fold
-- >>> import qualified Streamly.Prelude as Stream

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Test.Data.Array
-- Copyright : (c) 2019 Composewell Technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
module Main (main) where
import Data.Word (Word8)

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Test.Data.SmallArray
-- Copyright : (c) 2020 Composewell technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Test.FileSystem.Event.Common
-- Copyright : (c) 2020 Composewell Technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Test.Network.Socket
-- Copyright : (c) 2020 Composewell technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Test.Network.Socket
-- Copyright : (c) 2020 Composewell technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Test.Prelude
-- Copyright : (c) 2020 Composewell Technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Test.Prelude.Ahead
-- Copyright : (c) 2020 Composewell Technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Test.Prelude.Async
-- Copyright : (c) 2020 Composewell Technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Test.Prelude.Concurrent
-- Copyright : (c) 2020 Composewell Technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Test.Prelude.Fold
-- Copyright : (c) 2020 Composewell Technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Test.Prelude.Parallel
-- Copyright : (c) 2020 Composewell Technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Test.Prelude.MaxRate
-- Copyright : (c) 2018 Composewell Technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Test.Prelude.Serial
-- Copyright : (c) 2020 Composewell Technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
module Main (main) where
import Data.List (elem, intersect, nub, sort)

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Test.Prelude.WAsync
-- Copyright : (c) 2020 Composewell Technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Test.Prelude.WSerial
-- Copyright : (c) 2020 Composewell Technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Test.Prelude.ZipAsync
-- Copyright : (c) 2020 Composewell Technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Test.Prelude.ZipSerial
-- Copyright : (c) 2020 Composewell Technologies

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
module Streamly.Test.Unicode.Stream (main) where
import Data.Char (ord, chr)

View File

@ -1,3 +1,5 @@
{-# OPTIONS_GHC -Wno-deprecations #-}
-- |
-- Module : Streamly.Test.Prelude.Common
-- Copyright : (c) 2020 Composewell Technologies