Remove support for GHC 8.4.*

This commit is contained in:
Adithya Kumar 2022-09-28 15:21:17 +05:30
parent 4e4c194f74
commit 09ed99de1f
12 changed files with 11 additions and 193 deletions

View File

@ -409,8 +409,8 @@ workflows:
#- cabal-ghc-8_0_2:
# name: GHC 8.0.2 + no-test + no-bench + no-docs
#- cabal-ghc-7.10.3
- cabal-ghcjs-8_4:
name: GHCJS 8.4 + no-test + no-docs
# - cabal-ghcjs-8_4:
# name: GHCJS 8.4 + no-test + no-docs
#- stack-ghc-8.4
#- stack-ghc-8.2
#- coveralls-ghc-8.2.2

View File

@ -157,13 +157,6 @@ jobs:
cabal_project: cabal.project
cabal_build_options: "--flag debug --flag -opt"
ignore_error: false
- name: 8.4.4-sdist
ghc_version: 8.4.4
runner: ubuntu-latest
build: cabal
cabal_version: 3.6.2.0
cabal_project: cabal.project
ignore_error: false
steps:
- uses: actions/checkout@v2

View File

@ -113,128 +113,6 @@ unpin arr@(MutableByteArray marr#) =
-- The Unboxed type class
--------------------------------------------------------------------------------
#if !MIN_VERSION_base(4,12,0)
#define SIZEOF_HSCHAR_PRIMITIVE 4#
#define SIZEOF_HSINT_PRIMITIVE 8#
#define SIZEOF_HSWORD_PRIMITIVE 8#
#define SIZEOF_WORD8_PRIMITIVE 1#
#define SIZEOF_WORD32_PRIMITIVE 4#
#define SIZEOF_WORD64_PRIMITIVE 8#
#define SIZEOF_HSDOUBLE_PRIMITIVE 8#
#define SIZEOF_INT32_PRIMITIVE 4#
#define SIZEOF_INT64_PRIMITIVE 8#
#ifdef __GHCJS__
#define WORD64TYP Word64#
#else
#define WORD64TYP Word#
#endif
#ifdef __GHCJS__
#define INT64TYP Int64#
#else
#define INT64TYP Int#
#endif
{-# INLINE readWord8ArrayAsWideChar# #-}
readWord8ArrayAsWideChar# ::
MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #)
readWord8ArrayAsWideChar# arr# i# =
readWideCharArray# arr# (quotInt# i# SIZEOF_HSCHAR_PRIMITIVE)
{-# INLINE writeWord8ArrayAsWideChar# #-}
writeWord8ArrayAsWideChar# ::
MutableByteArray# d -> Int# -> Char# -> State# d -> State# d
writeWord8ArrayAsWideChar# arr# i# =
writeWideCharArray# arr# (quotInt# i# SIZEOF_HSCHAR_PRIMITIVE)
{-# INLINE readWord8ArrayAsInt# #-}
readWord8ArrayAsInt# ::
MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #)
readWord8ArrayAsInt# arr# i# =
readIntArray# arr# (quotInt# i# SIZEOF_HSINT_PRIMITIVE)
{-# INLINE writeWord8ArrayAsInt# #-}
writeWord8ArrayAsInt# ::
MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
writeWord8ArrayAsInt# arr# i# =
writeIntArray# arr# (quotInt# i# SIZEOF_HSINT_PRIMITIVE)
{-# INLINE readWord8ArrayAsInt32# #-}
readWord8ArrayAsInt32# ::
MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #)
readWord8ArrayAsInt32# arr# i# =
readInt32Array# arr# (quotInt# i# SIZEOF_INT32_PRIMITIVE)
{-# INLINE writeWord8ArrayAsInt32# #-}
writeWord8ArrayAsInt32# ::
MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
writeWord8ArrayAsInt32# arr# i# =
writeInt32Array# arr# (quotInt# i# SIZEOF_INT32_PRIMITIVE)
{-# INLINE readWord8ArrayAsInt64# #-}
readWord8ArrayAsInt64# ::
MutableByteArray# d -> Int# -> State# d -> (# State# d, INT64TYP #)
readWord8ArrayAsInt64# arr# i# =
readInt64Array# arr# (quotInt# i# SIZEOF_INT64_PRIMITIVE)
{-# INLINE writeWord8ArrayAsInt64# #-}
writeWord8ArrayAsInt64# ::
MutableByteArray# d -> Int# -> INT64TYP -> State# d -> State# d
writeWord8ArrayAsInt64# arr# i# =
writeInt64Array# arr# (quotInt# i# SIZEOF_INT64_PRIMITIVE)
{-# INLINE readWord8ArrayAsWord# #-}
readWord8ArrayAsWord# ::
MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #)
readWord8ArrayAsWord# arr# i# =
readWordArray# arr# (quotInt# i# SIZEOF_HSWORD_PRIMITIVE)
{-# INLINE writeWord8ArrayAsWord# #-}
writeWord8ArrayAsWord# ::
MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
writeWord8ArrayAsWord# arr# i# =
writeWordArray# arr# (quotInt# i# SIZEOF_HSWORD_PRIMITIVE)
{-# INLINE readWord8ArrayAsWord32# #-}
readWord8ArrayAsWord32# ::
MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #)
readWord8ArrayAsWord32# arr# i# =
readWord32Array# arr# (quotInt# i# SIZEOF_WORD32_PRIMITIVE)
{-# INLINE writeWord8ArrayAsWord32# #-}
writeWord8ArrayAsWord32# ::
MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
writeWord8ArrayAsWord32# arr# i# =
writeWord32Array# arr# (quotInt# i# SIZEOF_WORD32_PRIMITIVE)
{-# INLINE readWord8ArrayAsWord64# #-}
readWord8ArrayAsWord64# ::
MutableByteArray# d -> Int# -> State# d -> (# State# d, WORD64TYP #)
readWord8ArrayAsWord64# arr# i# =
readWord64Array# arr# (quotInt# i# SIZEOF_WORD64_PRIMITIVE)
{-# INLINE writeWord8ArrayAsWord64# #-}
writeWord8ArrayAsWord64# ::
MutableByteArray# d -> Int# -> WORD64TYP -> State# d -> State# d
writeWord8ArrayAsWord64# arr# i# =
writeWord64Array# arr# (quotInt# i# SIZEOF_WORD64_PRIMITIVE)
{-# INLINE readWord8ArrayAsDouble# #-}
readWord8ArrayAsDouble# ::
MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #)
readWord8ArrayAsDouble# arr# i# =
readDoubleArray# arr# (quotInt# i# SIZEOF_HSDOUBLE_PRIMITIVE)
{-# INLINE writeWord8ArrayAsDouble# #-}
writeWord8ArrayAsDouble# ::
MutableByteArray# d -> Int# -> Double# -> State# d -> State# d
writeWord8ArrayAsDouble# arr# i# =
writeDoubleArray# arr# (quotInt# i# SIZEOF_HSDOUBLE_PRIMITIVE)
#endif
-- In theory we could convert a type to and from a byte stream and use that
-- to implement boxing, unboxing. But that would be inefficient. This type
-- class allows each primitive type to have its own specific efficient

View File

@ -3,6 +3,7 @@
<!-- See rendered changelog at https://streamly.composewell.com -->
## Unreleased
* Remove support for GHC 8.4.*
* The unboxed arrays now require `Unbox` instance along with `Storable` for the
stored type. The `Unbox` typeclass can be found in `Streamly.Data.Unbox`.
* New modules for unboxed mutable & unboxed immutable arrays are added.

View File

@ -46,9 +46,6 @@ import Control.Monad (when, void)
import Control.Monad.IO.Class (MonadIO(liftIO))
import Data.Maybe (fromJust, fromMaybe)
import Data.IORef (IORef, modifyIORef, newIORef, readIORef, writeIORef)
#if __GLASGOW_HASKELL__ < 804
import Data.Semigroup ((<>))
#endif
import Streamly.Internal.Control.Concurrent (MonadAsync, askRunInIO)
import Streamly.Internal.Control.ForkLifted (doFork)
import Streamly.Internal.Data.Atomics

View File

@ -44,9 +44,6 @@ import Control.Monad (when, void)
import Control.Monad.IO.Class (MonadIO(liftIO))
import Data.Maybe (fromJust, fromMaybe)
import Data.IORef (IORef, modifyIORef, newIORef, readIORef, writeIORef)
#if __GLASGOW_HASKELL__ < 804
import Data.Semigroup ((<>))
#endif
import Streamly.Internal.Control.ForkLifted (doFork)
import Streamly.Internal.Data.Atomics
(atomicModifyIORefCAS, atomicModifyIORefCAS_, writeBarrier,

View File

@ -152,13 +152,11 @@ infixr 5 |:
--
-- @since 0.8.0
class
#if __GLASGOW_HASKELL__ >= 806
( forall m a. MonadAsync m => Semigroup (t m a)
, forall m a. MonadAsync m => Monoid (t m a)
, forall m. Monad m => Functor (t m)
, forall m. MonadAsync m => Applicative (t m)
) =>
#endif
IsStream t where
toStream :: t m a -> K.Stream m a
fromStream :: K.Stream m a -> t m a

View File

@ -57,13 +57,8 @@ isNonBlocking fd = fdIsNonBlocking fd /= 0
-- "poll"s the fd for data to become available or timeout
-- See cbits/inputReady.c in base package
#if __GLASGOW_HASKELL__ >= 804
foreign import ccall unsafe "fdReady"
unsafe_fdReady :: CInt -> CBool -> Int64 -> CBool -> IO CInt
#else
foreign import ccall safe "fdReady"
unsafe_fdReady :: CInt -> CInt -> CInt -> CInt -> IO CInt
#endif
writeNonBlocking :: String -> FD -> Ptr Word8 -> Int -> CSize -> IO CInt
writeNonBlocking loc !fd !buf !off !len

View File

@ -31,8 +31,7 @@ homepage: https://streamly.composewell.com
bug-reports: https://github.com/composewell/streamly/issues
license: BSD-3-Clause
license-file: LICENSE
tested-with: GHC==8.4.4
, GHC==8.6.5
tested-with: GHC==8.6.5
, GHC==8.8.4
, GHC==8.10.7
, GHC==9.0.2

View File

@ -410,8 +410,6 @@ enumerateFromThenToSmallUnit =
in testUnfold unf (f :: (), th, to) $
Prelude.take 1 $ Prelude.enumFromThenTo f th to
#if MIN_VERSION_base(4,12,0)
enumerateFromFractional :: Property
enumerateFromFractional =
property
@ -443,8 +441,6 @@ enumerateFromToFractional =
let unf = UF.enumerateFromToFractional
in testUnfold unf (f :: Double, t) [f..(t :: Double)]
#endif
-------------------------------------------------------------------------------
-- Stream transformation
-------------------------------------------------------------------------------
@ -651,12 +647,10 @@ testGeneration =
prop "enumerateFromToSmallBool" enumerateFromToSmallBool
prop "enumerateFromThenToSmallBool" enumerateFromThenToSmallBool
#if MIN_VERSION_base(4,12,0)
prop "enumerateFromFractional" enumerateFromFractional
prop "enumerateFromThenFractional" enumerateFromThenFractional
prop "enumerateFromToFractional" enumerateFromToFractional
prop "enumerateFromThenToFractional" enumerateFromThenToFractional
#endif
testTransformation :: Spec
testTransformation =

View File

@ -555,10 +555,8 @@ main = hspec
serialOps $ prop "serially replicateM" . constructWithReplicateM
serialOps $ prop "serially intFromThenTo" .
constructWithIntFromThenTo
#if __GLASGOW_HASKELL__ >= 806
serialOps $ prop "serially DoubleFromThenTo" .
constructWithDoubleFromThenTo
#endif
serialOps $ prop "serially iterate" . constructWithIterate
-- XXX test for all types of streams
serialOps $ prop "serially iterateM" . constructWithIterateM

View File

@ -15,9 +15,7 @@ module Streamly.Test.Prelude.Common
, constructWithReplicate
, constructWithReplicateM
, constructWithIntFromThenTo
#if __GLASGOW_HASKELL__ >= 806
, constructWithDoubleFromThenTo
#endif
, constructWithIterate
, constructWithIterateM
, constructWithEnumerate
@ -221,7 +219,6 @@ constructWithRepeatM = constructWithLenM stream list
stream n = S.take n $ S.repeatM (return 1)
list n = return $ replicate n 1
#if __GLASGOW_HASKELL__ >= 806
-- XXX try very small steps close to 0
constructWithDoubleFromThenTo
:: IsStream t
@ -235,7 +232,6 @@ constructWithDoubleFromThenTo op l =
let list len = take len [from,next..to]
stream len = S.take len $ S.enumerateFromThenTo from next to
in constructWithLen stream list op l
#endif
constructWithIterate ::
IsStream t => (t IO Int -> SerialT IO Int) -> Word8 -> Property
@ -396,11 +392,7 @@ constructWithUnfoldr listT op len =
else Just (seed, seed + 1)
constructWithFromPure ::
(IsStream t
#if __GLASGOW_HASKELL__ < 806
, Monoid (t IO Int)
#endif
)
(IsStream t, Monoid (t IO Int))
=> ([Int] -> [Int])
-> (t IO Int -> SerialT IO Int)
-> Word8
@ -416,11 +408,7 @@ constructWithFromPure listT op len =
listEquals (==) (listT strm) list
constructWithFromEffect ::
(IsStream t
#if __GLASGOW_HASKELL__ < 806
, Monoid (t IO Int)
#endif
)
(IsStream t, Monoid (t IO Int))
=> ([Int] -> [Int])
-> (t IO Int -> SerialT IO Int)
-> Word8
@ -1033,11 +1021,7 @@ foldFromList constr op eq = transformFromList constr eq id op
-- XXX concatenate streams of multiple elements rather than single elements
semigroupOps
:: (IsStream t
#if __GLASGOW_HASKELL__ < 804
, Semigroup (t IO Int)
#endif
, Monoid (t IO Int))
:: (IsStream t, Monoid (t IO Int))
=> String
-> ([Int] -> [Int] -> Bool)
-> (t IO Int -> SerialT IO Int)
@ -1469,11 +1453,7 @@ bracketPartialStreamProp t vec =
#endif
bracketExceptionProp ::
(IsStream t, MonadThrow (t IO)
#if __GLASGOW_HASKELL__ < 806
, Semigroup (t IO Int)
#endif
)
(IsStream t, MonadThrow (t IO), Semigroup (t IO Int))
=> (t IO Int -> SerialT IO Int)
-> Property
bracketExceptionProp t =
@ -1560,11 +1540,7 @@ finallyPartialStreamProp t vec =
#endif
finallyExceptionProp ::
(IsStream t, MonadThrow (t IO)
#if __GLASGOW_HASKELL__ < 806
, Semigroup (t IO Int)
#endif
)
(IsStream t, MonadThrow (t IO), Semigroup (t IO Int))
=> (t IO Int -> SerialT IO Int)
-> Property
finallyExceptionProp t =
@ -1582,11 +1558,7 @@ finallyExceptionProp t =
assert $ refValue == 1
onExceptionProp ::
(IsStream t, MonadThrow (t IO)
#if __GLASGOW_HASKELL__ < 806
, Semigroup (t IO Int)
#endif
)
(IsStream t, MonadThrow (t IO), Semigroup (t IO Int))
=> (t IO Int -> SerialT IO Int)
-> Property
onExceptionProp t =
@ -1620,11 +1592,7 @@ handleProp t vec =
assert $ res == vec ++ [0] ++ vec
exceptionOps ::
(IsStream t, MonadThrow (t IO)
#if __GLASGOW_HASKELL__ < 806
, Semigroup (t IO Int)
#endif
)
(IsStream t, MonadThrow (t IO), Semigroup (t IO Int))
=> String
-> (t IO Int -> SerialT IO Int)
-> Spec