Remove MonadTrans/MonadBase instances for GHC >= 9.6

Remove MonadTrans/MonadBase instances for:

* ParallelT
* AsyncT
* WAsyncT
* AheadT

To accommodate a breaking change in transformers-0.6 .
This commit is contained in:
Harendra Kumar 2023-06-30 13:54:53 +05:30
parent 8d7b837109
commit 4ccd51c2b8
9 changed files with 92 additions and 40 deletions

View File

@ -2,6 +2,15 @@
<!-- See rendered changelog at https://streamly.composewell.com -->
## Unreleased
### Breaking Changes
* MonadTrans and MonadBase instances has been removed for `AsyncT`,
`ParallelT`, `AheadT` for GHC versions 9.6 onwards. This is due to a
breaking change in `transformers` 0.6. You can replace `lift` with
`fromEffect` when using these as top level monads in a monad stack.
## 0.9.0 (Mar 2023)
Also see the following:

View File

@ -44,6 +44,6 @@ library
build-depends:
base >= 4.9 && < 4.19
, transformers >= 0.4 && < 0.6.2
, transformers >= 0.4 && < 0.7
, streamly
, streamly-core

View File

@ -34,13 +34,17 @@ where
import Control.Concurrent.MVar (putMVar, takeMVar)
import Control.Exception (assert)
import Control.Monad (void, when)
#if !(MIN_VERSION_transformers(0,6,0))
import Control.Monad.Base (MonadBase(..), liftBaseDefault)
#endif
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(..))
#if !(MIN_VERSION_transformers(0,6,0))
import Control.Monad.Trans.Class (MonadTrans(lift))
#endif
import Data.Heap (Heap, Entry(..))
import Data.IORef (IORef, readIORef, atomicModifyIORef, writeIORef)
import Data.Maybe (fromJust)
@ -693,9 +697,11 @@ consM m (AheadT r) = AheadT $ aheadK (K.fromEffect m) r
-- @since 0.8.0
newtype AheadT m a = AheadT {getAheadT :: Stream m a}
#if !(MIN_VERSION_transformers(0,6,0))
instance MonadTrans AheadT where
{-# INLINE lift #-}
lift = AheadT . K.fromEffect
#endif
-- | A serial IO stream of elements of type @a@ with concurrent lookahead. See
-- 'AheadT' documentation for more details.
@ -762,4 +768,9 @@ instance MonadAsync m => Monad (AheadT m) where
-- Other instances
------------------------------------------------------------------------------
#if !(MIN_VERSION_transformers(0,6,0))
instance (MonadBase b m, Monad m, MonadAsync m) => MonadBase b (AheadT m) where
liftBase = liftBaseDefault
#endif
MONAD_COMMON_INSTANCES(AheadT, MONADPARALLEL)

View File

@ -41,14 +41,18 @@ module Streamly.Internal.Data.Stream.Async {-# DEPRECATED "Please use \"Streamly
where
import Control.Concurrent (myThreadId)
#if !(MIN_VERSION_transformers(0,6,0))
import Control.Monad.Base (MonadBase(..), liftBaseDefault)
#endif
import Control.Monad.Catch (MonadThrow, throwM)
import Control.Concurrent.MVar (newEmptyMVar)
-- import Control.Monad.Error.Class (MonadError(..))
import Control.Monad.IO.Class (MonadIO(..))
import Control.Monad.Reader.Class (MonadReader(..))
import Control.Monad.State.Class (MonadState(..))
#if !(MIN_VERSION_transformers(0,6,0))
import Control.Monad.Trans.Class (MonadTrans(lift))
#endif
import Data.Concurrent.Queue.MichaelScott (LinkedQueue, newQ, nullQ, tryPopR, pushL)
import Data.IORef (IORef, newIORef, readIORef)
import Data.Maybe (fromJust)
@ -745,9 +749,11 @@ consMAsync m (AsyncT r) = AsyncT $ asyncK (K.fromEffect m) r
-- @since 0.8.0
newtype AsyncT m a = AsyncT {getAsyncT :: Stream m a}
#if !(MIN_VERSION_transformers(0,6,0))
instance MonadTrans AsyncT where
{-# INLINE lift #-}
lift = AsyncT . K.fromEffect
#endif
-- | A demand driven left biased parallely composing IO stream of elements of
-- type @a@. See 'AsyncT' documentation for more details.
@ -819,6 +825,11 @@ instance MonadAsync m => Monad (AsyncT m) where
-- Other instances
------------------------------------------------------------------------------
#if !(MIN_VERSION_transformers(0,6,0))
instance (MonadBase b m, Monad m, MonadAsync m) => MonadBase b (AsyncT m) where
liftBase = liftBaseDefault
#endif
MONAD_COMMON_INSTANCES(AsyncT, MONADPARALLEL)
------------------------------------------------------------------------------
@ -971,9 +982,11 @@ consMWAsync m (WAsyncT r) = WAsyncT $ wAsyncK (K.fromEffect m) r
--
newtype WAsyncT m a = WAsyncT {getWAsyncT :: Stream m a}
#if !(MIN_VERSION_transformers(0,6,0))
instance MonadTrans WAsyncT where
{-# INLINE lift #-}
lift = WAsyncT . K.fromEffect
#endif
-- | A round robin parallely composing IO stream of elements of type @a@.
-- See 'WAsyncT' documentation for more details.
@ -1043,4 +1056,9 @@ instance MonadAsync m => Monad (WAsyncT m) where
-- Other instances
------------------------------------------------------------------------------
#if !(MIN_VERSION_transformers(0,6,0))
instance (MonadBase b m, Monad m, MonadAsync m) => MonadBase b (WAsyncT m) where
liftBase = liftBaseDefault
#endif
MONAD_COMMON_INSTANCES(WAsyncT, MONADPARALLEL)

View File

@ -15,14 +15,11 @@ instance Monad m => Functor (STREAM m) where { \
{-# INLINE (<$) #-}; \
(<$) = fmap . const }; \
\
instance (MonadBase b m, Monad m CONSTRAINT) => MonadBase b (STREAM m) where {\
liftBase = liftBaseDefault }; \
\
instance (MonadIO m CONSTRAINT) => MonadIO (STREAM m) where { \
liftIO = lift . liftIO }; \
liftIO x = STREAM $ K.fromEffect $ liftIO x }; \
\
instance (MonadThrow m CONSTRAINT) => MonadThrow (STREAM m) where { \
throwM = lift . throwM }; \
throwM x = STREAM $ K.fromEffect $ throwM x }; \
\
{- \
instance (MonadError e m CONSTRAINT) => MonadError e (STREAM m) where { \
@ -32,16 +29,16 @@ instance (MonadError e m CONSTRAINT) => MonadError e (STREAM m) where { \
-} \
\
instance (MonadReader r m CONSTRAINT) => MonadReader r (STREAM m) where { \
ask = lift ask; \
ask = STREAM $ K.fromEffect ask; \
local f (STREAM m) = STREAM $ withLocal f m }; \
\
instance (MonadState s m CONSTRAINT) => MonadState s (STREAM m) where { \
{-# INLINE get #-}; \
get = lift get; \
get = STREAM $ K.fromEffect get; \
{-# INLINE put #-}; \
put x = lift (put x); \
put x = STREAM $ K.fromEffect $ put x; \
{-# INLINE state #-}; \
state k = lift (state k) }
state k = STREAM $ K.fromEffect $ state k }
------------------------------------------------------------------------------
-- Lists

View File

@ -49,13 +49,17 @@ where
import Control.Concurrent (myThreadId, takeMVar)
import Control.Monad (when)
#if !(MIN_VERSION_transformers(0,6,0))
import Control.Monad.Base (MonadBase(..), liftBaseDefault)
#endif
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(..))
#if !(MIN_VERSION_transformers(0,6,0))
import Control.Monad.Trans.Class (MonadTrans(lift))
#endif
import Data.Functor (void)
import Data.IORef (readIORef, writeIORef)
import Data.Maybe (fromJust)
@ -432,9 +436,11 @@ tapAsyncF f (D.Stream step1 state1) = D.Stream step TapInit
-- @since 0.8.0
newtype ParallelT m a = ParallelT {getParallelT :: K.StreamK m a}
#if !(MIN_VERSION_transformers(0,6,0))
instance MonadTrans ParallelT where
{-# INLINE lift #-}
lift = ParallelT . K.fromEffect
#endif
-- | A parallely composing IO stream of elements of type @a@.
-- See 'ParallelT' documentation for more details.
@ -504,6 +510,11 @@ instance MonadAsync m => Monad (ParallelT m) where
-- Other instances
------------------------------------------------------------------------------
#if !(MIN_VERSION_transformers(0,6,0))
instance (MonadBase b m, Monad m, MonadAsync m) => MonadBase b (ParallelT m) where
liftBase = liftBaseDefault
#endif
MONAD_COMMON_INSTANCES(ParallelT, MONADPARALLEL)
-------------------------------------------------------------------------------

View File

@ -48,9 +48,13 @@ module Streamly.Internal.Data.Stream.Serial {-# DEPRECATED "Please use \"Streaml
)
where
#if !(MIN_VERSION_base(4,18,0))
import Control.Applicative (liftA2)
#endif
import Control.DeepSeq (NFData(..), NFData1(..))
#if !(MIN_VERSION_transformers(0,6,0))
import Control.Monad.Base (MonadBase(..), liftBaseDefault)
#endif
import Control.Monad.Catch (MonadThrow, throwM)
import Control.Monad.IO.Class (MonadIO(..))
import Control.Monad.Reader.Class (MonadReader(..))
@ -408,6 +412,11 @@ instance Monad m => Monad (WSerialT m) where
-- Other instances
------------------------------------------------------------------------------
#if !(MIN_VERSION_transformers(0,6,0))
instance (MonadBase b m, Monad m) => MonadBase b (SerialT m) where
liftBase = liftBaseDefault
#endif
MONAD_COMMON_INSTANCES(WSerialT,)
LIST_INSTANCES(WSerialT)
NFDATA1_INSTANCE(WSerialT)

View File

@ -401,25 +401,12 @@ library
, Streamly.Network.Socket
, Streamly.Network.Inet.TCP
-- Deprecated modules
-- Deprecated
, Streamly
, Streamly.Data.Unicode.Stream
, Streamly.Memory.Array
, Streamly.Data.Array.Foreign
if !impl(ghcjs) && flag(dev)
exposed-modules:
Streamly.Internal.System.IOVec.Type
, Streamly.Internal.System.IOVec
, Streamly.Internal.FileSystem.FDIO
, Streamly.Internal.FileSystem.FD
if impl(ghc <= 9.4.5)
exposed-modules:
Streamly
, Streamly.Data.Unicode.Stream
, Streamly.Prelude
, Streamly.Internal.Data.Stream.Async
, Streamly.Internal.Data.Stream.Parallel
, Streamly.Internal.Data.Stream.Ahead
-- Deprecated Internal modules
, Streamly.Internal.Data.SVar.Worker
@ -435,6 +422,9 @@ library
, Streamly.Internal.Data.Stream.Serial
, Streamly.Internal.Data.Stream.Zip
, Streamly.Internal.Data.Stream.Async
, Streamly.Internal.Data.Stream.Parallel
, Streamly.Internal.Data.Stream.Ahead
, Streamly.Internal.Data.Stream.ZipAsync
, Streamly.Internal.Data.Stream.IsStream.Type
@ -451,6 +441,13 @@ library
, Streamly.Internal.Data.Stream.IsStream.Top
, Streamly.Internal.Data.Stream.IsStream
if !impl(ghcjs) && flag(dev)
exposed-modules:
Streamly.Internal.System.IOVec.Type
, Streamly.Internal.System.IOVec
, Streamly.Internal.FileSystem.FDIO
, Streamly.Internal.FileSystem.FD
if flag(dev)
exposed-modules: Streamly.Data.SmallArray
, Streamly.Internal.Data.SmallArray
@ -506,7 +503,7 @@ library
-- Network
, network >= 2.6 && < 3.2
if impl(ghc <= 9.4.5)
if impl(ghc < 9.6)
build-depends: transformers-base >= 0.4 && < 0.5
if flag(use-unliftio)

View File

@ -180,7 +180,7 @@ library
import: lib-options, test-dependencies
hs-source-dirs: lib
exposed-modules: Streamly.Test.Common
if !flag(use-streamly-core) && impl(ghc < 9.4.5)
if !flag(use-streamly-core)
exposed-modules: Streamly.Test.Prelude.Common
if flag(limit-build-mem)
ghc-options: +RTS -M1500M -RTS
@ -386,7 +386,7 @@ test-suite Prelude
type: exitcode-stdio-1.0
main-is: Streamly/Test/Prelude.hs
ghc-options: -main-is Streamly.Test.Prelude.main
if flag(use-streamly-core) || impl(ghc >= 9.6)
if flag(use-streamly-core)
buildable: False
test-suite Prelude.Ahead
@ -394,7 +394,7 @@ test-suite Prelude.Ahead
type: exitcode-stdio-1.0
main-is: Streamly/Test/Prelude/Ahead.hs
ghc-options: -main-is Streamly.Test.Prelude.Ahead.main
if flag(use-streamly-core) || impl(ghc >= 9.6)
if flag(use-streamly-core)
buildable: False
test-suite Prelude.Async
@ -402,7 +402,7 @@ test-suite Prelude.Async
type: exitcode-stdio-1.0
main-is: Streamly/Test/Prelude/Async.hs
ghc-options: -main-is Streamly.Test.Prelude.Async.main
if flag(use-streamly-core) || impl(ghc >= 9.6)
if flag(use-streamly-core)
buildable: False
test-suite Data.Stream.Concurrent
@ -420,7 +420,7 @@ test-suite Prelude.Concurrent
ghc-options: -main-is Streamly.Test.Prelude.Concurrent.main
if flag(limit-build-mem)
ghc-options: +RTS -M2000M -RTS
if flag(use-streamly-core) || impl(ghc >= 9.6)
if flag(use-streamly-core)
buildable: False
test-suite Prelude.Fold
@ -428,7 +428,7 @@ test-suite Prelude.Fold
type: exitcode-stdio-1.0
main-is: Streamly/Test/Prelude/Fold.hs
ghc-options: -main-is Streamly.Test.Prelude.Fold.main
if flag(use-streamly-core) || impl(ghc >= 9.6)
if flag(use-streamly-core)
buildable: False
test-suite Prelude.Parallel
@ -436,7 +436,7 @@ test-suite Prelude.Parallel
type: exitcode-stdio-1.0
main-is: Streamly/Test/Prelude/Parallel.hs
ghc-options: -main-is Streamly.Test.Prelude.Parallel.main
if flag(use-streamly-core) || impl(ghc >= 9.6)
if flag(use-streamly-core)
buildable: False
test-suite Prelude.Rate
@ -458,14 +458,14 @@ test-suite Prelude.Serial
ghc-options: -main-is Streamly.Test.Prelude.Serial.main
if flag(limit-build-mem)
ghc-options: +RTS -M1500M -RTS
if flag(use-streamly-core) || impl(ghc >= 9.6)
if flag(use-streamly-core)
buildable: False
test-suite Prelude.Top
import: test-options
type: exitcode-stdio-1.0
main-is: Streamly/Test/Prelude/Top.hs
if flag(use-streamly-core) || impl(ghc >= 9.6)
if flag(use-streamly-core)
buildable: False
test-suite Prelude.WAsync
@ -473,7 +473,7 @@ test-suite Prelude.WAsync
type: exitcode-stdio-1.0
main-is: Streamly/Test/Prelude/WAsync.hs
ghc-options: -main-is Streamly.Test.Prelude.WAsync.main
if flag(use-streamly-core) || impl(ghc >= 9.6)
if flag(use-streamly-core)
buildable: False
test-suite Prelude.WSerial
@ -481,7 +481,7 @@ test-suite Prelude.WSerial
type: exitcode-stdio-1.0
main-is: Streamly/Test/Prelude/WSerial.hs
ghc-options: -main-is Streamly.Test.Prelude.WSerial.main
if flag(use-streamly-core) || impl(ghc >= 9.6)
if flag(use-streamly-core)
buildable: False
test-suite Prelude.ZipAsync
@ -491,7 +491,7 @@ test-suite Prelude.ZipAsync
ghc-options: -main-is Streamly.Test.Prelude.ZipAsync.main
if flag(limit-build-mem)
ghc-options: +RTS -M750M -RTS
if flag(use-streamly-core) || impl(ghc >= 9.6)
if flag(use-streamly-core)
buildable: False
test-suite Prelude.ZipSerial
@ -499,7 +499,7 @@ test-suite Prelude.ZipSerial
type: exitcode-stdio-1.0
main-is: Streamly/Test/Prelude/ZipSerial.hs
ghc-options: -main-is Streamly.Test.Prelude.ZipSerial.main
if flag(use-streamly-core) || impl(ghc >= 9.6)
if flag(use-streamly-core)
buildable: False
test-suite Unicode.Stream