Replace Data.Strict with Data.*.Strict

"Streamly.Internal.Data.Strict" is replaced by:
Streamly.Internal.Data.Tuple.Strict
Streamly.Internal.Data.Maybe.Strict
Streamly.Internal.Data.Either.Strict

This commit also has some formatting changes to imports.
This commit is contained in:
adithyaov 2020-08-05 23:06:45 +05:30 committed by Harendra Kumar
parent ecef82f2aa
commit ead1601148
20 changed files with 188 additions and 158 deletions

View File

@ -47,7 +47,7 @@ import Foreign.Storable (Storable)
import Streamly.Internal.Data.Stream.StreamD.Type (Step(..))
import qualified Streamly.Internal.Data.Stream.StreamD.Type as D
import qualified Streamly.Internal.Data.Strict as Strict
import qualified Streamly.Internal.Data.Tuple.Strict as Strict
import qualified Streamly.Internal.Memory.Array as A
import qualified Streamly.Internal.Memory.Array.Types as AT

View File

@ -9,7 +9,7 @@ import Control.Monad.IO.Class (MonadIO(..))
import Data.Primitive.Types (Prim(..), sizeOf)
import Streamly.Internal.Data.Fold.Types (Fold(..))
import Streamly.Internal.Data.SVar (adaptState)
import Streamly.Internal.Data.Strict (Tuple'(..), Tuple3'(..))
import Streamly.Internal.Data.Tuple.Strict (Tuple'(..), Tuple3'(..))
import qualified Streamly.Internal.Data.Stream.StreamD.Type as D

View File

@ -13,7 +13,8 @@ import Data.Primitive.Types (Prim(..), sizeOf)
import Data.Semigroup (Semigroup(..))
#endif
import Data.Word (Word8)
import Streamly.Internal.Data.Strict (Tuple3'(..), Maybe'(..))
import Streamly.Internal.Data.Tuple.Strict (Tuple3'(..))
import Streamly.Internal.Data.Maybe.Strict (Maybe'(..))
import Streamly.Internal.Data.Fold.Types (Fold(..))
import Streamly.Internal.Data.SVar (adaptState)
import System.IO.Unsafe (unsafePerformIO)

View File

@ -29,7 +29,8 @@ import Control.Monad.IO.Class (MonadIO)
import Data.Bits ((.|.), unsafeShiftL)
import Data.Word (Word8, Word16, Word32, Word64)
import Streamly.Internal.Data.Parser (Parser)
import Streamly.Internal.Data.Strict (Maybe'(..), Tuple' (..))
import Streamly.Internal.Data.Maybe.Strict (Maybe'(..))
import Streamly.Internal.Data.Tuple.Strict (Tuple' (..))
import qualified Streamly.Internal.Memory.Array as A
import qualified Streamly.Internal.Data.Parser as PR

View File

@ -0,0 +1,26 @@
-- |
-- Module : Streamly.Internal.Data.Either.Strict
-- Copyright : (c) 2019 Composewell Technologies
-- (c) 2013 Gabriel Gonzalez
-- License : BSD3
-- Maintainer : streamly@composewell.com
-- Stability : experimental
-- Portability : GHC
--
-- | Strict data types to be used as accumulator for strict left folds and
-- scans. For more comprehensive strict data types see
-- https://hackage.haskell.org/package/strict-base-types . The names have been
-- suffixed by a prime so that programmers can easily distinguish the strict
-- versions from the lazy ones.
--
-- One major advantage of strict data structures as accumulators in folds and
-- scans is that it helps the compiler optimize the code much better by
-- unboxing. In a big tight loop the difference could be huge.
--
module Streamly.Internal.Data.Either.Strict
( Either' (..)
)
where
-- | A strict 'Either'
data Either' a b = Left' !a | Right' !b deriving Show

View File

@ -211,24 +211,24 @@ import Data.Map.Strict (Map)
#if __GLASGOW_HASKELL__ < 804
import Data.Semigroup (Semigroup((<>)))
#endif
import Streamly.Internal.Data.Pipe.Types (Pipe (..), PipeState(..))
import Streamly.Internal.Data.Tuple.Strict (Tuple'(..), Tuple3'(..))
import Streamly.Internal.Data.Either.Strict (Either'(..))
import Streamly.Internal.Data.Maybe.Strict (Maybe'(..), toMaybe)
import Prelude
hiding (filter, drop, dropWhile, take, takeWhile, zipWith,
foldl, map, mapM_, sequence, all, any, sum, product, elem,
notElem, maximum, minimum, head, last, tail, length, null,
reverse, iterate, init, and, or, lookup, (!!),
scanl, scanl1, replicate, concatMap, mconcat, foldMap, unzip,
span, splitAt, break, mapM)
import qualified Streamly.Internal.Data.Pipe.Types as Pipe
import qualified Data.Map.Strict as Map
import qualified Prelude
import Streamly.Internal.Data.Pipe.Types (Pipe (..), PipeState(..))
import Streamly.Internal.Data.Fold.Types
import Streamly.Internal.Data.Strict
import Prelude hiding
( filter, drop, dropWhile, take, takeWhile, zipWith
, foldl, map, mapM_, sequence, all, any, sum, product, elem
, notElem, maximum, minimum, head, last, tail, length, null
, reverse, iterate, init, and, or, lookup, (!!)
, scanl, scanl1, replicate, concatMap, mconcat, foldMap, unzip
, span, splitAt, break, mapM)
import Streamly.Internal.Data.SVar
import qualified Streamly.Internal.Data.Pipe.Types as Pipe
import Streamly.Internal.Data.Fold.Types
------------------------------------------------------------------------------
-- Smart constructors

View File

@ -152,7 +152,8 @@ import Data.Maybe (isJust, fromJust)
#if __GLASGOW_HASKELL__ < 808
import Data.Semigroup (Semigroup(..))
#endif
import Streamly.Internal.Data.Strict (Tuple'(..), Tuple3'(..), Either'(..))
import Streamly.Internal.Data.Tuple.Strict (Tuple'(..), Tuple3'(..))
import Streamly.Internal.Data.Either.Strict (Either'(..))
import Streamly.Internal.Data.SVar (MonadAsync)
------------------------------------------------------------------------------

View File

@ -0,0 +1,33 @@
-- |
-- Module : Streamly.Internal.Data.Maybe.Strict
-- Copyright : (c) 2019 Composewell Technologies
-- (c) 2013 Gabriel Gonzalez
-- License : BSD3
-- Maintainer : streamly@composewell.com
-- Stability : experimental
-- Portability : GHC
--
-- | Strict data types to be used as accumulator for strict left folds and
-- scans. For more comprehensive strict data types see
-- https://hackage.haskell.org/package/strict-base-types . The names have been
-- suffixed by a prime so that programmers can easily distinguish the strict
-- versions from the lazy ones.
--
-- One major advantage of strict data structures as accumulators in folds and
-- scans is that it helps the compiler optimize the code much better by
-- unboxing. In a big tight loop the difference could be huge.
--
module Streamly.Internal.Data.Maybe.Strict
( Maybe' (..)
, toMaybe
)
where
-- | A strict 'Maybe'
data Maybe' a = Just' !a | Nothing' deriving Show
-- | Convert strict Maybe' to lazy Maybe
{-# INLINABLE toMaybe #-}
toMaybe :: Maybe' a -> Maybe a
toMaybe Nothing' = Nothing
toMaybe (Just' a) = Just a

View File

@ -160,13 +160,13 @@ where
import Control.Exception (assert)
import Control.Monad.Catch (MonadCatch, MonadThrow(..))
import Prelude
hiding (any, all, take, takeWhile, sequence, concatMap, maybe, either)
import Streamly.Internal.Data.Fold.Types (Fold(..))
import Streamly.Internal.Data.Tuple.Strict (Tuple'(..))
import Prelude hiding
(any, all, take, takeWhile, sequence, concatMap, maybe, either)
import Streamly.Internal.Data.Parser.ParserD.Tee
import Streamly.Internal.Data.Parser.ParserD.Types
import Streamly.Internal.Data.Strict
-------------------------------------------------------------------------------
-- Upgrade folds to parses

View File

@ -133,11 +133,11 @@ import Control.Applicative (Alternative(..))
import Control.Exception (assert, Exception(..))
import Control.Monad (MonadPlus(..))
import Control.Monad.Catch (MonadCatch, try, throwM, MonadThrow)
import Prelude hiding (concatMap)
import Fusion.Plugin.Types (Fuse(..))
import Streamly.Internal.Data.Fold (Fold(..), toList)
import Streamly.Internal.Data.Strict (Tuple3'(..))
import Streamly.Internal.Data.Tuple.Strict (Tuple3'(..))
import Prelude hiding (concatMap)
-- | The return type of a 'Parser' step.
--

View File

@ -26,7 +26,7 @@ import Data.Maybe (isJust)
import Data.Semigroup (Semigroup(..))
#endif
import Prelude hiding (zipWith, map, id, unzip, null)
import Streamly.Internal.Data.Strict (Tuple'(..), Tuple3'(..))
import Streamly.Internal.Data.Tuple.Strict (Tuple'(..), Tuple3'(..))
import qualified Prelude

View File

@ -48,7 +48,6 @@ import Control.DeepSeq (NFData1(..))
#endif
import Control.Monad.Base (MonadBase(..), liftBaseDefault)
import Control.Monad.Catch (MonadThrow, throwM)
-- import Control.Monad.Error.Class (MonadError(..))
import Control.Monad.IO.Class (MonadIO(..))
import Control.Monad.Reader.Class (MonadReader(..))
import Control.Monad.State.Class (MonadState(..))
@ -61,18 +60,20 @@ import Data.Semigroup (Endo(..))
import Data.Semigroup (Semigroup(..))
#endif
import GHC.Exts (IsList(..), IsString(..))
import Text.Read (Lexeme(Ident), lexP, parens, prec, readPrec, readListPrec,
readListPrecDefault)
import Prelude hiding (map, mapM, errorWithoutStackTrace)
import Text.Read
( Lexeme(Ident), lexP, parens, prec, readPrec, readListPrec
, readListPrecDefault)
import Streamly.Internal.BaseCompat ((#.), errorWithoutStackTrace)
import Streamly.Internal.Data.Stream.StreamK (IsStream(..), adapt, Stream, mkStream,
foldStream)
import Streamly.Internal.Data.Strict (Maybe'(..), toMaybe)
import Streamly.Internal.Data.Stream.StreamK
(IsStream(..), adapt, Stream, mkStream, foldStream)
import Streamly.Internal.Data.Maybe.Strict (Maybe'(..), toMaybe)
import qualified Streamly.Internal.Data.Stream.Prelude as P
import qualified Streamly.Internal.Data.Stream.StreamK as K
import qualified Streamly.Internal.Data.Stream.StreamD as D
import Prelude hiding (map, mapM, errorWithoutStackTrace)
#include "Instances.hs"
#include "inline.hs"

View File

@ -322,24 +322,11 @@ import Foreign.Ptr (Ptr)
import Foreign.Storable (Storable(..))
import GHC.Types (SPEC(..))
import System.Mem (performMajorGC)
import Prelude
hiding (map, mapM, mapM_, repeat, foldr, last, take, filter,
takeWhile, drop, dropWhile, all, any, maximum, minimum, elem,
notElem, null, head, tail, zipWith, lookup, foldr1, sequence,
(!!), scanl, scanl1, concatMap, replicate, enumFromTo, concat,
reverse, iterate, splitAt)
import qualified Control.Monad.Catch as MC
import qualified Control.Monad.Trans.Reader as Reader
import qualified Control.Monad.Trans.State.Strict as State
import qualified Prelude
import Fusion.Plugin.Types (Fuse(..))
import Streamly.Internal.Mutable.Prim.Var
(Prim, Var, readVar, newVar, modifyVar')
import Streamly.Internal.Data.Time.Units
(TimeUnit64, toRelTime64, diffAbsTime64, RelTime64)
import Streamly.Internal.Data.Atomics (atomicModifyIORefCAS_)
import Streamly.Internal.Memory.Array.Types (Array(..))
import Streamly.Internal.Data.Fold.Types (Fold(..))
@ -349,10 +336,7 @@ import Streamly.Internal.Data.Time.Clock (Clock(Monotonic), getTime)
import Streamly.Internal.Data.Time.Units
(MicroSecond64(..), fromAbsTime, toAbsTime, AbsTime)
import Streamly.Internal.Data.Unfold.Types (Unfold(..))
import Streamly.Internal.Data.Strict (Tuple3'(..))
import Streamly.Internal.Data.Stream.StreamD.Type
import Streamly.Internal.Data.SVar
import Streamly.Internal.Data.Tuple.Strict (Tuple3'(..))
import Streamly.Internal.Data.Stream.SVar (fromConsumer, pushToFold)
import qualified Streamly.Internal.Data.Pipe.Types as Pipe
@ -363,6 +347,19 @@ import qualified Streamly.Memory.Ring as RB
import qualified Streamly.Internal.Data.Stream.StreamK as K
import qualified Streamly.Internal.Data.Parser as PR
import qualified Streamly.Internal.Data.Parser.ParserD as PRD
import qualified Control.Monad.Catch as MC
import qualified Control.Monad.Trans.Reader as Reader
import qualified Control.Monad.Trans.State.Strict as State
import qualified Prelude
import Prelude hiding
( map, mapM, mapM_, repeat, foldr, last, take, filter
, takeWhile, drop, dropWhile, all, any, maximum, minimum, elem
, notElem, null, head, tail, zipWith, lookup, foldr1, sequence
, (!!), scanl, scanl1, concatMap, replicate, enumFromTo, concat
, reverse, iterate, splitAt)
import Streamly.Internal.Data.Stream.StreamD.Type
import Streamly.Internal.Data.SVar
------------------------------------------------------------------------------
-- Construction

View File

@ -45,25 +45,25 @@ import Data.Semigroup (Endo(..))
import Data.Semigroup (Semigroup(..))
#endif
import GHC.Exts (IsList(..), IsString(..))
import Text.Read (Lexeme(Ident), lexP, parens, prec, readPrec, readListPrec,
readListPrecDefault)
import Prelude hiding (map, repeat, zipWith, errorWithoutStackTrace)
import Text.Read
( Lexeme(Ident), lexP, parens, prec, readPrec, readListPrec
, readListPrecDefault)
import Streamly.Internal.BaseCompat ((#.), errorWithoutStackTrace)
import Streamly.Internal.Data.Stream.StreamK (IsStream(..), Stream)
import Streamly.Internal.Data.Strict (Maybe'(..), toMaybe)
import Streamly.Internal.Data.Maybe.Strict (Maybe'(..), toMaybe)
import Streamly.Internal.Data.SVar (MonadAsync)
import qualified Streamly.Internal.Data.Stream.Prelude as P
import qualified Streamly.Internal.Data.Stream.StreamK as K
import qualified Streamly.Internal.Data.Stream.StreamD as D
#ifdef USE_STREAMK_ONLY
import qualified Streamly.Internal.Data.Stream.StreamK as S
#else
import qualified Streamly.Internal.Data.Stream.StreamD as S
#endif
import Prelude hiding (map, repeat, zipWith, errorWithoutStackTrace)
#include "Instances.hs"
-- | Like 'zipWith' but using a monadic zipping function.

View File

@ -1,59 +0,0 @@
-- |
-- Module : Streamly.Internal.Data.Strict
-- Copyright : (c) 2019 Composewell Technologies
-- (c) 2013 Gabriel Gonzalez
-- License : BSD3
-- Maintainer : streamly@composewell.com
-- Stability : experimental
-- Portability : GHC
--
-- | Strict data types to be used as accumulator for strict left folds and
-- scans. For more comprehensive strict data types see
-- https://hackage.haskell.org/package/strict-base-types . The names have been
-- suffixed by a prime so that programmers can easily distinguish the strict
-- versions from the lazy ones.
--
-- One major advantage of strict data structures as accumulators in folds and
-- scans is that it helps the compiler optimize the code much better by
-- unboxing. In a big tight loop the difference could be huge.
--
module Streamly.Internal.Data.Strict
(
Tuple' (..)
, Tuple3' (..)
, Tuple4' (..)
, Maybe' (..)
, toMaybe
, Either' (..)
)
where
-------------------------------------------------------------------------------
-- Tuples
-------------------------------------------------------------------------------
--
data Tuple' a b = Tuple' !a !b deriving Show
data Tuple3' a b c = Tuple3' !a !b !c deriving Show
data Tuple4' a b c d = Tuple4' !a !b !c !d deriving Show
-------------------------------------------------------------------------------
-- Maybe
-------------------------------------------------------------------------------
--
-- | A strict 'Maybe'
data Maybe' a = Just' !a | Nothing' deriving Show
-- XXX perhaps we can use a type class having fromStrict/toStrict operations.
--
-- | Convert strict Maybe' to lazy Maybe
{-# INLINABLE toMaybe #-}
toMaybe :: Maybe' a -> Maybe a
toMaybe Nothing' = Nothing
toMaybe (Just' a) = Just a
-------------------------------------------------------------------------------
-- Either
-------------------------------------------------------------------------------
--
-- | A strict 'Either'
data Either' a b = Left' !a | Right' !b deriving Show

View File

@ -0,0 +1,35 @@
-- |
-- Module : Streamly.Internal.Data.Tuple.Strict
-- Copyright : (c) 2019 Composewell Technologies
-- (c) 2013 Gabriel Gonzalez
-- License : BSD3
-- Maintainer : streamly@composewell.com
-- Stability : experimental
-- Portability : GHC
--
-- | Strict data types to be used as accumulator for strict left folds and
-- scans. For more comprehensive strict data types see
-- https://hackage.haskell.org/package/strict-base-types . The names have been
-- suffixed by a prime so that programmers can easily distinguish the strict
-- versions from the lazy ones.
--
-- One major advantage of strict data structures as accumulators in folds and
-- scans is that it helps the compiler optimize the code much better by
-- unboxing. In a big tight loop the difference could be huge.
--
module Streamly.Internal.Data.Tuple.Strict
(
Tuple' (..)
, Tuple3' (..)
, Tuple4' (..)
)
where
-- | A strict '(,)'
data Tuple' a b = Tuple' !a !b deriving Show
-- | A strict '(,,)'
data Tuple3' a b c = Tuple3' !a !b !c deriving Show
-- | A strict '(,,,)'
data Tuple4' a b c d = Tuple4' !a !b !c !d deriving Show

View File

@ -64,21 +64,21 @@ import GHC.Base (assert, unsafeChr)
import GHC.ForeignPtr (ForeignPtr (..))
import GHC.IO.Encoding.Failure (isSurrogate)
import GHC.Ptr (Ptr (..), plusPtr)
import Prelude hiding (String, lines, words, unlines, unwords)
import System.IO.Unsafe (unsafePerformIO)
import Streamly (IsStream)
import Streamly.Data.Fold (Fold)
import Streamly.Memory.Array (Array)
import Streamly.Internal.Data.Unfold (Unfold)
import Streamly.Internal.Data.SVar (adaptState)
import Streamly.Internal.Data.Stream.StreamD (Stream(..), Step (..))
import Streamly.Internal.Data.Strict (Tuple'(..))
import Streamly.Internal.Data.Tuple.Strict (Tuple'(..))
import qualified Streamly.Internal.Memory.Array.Types as A
import qualified Streamly.Internal.Prelude as S
import qualified Streamly.Internal.Data.Stream.StreamD as D
import Prelude hiding (String, lines, words, unlines, unwords)
-------------------------------------------------------------------------------
-- Encoding/Decoding Unicode (UTF-8) Characters
-------------------------------------------------------------------------------

View File

@ -94,6 +94,9 @@ import Control.DeepSeq (NFData(..))
import Control.Monad (when, void)
import Control.Monad.IO.Class (MonadIO(..))
import Data.Functor.Identity (runIdentity)
#if __GLASGOW_HASKELL__ < 808
import Data.Semigroup (Semigroup(..))
#endif
import Data.Word (Word8)
import Foreign.C.Types (CSize(..), CInt(..))
import Foreign.ForeignPtr (withForeignPtr, touchForeignPtr)
@ -105,11 +108,17 @@ import GHC.Exts (IsList, IsString(..))
import GHC.ForeignPtr (ForeignPtr(..))
import GHC.IO (IO(IO), unsafePerformIO)
import GHC.Ptr (Ptr(..))
#if !defined(mingw32_HOST_OS)
import Streamly.FileSystem.FDIO (IOVec(..))
#endif
import Streamly.Internal.Data.Fold.Types (Fold(..))
import Streamly.Internal.Data.Strict (Tuple'(..))
import Streamly.Internal.Data.Tuple.Strict (Tuple'(..))
import Streamly.Internal.Data.SVar (adaptState)
import Text.Read (readPrec, readListPrec, readListPrecDefault)
#ifdef DEVBUILD
import qualified Data.Foldable as F
#endif
import qualified Streamly.Memory.Malloc as Malloc
import qualified Streamly.Internal.Data.Stream.StreamD.Type as D
import qualified Streamly.Internal.Data.Stream.StreamK as K
@ -117,18 +126,6 @@ import qualified GHC.Exts as Exts
import Prelude hiding (length, foldr, read, unlines, splitAt)
#if __GLASGOW_HASKELL__ < 808
import Data.Semigroup (Semigroup(..))
#endif
#if !defined(mingw32_HOST_OS)
import Streamly.FileSystem.FDIO (IOVec(..))
#endif
#ifdef DEVBUILD
import qualified Data.Foldable as F
#endif
#if MIN_VERSION_base(4,10,0)
import Foreign.ForeignPtr (plusForeignPtr)
#else

View File

@ -535,25 +535,12 @@ import Data.Heap (Entry(..))
import Data.Maybe (isJust, fromJust, isNothing)
import Data.Void (Void)
import Foreign.Storable (Storable)
import Prelude
hiding (filter, drop, dropWhile, take, takeWhile, zipWith, foldr,
foldl, map, mapM, mapM_, sequence, all, any, sum, product, elem,
notElem, maximum, minimum, head, last, tail, length, null,
reverse, iterate, init, and, or, lookup, foldr1, (!!),
scanl, scanl1, replicate, concatMap, span, splitAt, break,
repeat, concat, mconcat)
import qualified Data.Heap as H
import qualified Data.Map.Strict as Map
import qualified Prelude
import qualified System.IO as IO
import Streamly.Internal.Data.Stream.Enumeration (Enumerable(..), enumerate, enumerateTo)
import Streamly.Internal.Data.Stream.Enumeration
(Enumerable(..), enumerate, enumerateTo)
import Streamly.Internal.Data.Fold.Types (Fold (..), Fold2 (..))
import Streamly.Internal.Data.Parser (Parser (..))
import Streamly.Internal.Data.Unfold.Types (Unfold)
import Streamly.Internal.Memory.Array.Types (Array, writeNUnsafe)
-- import Streamly.Memory.Ring (Ring)
import Streamly.Internal.Data.SVar (MonadAsync, defState, Rate)
import Streamly.Internal.Data.Stream.Combinators (inspectMode, maxYields)
import Streamly.Internal.Data.Stream.Prelude
@ -564,11 +551,10 @@ import Streamly.Internal.Data.Stream.Serial (SerialT, WSerialT)
import Streamly.Internal.Data.Stream.Zip (ZipSerialM)
import Streamly.Internal.Data.Pipe.Types (Pipe (..))
import Streamly.Internal.Data.Time.Units
(AbsTime, MilliSecond64(..), addToAbsTime, toRelTime,
toAbsTime, TimeUnit64, RelTime64, addToAbsTime64)
( AbsTime, MilliSecond64(..), addToAbsTime, toRelTime
, toAbsTime, TimeUnit64, RelTime64, addToAbsTime64)
import Streamly.Internal.Mutable.Prim.Var (Prim, Var)
import Streamly.Internal.Data.Strict
import Streamly.Internal.Data.Tuple.Strict (Tuple'(..))
import qualified Streamly.Internal.Memory.Array as A
import qualified Streamly.Data.Fold as FL
@ -576,19 +562,28 @@ import qualified Streamly.Internal.Data.Fold.Types as FL
import qualified Streamly.Internal.Data.Stream.Prelude as P
import qualified Streamly.Internal.Data.Stream.StreamK as K
import qualified Streamly.Internal.Data.Stream.StreamD as D
import qualified Streamly.Internal.Data.Stream.Serial as Serial
import qualified Streamly.Internal.Data.Stream.Parallel as Par
import qualified Streamly.Internal.Data.Stream.Zip as Z
import qualified Streamly.Internal.Data.Parser.ParserK.Types as PRK
import qualified Streamly.Internal.Data.Parser.ParserD as PRD
import qualified Data.Heap as H
import qualified Data.Map.Strict as Map
import qualified Prelude
import qualified System.IO as IO
#ifdef USE_STREAMK_ONLY
import qualified Streamly.Internal.Data.Stream.StreamK as S
#else
import qualified Streamly.Internal.Data.Stream.StreamD as S
#endif
-- import qualified Streamly.Internal.Data.Stream.Async as Async
import qualified Streamly.Internal.Data.Stream.Serial as Serial
import qualified Streamly.Internal.Data.Stream.Parallel as Par
import qualified Streamly.Internal.Data.Stream.Zip as Z
import qualified Streamly.Internal.Data.Parser.ParserK.Types as PRK
import qualified Streamly.Internal.Data.Parser.ParserD as PRD
import Prelude hiding
( filter, drop, dropWhile, take, takeWhile, zipWith, foldr
, foldl, map, mapM, mapM_, sequence, all, any, sum, product, elem
, notElem, maximum, minimum, head, last, tail, length, null
, reverse, iterate, init, and, or, lookup, foldr1, (!!)
, scanl, scanl1, replicate, concatMap, span, splitAt, break
, repeat, concat, mconcat)
------------------------------------------------------------------------------
-- Deconstruction

View File

@ -375,7 +375,9 @@ library
-- Internal modules
, Streamly.Internal.BaseCompat
, Streamly.Internal.Control.Monad
, Streamly.Internal.Data.Strict
, Streamly.Internal.Data.Tuple.Strict
, Streamly.Internal.Data.Maybe.Strict
, Streamly.Internal.Data.Either.Strict
, Streamly.Internal.Data.Atomics
, Streamly.Internal.Data.Time
, Streamly.Internal.Data.Time.TimeSpec