diff --git a/benchmark/Streamly/Benchmark/Data/Array.hs b/benchmark/Streamly/Benchmark/Data/Array.hs index 5a74c94a60..4a3c875af6 100644 --- a/benchmark/Streamly/Benchmark/Data/Array.hs +++ b/benchmark/Streamly/Benchmark/Data/Array.hs @@ -5,6 +5,9 @@ #include "Streamly/Benchmark/Data/Array/CommonImports.hs" import Control.DeepSeq (deepseq) +#if __GLASGOW_HASKELL__ >= 810 +import Data.Kind (Type) +#endif import qualified Streamly.Internal.Data.Array as IA import qualified GHC.Exts as GHC @@ -12,6 +15,9 @@ import qualified GHC.Exts as GHC -- import qualified Streamly.Data.Array as A import qualified Streamly.Internal.Data.Array as A +#if __GLASGOW_HASKELL__ >= 810 +type Stream :: Type -> Type +#endif type Stream = A.Array #include "Streamly/Benchmark/Data/Array/Common.hs" diff --git a/benchmark/Streamly/Benchmark/Data/MutArray.hs b/benchmark/Streamly/Benchmark/Data/MutArray.hs index 4faa9bc9f3..fa1aef1e5f 100644 --- a/benchmark/Streamly/Benchmark/Data/MutArray.hs +++ b/benchmark/Streamly/Benchmark/Data/MutArray.hs @@ -22,6 +22,9 @@ import Control.DeepSeq (NFData(..)) import Control.Monad.IO.Class (MonadIO) import Data.Functor ((<&>)) +#if __GLASGOW_HASKELL__ >= 810 +import Data.Kind (Type) +#endif import System.Random (randomRIO) import Prelude ( IO @@ -52,6 +55,9 @@ import qualified Streamly.Internal.Data.Stream as Stream import Test.Tasty.Bench import Streamly.Benchmark.Common hiding (benchPureSrc) +#if __GLASGOW_HASKELL__ >= 810 +type Stream :: Type -> Type +#endif type Stream = MutArray instance NFData (MutArray a) where diff --git a/benchmark/streamly-benchmarks.cabal b/benchmark/streamly-benchmarks.cabal index 6a2b129366..c2e962e9c2 100644 --- a/benchmark/streamly-benchmarks.cabal +++ b/benchmark/streamly-benchmarks.cabal @@ -69,10 +69,23 @@ flag use-prelude ------------------------------------------------------------------------------- common default-extensions + default-language: Haskell2010 + + -- GHC2024 may include more extensions than we are actually using, see the + -- full list below. We enable this to ensure that we are able to compile + -- with this i.e. there is no interference by other extensions. + if impl(ghc >= 9.10) + default-language: GHC2024 + + if impl(ghc >= 9.2) && impl(ghc < 9.10) + default-language: GHC2021 + + if impl(ghc >= 8.10) + default-extensions: StandaloneKindSignatures + + -- In GHC 2024 default-extensions: BangPatterns - CApiFFI - CPP ConstraintKinds DeriveDataTypeable DeriveGeneric @@ -84,29 +97,20 @@ common default-extensions InstanceSigs KindSignatures LambdaCase - MagicHash MultiParamTypeClasses - PatternSynonyms RankNTypes - RecordWildCards ScopedTypeVariables TupleSections TypeApplications - TypeFamilies TypeOperators - ViewPatterns - -- MonoLocalBinds, enabled by TypeFamilies, causes performance - -- regressions. Disable it. This must come after TypeFamilies, - -- otherwise TypeFamilies will enable it again. - NoMonoLocalBinds - - -- UndecidableInstances -- Does not show any perf impact - -- UnboxedTuples -- interferes with (#.) + -- Not in GHC2024 + CPP + MagicHash + RecordWildCards common compile-options import: default-extensions - default-language: Haskell2010 if flag(use-streamly-core) cpp-options: -DUSE_STREAMLY_CORE @@ -229,7 +233,7 @@ library common bench-options import: compile-options, optimization-options, bench-depends include-dirs: . - ghc-options: -rtsopts + ghc-options: -rtsopts -with-rtsopts "-t" if flag(limit-build-mem) ghc-options: +RTS -M512M -RTS build-depends: streamly-benchmarks == 0.0.0 @@ -239,7 +243,7 @@ common bench-options-threaded import: compile-options, optimization-options, bench-depends -- -threaded and -N2 is important because some GC and space leak issues -- trigger only with these options. - ghc-options: -threaded -rtsopts -with-rtsopts "-N2" + ghc-options: -threaded -rtsopts -with-rtsopts "-t -N2" if flag(limit-build-mem) ghc-options: +RTS -M512M -RTS build-depends: streamly-benchmarks == 0.0.0 @@ -313,6 +317,10 @@ benchmark Data.Fold.Window type: exitcode-stdio-1.0 hs-source-dirs: Streamly/Benchmark/Data/Fold main-is: Window.hs + -- MonoLocalBinds increases the memory requirement from 400MB to 1000MB, + -- observed on macOS. + if flag(limit-build-mem) + ghc-options: +RTS -M1000M -RTS benchmark Data.MutArray import: bench-options diff --git a/core/src/Streamly/Internal/Data/IORef.hs b/core/src/Streamly/Internal/Data/IORef.hs index da0d2b40c2..7105a49fc8 100644 --- a/core/src/Streamly/Internal/Data/IORef.hs +++ b/core/src/Streamly/Internal/Data/IORef.hs @@ -39,6 +39,9 @@ where #include "inline.hs" import Control.Monad.IO.Class (MonadIO(..)) +#if __GLASGOW_HASKELL__ >= 810 +import Data.Kind (Type) +#endif import Data.Proxy (Proxy(..)) import Streamly.Internal.Data.MutByteArray.Type (MutByteArray) import Streamly.Internal.Data.Unbox (Unbox(..), sizeOf) @@ -47,6 +50,9 @@ import qualified Streamly.Internal.Data.MutByteArray.Type as MBA import qualified Streamly.Internal.Data.Stream.Type as D -- | An 'IORef' holds a single 'Unbox'-able value. +#if __GLASGOW_HASKELL__ >= 810 +type IORef :: Type -> Type +#endif newtype IORef a = IORef MutByteArray -- | Create a new 'IORef'. diff --git a/core/src/Streamly/Internal/Data/Parser.hs b/core/src/Streamly/Internal/Data/Parser.hs index 94e1ac5038..c986e8846c 100644 --- a/core/src/Streamly/Internal/Data/Parser.hs +++ b/core/src/Streamly/Internal/Data/Parser.hs @@ -1,4 +1,5 @@ {-# LANGUAGE CPP #-} +{-# LANGUAGE NoMonoLocalBinds #-} -- | -- Module : Streamly.Internal.Data.Parser -- Copyright : (c) 2020 Composewell Technologies diff --git a/core/src/Streamly/Internal/Data/Parser/Type.hs b/core/src/Streamly/Internal/Data/Parser/Type.hs index 6b9defe3af..e0ac6bb2a6 100644 --- a/core/src/Streamly/Internal/Data/Parser/Type.hs +++ b/core/src/Streamly/Internal/Data/Parser/Type.hs @@ -1,4 +1,5 @@ {-# LANGUAGE CPP #-} +{-# LANGUAGE NoMonoLocalBinds #-} -- | -- Module : Streamly.Internal.Data.Parser.ParserD.Type -- Copyright : (c) 2020 Composewell Technologies diff --git a/core/src/Streamly/Internal/Data/Pipe/Type.hs b/core/src/Streamly/Internal/Data/Pipe/Type.hs index 33fa6b859f..1624168279 100644 --- a/core/src/Streamly/Internal/Data/Pipe/Type.hs +++ b/core/src/Streamly/Internal/Data/Pipe/Type.hs @@ -36,6 +36,9 @@ where -- import Control.Arrow (Arrow(..)) import Control.Category (Category(..)) import Data.Functor ((<&>)) +#if __GLASGOW_HASKELL__ >= 810 +import Data.Kind (Type) +#endif import Fusion.Plugin.Types (Fuse(..)) import Streamly.Internal.Data.Fold.Type (Fold(..)) import Streamly.Internal.Data.Scanr (Scanr(..)) @@ -146,6 +149,9 @@ instance Functor m => Functor (Pipe m a) where ------------------------------------------------------------------------------- {-# ANN type ComposeConsume Fuse #-} +#if __GLASGOW_HASKELL__ >= 810 +type ComposeConsume :: Type -> Type -> Type -> Type +#endif data ComposeConsume csL psL csR = ComposeConsume csL csR @@ -614,6 +620,9 @@ filter f = filterM (return Prelude.. f) -- that. {-# ANN type FromFoldConsume Fuse #-} +#if __GLASGOW_HASKELL__ >= 810 +type FromFoldConsume :: Type -> Type -> Type +#endif data FromFoldConsume s x = FoldConsumeInit | FoldConsumeGo s {-# ANN type FromFoldProduce Fuse #-} diff --git a/core/src/Streamly/Internal/Data/Stream/Type.hs b/core/src/Streamly/Internal/Data/Stream/Type.hs index db0b971dd9..c0067f07f5 100644 --- a/core/src/Streamly/Internal/Data/Stream/Type.hs +++ b/core/src/Streamly/Internal/Data/Stream/Type.hs @@ -172,6 +172,9 @@ import Control.Monad.IO.Class (MonadIO(..)) import Data.Foldable (Foldable(foldl'), fold, foldr) import Data.Functor (($>)) import Data.Functor.Identity (Identity(..)) +#if __GLASGOW_HASKELL__ >= 810 +import Data.Kind (Type) +#endif import Data.Maybe (fromMaybe) import Data.Semigroup (Endo(..)) import Fusion.Plugin.Types (Fuse(..)) @@ -1837,6 +1840,9 @@ foldIterateBfs = undefined -- s = stream state, fs = fold state {-# ANN type FoldManyPost Fuse #-} +#if __GLASGOW_HASKELL__ >= 810 +type FoldManyPost :: Type -> Type -> Type -> Type -> Type +#endif data FoldManyPost s fs b a = FoldManyPostStart s | FoldManyPostLoop s fs @@ -1918,6 +1924,9 @@ foldManySepBy :: -- Monad m => foldManySepBy _f1 _f2 = undefined {-# ANN type FoldMany Fuse #-} +#if __GLASGOW_HASKELL__ >= 810 +type FoldMany :: Type -> Type -> Type -> Type -> Type +#endif data FoldMany s fs b a = FoldManyStart s | FoldManyFirst fs s diff --git a/core/src/Streamly/Internal/Data/StreamK/Type.hs b/core/src/Streamly/Internal/Data/StreamK/Type.hs index dbeec2944b..5e15d214c7 100644 --- a/core/src/Streamly/Internal/Data/StreamK/Type.hs +++ b/core/src/Streamly/Internal/Data/StreamK/Type.hs @@ -164,6 +164,9 @@ import Control.Monad.IO.Class (MonadIO(..)) import Data.Foldable (Foldable(foldl'), fold, foldr) import Data.Function (fix) import Data.Functor.Identity (Identity(..)) +#if __GLASGOW_HASKELL__ >= 810 +import Data.Kind (Type) +#endif import Data.Maybe (fromMaybe) import Data.Semigroup (Endo(..)) import GHC.Exts (IsList(..), IsString(..), oneShot) @@ -233,12 +236,18 @@ mkStream mkStream = MkStream -- | A terminal function that has no continuation to follow. +#if __GLASGOW_HASKELL__ >= 810 +type StopK :: (Type -> Type) -> Type +#endif type StopK m = forall r. m r -> m r -- | A monadic continuation, it is a function that yields a value of type "a" -- and calls the argument (a -> m r) as a continuation with that value. We can -- also think of it as a callback with a handler (a -> m r). Category -- theorists call it a codensity type, a special type of right kan extension. +#if __GLASGOW_HASKELL__ >= 810 +type YieldK :: (Type -> Type) -> Type -> Type +#endif type YieldK m a = forall r. (a -> m r) -> m r _wrapM :: Monad m => m a -> YieldK m a diff --git a/core/src/Streamly/Internal/FileSystem/File.hs b/core/src/Streamly/Internal/FileSystem/File.hs index 7cb7981b7a..cca3bb11cf 100644 --- a/core/src/Streamly/Internal/FileSystem/File.hs +++ b/core/src/Streamly/Internal/FileSystem/File.hs @@ -95,6 +95,7 @@ where import Control.Monad.Catch (MonadCatch) import Control.Monad.IO.Class (MonadIO(..)) +import Data.Kind (Type) import Data.Word (Word8) import System.IO (Handle, openFile, IOMode(..), hClose) import Prelude hiding (read) @@ -204,7 +205,7 @@ usingFile3 = UF.bracketIO before after -- /Pre-release/ -- {-# INLINABLE putChunk #-} -putChunk :: FilePath -> Array a -> IO () +putChunk :: forall (a :: Type). FilePath -> Array a -> IO () putChunk file arr = SIO.withFile file WriteMode (`FH.putChunk` arr) -- | append an array to a file. @@ -212,7 +213,7 @@ putChunk file arr = SIO.withFile file WriteMode (`FH.putChunk` arr) -- /Pre-release/ -- {-# INLINABLE writeAppendArray #-} -writeAppendArray :: FilePath -> Array a -> IO () +writeAppendArray :: forall (a :: Type). FilePath -> Array a -> IO () writeAppendArray file arr = SIO.withFile file AppendMode (`FH.putChunk` arr) ------------------------------------------------------------------------------- @@ -369,7 +370,7 @@ readShared = undefined ------------------------------------------------------------------------------- {-# INLINE fromChunksMode #-} -fromChunksMode :: (MonadIO m, MonadCatch m) +fromChunksMode :: forall m (a :: Type). (MonadIO m, MonadCatch m) => IOMode -> FilePath -> Stream m (Array a) -> m () fromChunksMode mode file xs = S.fold drain $ withFile file mode (\h -> S.mapM (FH.putChunk h) xs) @@ -379,7 +380,7 @@ fromChunksMode mode file xs = S.fold drain $ -- /Pre-release/ -- {-# INLINE fromChunks #-} -fromChunks :: (MonadIO m, MonadCatch m) +fromChunks :: forall m (a :: Type). (MonadIO m, MonadCatch m) => FilePath -> Stream m (Array a) -> m () fromChunks = fromChunksMode WriteMode @@ -431,7 +432,7 @@ write = toHandleWith A.defaultChunkSize -- -- /Pre-release/ {-# INLINE writeChunks #-} -writeChunks :: (MonadIO m, MonadCatch m) +writeChunks :: forall m (a :: Type). (MonadIO m, MonadCatch m) => FilePath -> Fold m (Array a) () writeChunks path = Fold step initial extract final where @@ -487,7 +488,7 @@ write = writeWith defaultChunkSize -- /Pre-release/ -- {-# INLINE writeAppendChunks #-} -writeAppendChunks :: (MonadIO m, MonadCatch m) +writeAppendChunks :: forall m (a :: Type). (MonadIO m, MonadCatch m) => FilePath -> Stream m (Array a) -> m () writeAppendChunks = fromChunksMode AppendMode diff --git a/core/src/Streamly/Internal/FileSystem/Handle.hs b/core/src/Streamly/Internal/FileSystem/Handle.hs index c88e9ad4b1..2f3fda09fb 100644 --- a/core/src/Streamly/Internal/FileSystem/Handle.hs +++ b/core/src/Streamly/Internal/FileSystem/Handle.hs @@ -121,6 +121,7 @@ where import Control.Exception (assert) import Control.Monad.IO.Class (MonadIO(..)) import Data.Function ((&)) +import Data.Kind (Type) import Data.Maybe (isNothing, fromJust) import Data.Word (Word8) import Streamly.Internal.Data.Unbox (Unbox) @@ -373,7 +374,7 @@ read = A.concat . readChunks -- | Write an 'Array' to a file handle. -- {-# INLINABLE putChunk #-} -putChunk :: MonadIO m => Handle -> Array a -> m () +putChunk :: forall m (a :: Type). MonadIO m => Handle -> Array a -> m () putChunk _ arr | byteLength arr == 0 = return () putChunk h arr = A.unsafePinnedAsPtr arr $ \ptr byteLen -> liftIO $ hPutBuf h ptr byteLen @@ -392,7 +393,8 @@ putChunk h arr = A.unsafePinnedAsPtr arr $ \ptr byteLen -> -- >>> putChunks h = Stream.fold (Fold.drainBy (Handle.putChunk h)) -- {-# INLINE putChunks #-} -putChunks :: MonadIO m => Handle -> Stream m (Array a) -> m () +putChunks :: forall m (a :: Type). MonadIO m => + Handle -> Stream m (Array a) -> m () putChunks h = S.fold (FL.drainMapM (putChunk h)) -- XXX AS.compact can be written idiomatically in terms of foldMany, just like @@ -437,14 +439,14 @@ putBytes = putBytesWith defaultChunkSize -- writeChunks h = Fold.drainBy (Handle.putChunk h) -- {-# INLINE writeChunks #-} -writeChunks :: MonadIO m => Handle -> Fold m (Array a) () +writeChunks :: forall m (a :: Type). MonadIO m => Handle -> Fold m (Array a) () writeChunks h = FL.drainMapM (putChunk h) -- | Like writeChunks but uses the experimental 'Refold' API. -- -- /Internal/ {-# INLINE chunkWriter #-} -chunkWriter :: MonadIO m => Refold m Handle (Array a) () +chunkWriter :: forall m (a :: Type). MonadIO m => Refold m Handle (Array a) () chunkWriter = Refold.drainBy putChunk -- | @writeChunksWith bufsize handle@ writes a stream of arrays diff --git a/core/streamly-core.cabal b/core/streamly-core.cabal index 4dfc9b774d..6ba9e2be0e 100644 --- a/core/streamly-core.cabal +++ b/core/streamly-core.cabal @@ -162,8 +162,6 @@ flag force-lstat-readdir ------------------------------------------------------------------------------- common compile-options - default-language: Haskell2010 - if flag(force-lstat-readdir) cpp-options: -DFORCE_LSTAT_READDIR @@ -200,6 +198,10 @@ common compile-options ghc-options: -Wno-missing-role-annotations + if impl(ghc >= 9.10) + ghc-options: + -Wno-missing-poly-kind-signatures + if flag(has-llvm) ghc-options: -fllvm @@ -214,6 +216,21 @@ common compile-options cpp-options: -DUSE_UNLIFTIO common default-extensions + default-language: Haskell2010 + + -- GHC2024 may include more extensions than we are actually using, see the + -- full list below. We enable this to ensure that we are able to compile + -- with this i.e. there is no interference by other extensions. + if impl(ghc >= 9.10) + default-language: GHC2024 + + if impl(ghc >= 9.2) && impl(ghc < 9.10) + default-language: GHC2021 + + if impl(ghc >= 8.10) + default-extensions: StandaloneKindSignatures + + -- In GHC 2024 default-extensions: BangPatterns ConstraintKinds @@ -226,6 +243,7 @@ common default-extensions GeneralizedNewtypeDeriving InstanceSigs KindSignatures + LambdaCase MultiParamTypeClasses RankNTypes ScopedTypeVariables @@ -234,25 +252,34 @@ common default-extensions TypeApplications TypeOperators - -- Not GHC2021 + -- Not in GHC2024 CApiFFI CPP DefaultSignatures - LambdaCase MagicHash RecordWildCards -- TypeFamilies is required by IsList, IsMap type classes and -- Unbox generic deriving code. -- TypeFamilies - -- MonoLocalBinds, enabled by TypeFamilies, causes performance - -- regressions. Disable it. This must come after TypeFamilies, + + -- MonoLocalBinds, enabled by TypeFamilies and GHC2024, was + -- once found to cause runtime performance regressions which + -- does not seem to be the case anymore, but need more testing + -- to confirm. It is confirmed that it requires more memory + -- for compilation at least in some cases (Data.Fold.Window + -- benchmark on GHC-9.10.1 macOS). It also causes some + -- code to not compile, so has been disabled in specific + -- modules. Disabling this must come after TypeFamilies, -- otherwise TypeFamilies will enable it again. -- NoMonoLocalBinds -- UndecidableInstances -- Does not show any perf impact -- UnboxedTuples -- interferes with (#.) + if impl(ghc >= 8.6) + default-extensions: QuantifiedConstraints + common optimization-options if flag(opt) ghc-options: -O2 @@ -285,9 +312,6 @@ common lib-options library import: lib-options - if impl(ghc >= 8.6) - default-extensions: QuantifiedConstraints - js-sources: jsbits/clock.js include-dirs: diff --git a/src/Streamly/Internal/Data/Stream/Channel/Operations.hs b/src/Streamly/Internal/Data/Stream/Channel/Operations.hs index 38b90db99f..604ff992cf 100644 --- a/src/Streamly/Internal/Data/Stream/Channel/Operations.hs +++ b/src/Streamly/Internal/Data/Stream/Channel/Operations.hs @@ -33,6 +33,9 @@ import Control.Exception (fromException) import Control.Monad (when) import Control.Monad.Catch (throwM, MonadThrow) import Control.Monad.IO.Class (MonadIO(liftIO)) +#if __GLASGOW_HASKELL__ >= 810 +import Data.Kind (Type) +#endif import Data.IORef (newIORef, readIORef, mkWeakIORef, writeIORef) import Data.Maybe (isNothing) import Streamly.Internal.Control.Concurrent @@ -262,6 +265,9 @@ fromChannelK chan = fromChannel :: MonadAsync m => Channel m a -> Stream m a fromChannel = Stream.fromStreamK . fromChannelK +#if __GLASGOW_HASKELL__ >= 810 +type FromSVarState :: Type -> (Type -> Type) -> Type -> Type +#endif data FromSVarState t m a = FromSVarInit | FromSVarRead (Channel m a) diff --git a/src/Streamly/Internal/Data/Stream/IsStream/Reduce.hs b/src/Streamly/Internal/Data/Stream/IsStream/Reduce.hs index d9bf0f818b..6a7e3e5d36 100644 --- a/src/Streamly/Internal/Data/Stream/IsStream/Reduce.hs +++ b/src/Streamly/Internal/Data/Stream/IsStream/Reduce.hs @@ -1604,8 +1604,7 @@ classifySessionsOf = classifySessionsBy 1 False -- -- /Pre-release/ {-# INLINE splitInnerBy #-} -splitInnerBy - :: (IsStream t, Monad m) +splitInnerBy :: forall t m (f :: Type -> Type) a. (IsStream t, Monad m) => (f a -> m (f a, Maybe (f a))) -- splitter -> (f a -> f a -> m (f a)) -- joiner -> t m (f a) @@ -1618,8 +1617,8 @@ splitInnerBy splitter joiner xs = -- -- /Pre-release/ {-# INLINE splitInnerBySuffix #-} -splitInnerBySuffix - :: (IsStream t, Monad m, Eq (f a), Monoid (f a)) +splitInnerBySuffix :: forall t m (f :: Type -> Type) a. + (IsStream t, Monad m, Eq (f a), Monoid (f a)) => (f a -> m (f a, Maybe (f a))) -- splitter -> (f a -> f a -> m (f a)) -- joiner -> t m (f a) diff --git a/src/Streamly/Internal/Data/Stream/Parallel.hs b/src/Streamly/Internal/Data/Stream/Parallel.hs index 8a7d4a905d..afc6fa655f 100644 --- a/src/Streamly/Internal/Data/Stream/Parallel.hs +++ b/src/Streamly/Internal/Data/Stream/Parallel.hs @@ -61,6 +61,9 @@ import Control.Monad.State.Class (MonadState(..)) import Control.Monad.Trans.Class (MonadTrans(lift)) #endif import Data.Functor (void) +#if __GLASGOW_HASKELL__ >= 810 +import Data.Kind (Type) +#endif import Data.IORef (readIORef, writeIORef) import Data.Maybe (fromJust) @@ -362,6 +365,9 @@ tapAsyncK f m = K.mkStream $ \st yld sng stp -> do K.foldStreamShared st yld sng stp $ Stream.toStreamK (SVar.teeToSVar sv $ Stream.fromStreamK m) +#if __GLASGOW_HASKELL__ >= 810 +type TapState :: Type -> Type -> Type -> Type +#endif data TapState fs st a = TapInit | Tapping !fs st | TapDone st -- | Like 'tapAsync' but uses a 'Fold' instead of a fold function. diff --git a/src/Streamly/Internal/Data/Stream/SVar/Generate.hs b/src/Streamly/Internal/Data/Stream/SVar/Generate.hs index 27ebfd8034..edf4ed7e5d 100644 --- a/src/Streamly/Internal/Data/Stream/SVar/Generate.hs +++ b/src/Streamly/Internal/Data/Stream/SVar/Generate.hs @@ -113,7 +113,7 @@ toSVar sv m = do -- | Pull a stream from an SVar. {-# NOINLINE fromStreamVar #-} -fromStreamVar :: MonadAsync m => SVar K.Stream m a -> K.Stream m a +fromStreamVar :: forall m a. MonadAsync m => SVar K.Stream m a -> K.Stream m a fromStreamVar sv = K.mkStream $ \st yld sng stp -> do list <- readOutputQ sv -- Reversing the output is important to guarantee that we process the @@ -123,6 +123,7 @@ fromStreamVar sv = K.mkStream $ \st yld sng stp -> do where + allDone :: forall r. m r -> m r allDone stp = do when (svarInspectMode sv) $ do t <- liftIO $ getTime Monotonic diff --git a/streamly.cabal b/streamly.cabal index c86d961e20..72347d54ba 100644 --- a/streamly.cabal +++ b/streamly.cabal @@ -242,8 +242,6 @@ flag use-unliftio ------------------------------------------------------------------------------- common compile-options - default-language: Haskell2010 - if os(darwin) cpp-options: -DCABAL_OS_DARWIN @@ -297,6 +295,22 @@ common compile-options cpp-options: -DUSE_UNLIFTIO common default-extensions + default-language: Haskell2010 + + -- GHC2024 may include more extensions than we are actually using, see the + -- full list below. We enable this to ensure that we are able to compile + -- with this i.e. there is no interference by other extensions. + if impl(ghc >= 9.10) + default-language: GHC2024 + + if impl(ghc >= 9.2) && impl(ghc < 9.10) + default-language: GHC2021 + + if impl(ghc >= 8.10) + default-extensions: + StandaloneKindSignatures + + -- In GHC 2024 default-extensions: BangPatterns ConstraintKinds @@ -309,6 +323,7 @@ common default-extensions GeneralizedNewtypeDeriving InstanceSigs KindSignatures + LambdaCase MultiParamTypeClasses RankNTypes ScopedTypeVariables @@ -316,22 +331,31 @@ common default-extensions TypeApplications TypeOperators - -- Not GHC2021 + -- Not in GHC2024 + default-extensions: CApiFFI CPP - LambdaCase MagicHash RecordWildCards -- TypeFamilies -- required by IsHashMap type class - -- MonoLocalBinds, enabled by TypeFamilies, causes performance - -- regressions. Disable it. This must come after TypeFamilies, - -- otherwise TypeFamilies will enable it again. + + -- MonoLocalBinds, enabled by TypeFamilies and GHC2024, was + -- once found to cause runtime performance regressions which + -- does not seem to be the case anymore, but need more testing + -- to confirm. It is confirmed that it requires more memory + -- for compilation at least in some cases (Data.Fold.Window + -- benchmark on GHC-9.10.1 macOS). Disabling this must come + -- after TypeFamilies, otherwise TypeFamilies will enable it + -- again. -- NoMonoLocalBinds -- UndecidableInstances -- Does not show any perf impact -- UnboxedTuples -- interferes with (#.) + if impl(ghc >= 8.6) + default-extensions: QuantifiedConstraints + common optimization-options if flag(opt) ghc-options: -O2 @@ -364,9 +388,6 @@ common lib-options library import: lib-options - if impl(ghc >= 8.6) - default-extensions: QuantifiedConstraints - include-dirs: src , src/doctest diff --git a/test/Streamly/Test/Data/MutArray.hs b/test/Streamly/Test/Data/MutArray.hs index b91463bc79..b52bbb7375 100644 --- a/test/Streamly/Test/Data/MutArray.hs +++ b/test/Streamly/Test/Data/MutArray.hs @@ -20,7 +20,7 @@ import Test.Hspec.QuickCheck import Test.QuickCheck (forAll, Property) import Test.QuickCheck.Monadic (monadicIO, assert) #if MIN_VERSION_base(4,15,0) -import GHC.RTS.Flags (IoSubSystem(..)) +import GHC.IO.SubSystem (IoSubSystem (..)) #endif import qualified Streamly.Internal.Data.MutArray as MArray diff --git a/test/Streamly/Test/Data/Parser.hs b/test/Streamly/Test/Data/Parser.hs index fde76190dd..0ab87c82b6 100644 --- a/test/Streamly/Test/Data/Parser.hs +++ b/test/Streamly/Test/Data/Parser.hs @@ -1,3 +1,4 @@ +{-# Language NoMonoLocalBinds #-} -- XXX We are using head/tail at one place #if __GLASGOW_HASKELL__ >= 908 {-# OPTIONS_GHC -Wno-x-partial #-} diff --git a/test/lib/Streamly/Test/Prelude/Common.hs b/test/lib/Streamly/Test/Prelude/Common.hs index 9085dd5483..7c55a6b5d8 100644 --- a/test/lib/Streamly/Test/Prelude/Common.hs +++ b/test/lib/Streamly/Test/Prelude/Common.hs @@ -1,3 +1,4 @@ +{-# Language NoMonoLocalBinds #-} {-# OPTIONS_GHC -Wno-deprecations #-} -- XXX We are using head/tail at one place #if __GLASGOW_HASKELL__ >= 908 diff --git a/test/streamly-tests.cabal b/test/streamly-tests.cabal index 399697794a..470955f4ef 100644 --- a/test/streamly-tests.cabal +++ b/test/streamly-tests.cabal @@ -50,8 +50,6 @@ flag use-streamly-core ------------------------------------------------------------------------------- common compile-options - default-language: Haskell2010 - if os(darwin) cpp-options: -DCABAL_OS_DARWIN @@ -74,7 +72,6 @@ common compile-options -Wnoncanonical-monad-instances -Wmissing-export-lists -Rghc-timing - -with-rtsopts "-t" if flag(has-llvm) ghc-options: -fllvm @@ -93,10 +90,23 @@ common compile-options cpp-options: -DINCLUDE_FLAKY_TESTS common default-extensions + default-language: Haskell2010 + + -- GHC2024 may include more extensions than we are actually using, see the + -- full list below. We enable this to ensure that we are able to compile + -- with this i.e. there is no interference by other extensions. + if impl(ghc >= 9.10) + default-language: GHC2024 + + if impl(ghc >= 9.2) && impl(ghc < 9.10) + default-language: GHC2021 + + if impl(ghc >= 8.10) + default-extensions: StandaloneKindSignatures + + -- In GHC 2024 default-extensions: BangPatterns - CApiFFI - CPP ConstraintKinds DeriveDataTypeable DeriveGeneric @@ -108,24 +118,18 @@ common default-extensions InstanceSigs KindSignatures LambdaCase - MagicHash MultiParamTypeClasses - PatternSynonyms RankNTypes - RecordWildCards ScopedTypeVariables TupleSections - TypeFamilies - ViewPatterns - -- MonoLocalBinds, enabled by TypeFamilies, causes performance - -- regressions. Disable it. This must come after TypeFamilies, - -- otherwise TypeFamilies will enable it again. + -- Not in GHC2024 + CPP + MagicHash + PatternSynonyms + RecordWildCards NoMonoLocalBinds - -- UndecidableInstances -- Does not show any perf impact - -- UnboxedTuples -- interferes with (#.) - common threading-options ghc-options: -threaded -with-rtsopts=-N @@ -197,7 +201,10 @@ library common test-options import: lib-options , threading-options - ghc-options: -rtsopts -fno-ignore-asserts + ghc-options: + -rtsopts + -with-rtsopts "-t" + -fno-ignore-asserts include-dirs: . build-depends: streamly-tests @@ -211,6 +218,7 @@ common always-optimized -fmax-worker-args=16 -fspec-constr-recursive=16 -rtsopts + -with-rtsopts "-t" -fno-ignore-asserts if flag(fusion-plugin) && !impl(ghcjs) && !impl(ghc < 8.6) ghc-options: -fplugin Fusion.Plugin