Merge pull request #335 from barrucadu/ghc9

Add support for GHC 9.0
This commit is contained in:
Michael Walker 2021-03-14 11:38:49 +00:00 committed by GitHub
commit 7fa062198d
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
23 changed files with 77 additions and 53 deletions

View File

@ -15,14 +15,15 @@
# I don't think this helps
- ignore: {name: "Avoid lambda using `infix`"}
# Breaks type inference with higher-rank types in GHC 9
- ignore: {name: Use const}
# Inapplicable
- ignore: {name: Use readTVarIO, within: Control.Monad.Conc.Class}
# GHC treats infix $ specially wrt type checking, so that things like
# "runST $ do ..." work even though they're impredicative.
# Unfortunately, this means that HLint's "avoid lambda" warning for
# this module would lead to code which no longer compiles!
# Type inference errors
- ignore: {name: Avoid lambda, within: Test.DejaFu.Conc.Internal.Program}
- ignore: {name: Avoid lambda, within: Examples.SearchParty}
# Prefer applicative operators over monadic ones.
- suggest: {name: Generalise monadic functions, lhs: return, rhs: pure}

View File

@ -42,8 +42,8 @@ There are a few different packages under the Déjà Fu umbrella:
| | Version | Summary |
| - | ------- | ------- |
| [concurrency][h:conc] | 1.11.0.0 | Typeclasses, functions, and data types for concurrency and STM. |
| [dejafu][h:dejafu] | 2.4.0.1 | Systematic testing for Haskell concurrency. |
| [concurrency][h:conc] | 1.11.0.1 | Typeclasses, functions, and data types for concurrency and STM. |
| [dejafu][h:dejafu] | 2.4.0.2 | Systematic testing for Haskell concurrency. |
| [hunit-dejafu][h:hunit] | 2.0.0.4 | Deja Fu support for the HUnit test framework. |
| [tasty-dejafu][h:tasty] | 2.0.0.7 | Deja Fu support for the Tasty test framework. |

View File

@ -6,6 +6,19 @@ standard Haskell versioning scheme.
.. _PVP: https://pvp.haskell.org/
1.11.0.1 (2021-03-14)
---------------------
* Git: :tag:`concurrency-1.11.0.1`
* Hackage: :hackage:`concurrency-1.11.0.1`
Fixed
~~~~~
* (:issue:`334`) Compilation error under GHC 9 due to use of
``const``.
1.11.0.0 (2020-05-14)
--------------------

View File

@ -9,7 +9,7 @@
-- |
-- Module : Control.Monad.Conc.Class
-- Copyright : (c) 2016--2020 Michael Walker
-- Copyright : (c) 2016--2021 Michael Walker
-- License : MIT
-- Maintainer : Michael Walker <mike@barrucadu.co.uk>
-- Stability : experimental
@ -101,6 +101,7 @@ import Control.Monad.Fail (MonadFail(..))
import Control.Monad.STM.Class (IsSTM, MonadSTM, TVar, fromIsSTM,
newTVar, readTVar)
import Control.Monad.Trans.Control (MonadTransControl, StT, liftWith)
import Data.Kind (Type)
import Data.Proxy (Proxy(..))
-- for the 'IO' instance
@ -195,7 +196,7 @@ class ( Monad m
-- | The associated 'MonadSTM' for this class.
--
-- @since 1.0.0.0
type STM m :: * -> *
type STM m :: Type -> Type
-- | The mutable reference type, like 'MVar's. This may contain one
-- value at a time, attempting to read or take from an \"empty\"
@ -203,26 +204,26 @@ class ( Monad m
-- \"full\" @MVar@ will block until it is empty.
--
-- @since 1.0.0.0
type MVar m :: * -> *
type MVar m :: Type -> Type
-- | The mutable non-blocking reference type. These may suffer from
-- relaxed memory effects if functions outside the set @newIORef@,
-- @readIORef@, @atomicModifyIORef@, and @atomicWriteIORef@ are used.
--
-- @since 1.6.0.0
type IORef m :: * -> *
type IORef m :: Type -> Type
-- | When performing compare-and-swap operations on @IORef@s, a
-- @Ticket@ is a proof that a thread observed a specific previous
-- value.
--
-- @since 1.0.0.0
type Ticket m :: * -> *
type Ticket m :: Type -> Type
-- | An abstract handle to a thread.
--
-- @since 1.0.0.0
type ThreadId m :: *
type ThreadId m :: Type
-- | Like 'fork', but the child thread is passed a function that can
-- be used to unmask asynchronous exceptions. This function should
@ -522,7 +523,7 @@ class ( Monad m
--
-- @since 1.5.0.0
fork :: MonadConc m => m () -> m (ThreadId m)
fork ma = forkWithUnmask (const ma)
fork ma = forkWithUnmask (\_ -> ma)
-- | Fork a computation to happen on a specific processor. The
-- specified int is the /capability number/, typically capabilities
@ -532,7 +533,7 @@ fork ma = forkWithUnmask (const ma)
--
-- @since 1.5.0.0
forkOn :: MonadConc m => Int -> m () -> m (ThreadId m)
forkOn c ma = forkOnWithUnmask c (const ma)
forkOn c ma = forkOnWithUnmask c (\_ -> ma)
-- | Fork a computation to happen in a /bound thread/, which is
-- necessary if you need to call foreign (non-Haskell) libraries
@ -540,7 +541,7 @@ forkOn c ma = forkOnWithUnmask c (const ma)
--
-- @since 1.5.0.0
forkOS :: MonadConc m => m () -> m (ThreadId m)
forkOS ma = forkOSWithUnmask (const ma)
forkOS ma = forkOSWithUnmask (\_ -> ma)
-- | Fork a thread and call the supplied function when the thread is
-- about to terminate, with an exception or a returned value. The
@ -578,21 +579,21 @@ killThread tid = throwTo tid ThreadKilled
--
-- @since 1.0.0.0
forkN :: MonadConc m => String -> m () -> m (ThreadId m)
forkN name ma = forkWithUnmaskN name (const ma)
forkN name ma = forkWithUnmaskN name (\_ -> ma)
-- | Like 'forkOn', but the thread is given a name which may be used
-- to present more useful debugging information.
--
-- @since 1.0.0.0
forkOnN :: MonadConc m => String -> Int -> m () -> m (ThreadId m)
forkOnN name i ma = forkOnWithUnmaskN name i (const ma)
forkOnN name i ma = forkOnWithUnmaskN name i (\_ -> ma)
-- | Like 'forkOS', but the thread is given a name which may be used
-- to present more useful debugging information.
--
-- @since 1.5.0.0
forkOSN :: MonadConc m => String -> m () -> m (ThreadId m)
forkOSN name ma = forkOSWithUnmaskN name (const ma)
forkOSN name ma = forkOSWithUnmaskN name (\_ -> ma)
-- | 'True' if bound threads are supported. If
-- 'rtsSupportsBoundThreads' is 'False', 'isCurrentThreadBound' will

View File

@ -6,7 +6,7 @@
-- |
-- Module : Control.Monad.STM.Class
-- Copyright : (c) 2016--2017 Michael Walker
-- Copyright : (c) 2016--2021 Michael Walker
-- License : MIT
-- Maintainer : Michael Walker <mike@barrucadu.co.uk>
-- Stability : experimental
@ -65,6 +65,7 @@ import Control.Monad.Fail (MonadFail(..))
import Control.Monad.Reader (ReaderT)
import Control.Monad.Trans (lift)
import Control.Monad.Trans.Identity (IdentityT)
import Data.Kind (Type)
import qualified Control.Concurrent.STM as STM
import qualified Control.Monad.Catch as Ca
@ -94,7 +95,7 @@ class (Ca.MonadCatch stm, MonadPlus stm) => MonadSTM stm where
-- synchronised.
--
-- @since 1.0.0.0
type TVar stm :: * -> *
type TVar stm :: Type -> Type
-- | Create a new @TVar@ containing the given value.
--

View File

@ -2,7 +2,7 @@
-- documentation, see http://haskell.org/cabal/users-guide/
name: concurrency
version: 1.11.0.0
version: 1.11.0.1
synopsis: Typeclasses, functions, and data types for concurrency and STM.
description:
@ -32,7 +32,7 @@ source-repository head
source-repository this
type: git
location: https://github.com/barrucadu/dejafu.git
tag: concurrency-1.11.0.0
tag: concurrency-1.11.0.1
library
exposed-modules: Control.Monad.Conc.Class

View File

@ -13,8 +13,6 @@ import Control.Monad.IO.Class (MonadIO, liftIO)
import Data.Maybe (isJust)
import Data.Set (fromList)
import qualified Hedgehog as H
import Test.DejaFu (defaultMemType, defaultWay)
import Test.DejaFu.Conc (ConcIO)
import Test.DejaFu.SCT (runSCT)
import Common

View File

@ -11,7 +11,7 @@ import Common
tests :: [TestTree]
tests = toTestList
[ TEST' True "testing exposes a deadlock" parFilter deadlocksSometimes [("randomly", toSettings (randomly (mkStdGen 0) 150)), ("systematically", defaultSettings)] True
[ TEST' False "testing exposes a deadlock" parFilter deadlocksSometimes [("randomly", toSettings (randomly (mkStdGen 0) 150)), ("systematically", defaultSettings)] True
]
parFilter :: (MonadConc m, MonadIO m) => m Bool

View File

@ -26,7 +26,7 @@ import Data.Maybe (fromJust, isNothing)
-- test imports
import Data.List (sort)
import Test.DejaFu (Predicate, alwaysSameOn)
import Test.DejaFu (alwaysSameOn)
import Common
@ -161,7 +161,7 @@ blockOn fs = do
_ -> retry
-- Kill everything if something failed.
unless success_ $ mapM_ (_killme . unWrap) fs
unless success_ $ mapM_ (\x -> _killme (unWrap x)) fs
pure success_

View File

@ -15,7 +15,6 @@ import Data.List (sort)
import Data.Maybe (isJust, isNothing)
import Data.Typeable (Typeable)
import Test.DejaFu (alwaysTrue)
import Test.DejaFu.Conc (ConcIO)
import Common

View File

@ -4,8 +4,7 @@ module Integration.Litmus where
import Control.Monad (replicateM, void)
import Data.List (nub, sort)
import Test.DejaFu (MemType(..), defaultWay, gives')
import Test.DejaFu.Conc (ConcIO)
import Test.DejaFu (gives')
import Test.DejaFu.SCT (runSCT)
import qualified Test.Tasty.Hedgehog as H

View File

@ -4,9 +4,8 @@ import qualified Control.Concurrent.Classy as C
import Control.Monad.Catch.Pure (runCatchT)
import Control.Monad.ST (runST)
import Test.DejaFu.Conc (Condition(..), Program,
roundRobinSched, runConcurrent)
import Test.DejaFu.Settings (defaultMemType)
import Test.DejaFu.Conc (Condition(..), roundRobinSched,
runConcurrent)
import Test.DejaFu.Types (MonadDejaFu)
import qualified Test.Tasty.HUnit as TH

View File

@ -6,8 +6,7 @@ import Control.Monad (replicateM, void, when)
import Control.Monad.IO.Class (liftIO)
import System.Random (mkStdGen)
import Test.DejaFu (Condition(..), gives, gives',
isUncaughtException, withSetup,
withSetupAndTeardown)
isUncaughtException)
import Control.Concurrent.Classy hiding (newQSemN, signalQSemN,
waitQSemN)

View File

@ -2,7 +2,6 @@ module Integration.Names where
import Control.Concurrent.Classy hiding (check)
import Data.Maybe (mapMaybe)
import Test.DejaFu.Conc (ConcIO)
import Test.DejaFu.Internal (iorefOf, mvarOf, simplifyAction,
tidsOf, tvarsOf)
import Test.DejaFu.SCT (runSCT)

View File

@ -2,7 +2,6 @@ module Integration.Refinement where
import Control.Concurrent.Classy.MVar
import Control.Monad (void)
import Test.DejaFu.Conc (ConcIO)
import Test.DejaFu.Refinement
import Test.Tasty.DejaFu (testProperty)

View File

@ -7,6 +7,19 @@ standard Haskell versioning scheme.
.. _PVP: https://pvp.haskell.org/
2.4.0.2 (2021-03-14)
--------------------
* Git: :tag:`dejafu-2.4.0.2`
* Hackage: :hackage:`dejafu-2.4.0.2`
Fixed
~~~~~
* (:issue:`334`) Compilation error under GHC 9 due to use of
``const``.
2.4.0.1 (2020-12-28)
--------------------

View File

@ -6,7 +6,7 @@
-- |
-- Module : Test.DejaFu.Conc.Internal
-- Copyright : (c) 2016--2020 Michael Walker
-- Copyright : (c) 2016--2021 Michael Walker
-- License : MIT
-- Maintainer : Michael Walker <mike@barrucadu.co.uk>
-- Stability : experimental
@ -81,7 +81,7 @@ runConcurrency invariants forSnapshot sched memtype g idsrc caps ma = do
, cCState = initialCState
}
(c, ref) <- runRefCont AStop (Just . Right) (runModelConc ma)
let threads0 = launch' Unmasked initialThread (const c) (cThreads ctx)
let threads0 = launch' Unmasked initialThread (\_ -> c) (cThreads ctx)
threads <- case forkBoundThread of
Just fbt -> makeBound fbt initialThread threads0
Nothing -> pure threads0
@ -100,7 +100,7 @@ runConcurrencyWithSnapshot :: (MonadDejaFu n, HasCallStack)
runConcurrencyWithSnapshot sched memtype ctx restore ma = do
(c, ref) <- runRefCont AStop (Just . Right) (runModelConc ma)
let threads0 = M.delete initialThread (cThreads ctx)
let threads1 = launch' Unmasked initialThread (const c) threads0
let threads1 = launch' Unmasked initialThread (\_ -> c) threads0
threads <- case forkBoundThread of
Just fbt -> do
let boundThreads = M.filter (isJust . _bound) threads1

View File

@ -12,7 +12,7 @@
-- |
-- Module : Test.DejaFu.Conc.Internal.Program
-- Copyright : (c) 2019 Michael Walker
-- Copyright : (c) 2019--2021 Michael Walker
-- License : MIT
-- Maintainer : Michael Walker <mike@barrucadu.co.uk>
-- Stability : experimental
@ -141,7 +141,7 @@ instance (pty ~ Basic, Monad n) => C.MonadConc (Program pty n) where
getMaskingState = ModelConc (\c -> AGetMasking c)
unsafeUnmask ma = ModelConc (AMasking Unmasked (const ma))
unsafeUnmask ma = ModelConc (AMasking Unmasked (\_ -> ma))
-- ----------
@ -259,7 +259,7 @@ recordSnapshot
:: MonadDejaFu n
=> Program pty n a
-> n (Maybe (Either Condition (Snapshot pty n a), Trace))
recordSnapshot ModelConc{..} = pure Nothing
recordSnapshot ModelConc{} = pure Nothing
recordSnapshot WithSetup{..} =
let mkSnapshot snap _ = WS snap
in defaultRecordSnapshot mkSnapshot wsSetup wsProgram

View File

@ -7,7 +7,7 @@
-- |
-- Module : Test.DejaFu.Refinement
-- Copyright : (c) 2017--2018 Michael Walker
-- Copyright : (c) 2017--2021 Michael Walker
-- License : MIT
-- Maintainer : Michael Walker <mike@barrucadu.co.uk>
-- Stability : experimental
@ -109,6 +109,7 @@ module Test.DejaFu.Refinement
import Control.Arrow (first)
import Control.Monad.Conc.Class (fork)
import Data.Kind (Type)
import Data.Maybe (isNothing)
import Data.Set (Set)
import qualified Data.Set as S
@ -236,11 +237,11 @@ strictlyRefines = RP Strict
class Testable a where
-- | The observation value type. This is used to compare the
-- results.
type O a :: *
type O a :: Type
-- | The seed value type. This is used to construct the concurrent
-- states.
type X a :: *
type X a :: Type
rpropTiers :: a -> [[([String], RefinementProperty (O a) (X a))]]

View File

@ -8,7 +8,7 @@
-- |
-- Module : Test.DejaFu.Types
-- Copyright : (c) 2017--2020 Michael Walker
-- Copyright : (c) 2017--2021 Michael Walker
-- License : MIT
-- Maintainer : Michael Walker <mike@barrucadu.co.uk>
-- Stability : experimental
@ -31,6 +31,7 @@ import Data.Function (on)
import Data.Functor.Contravariant (Contravariant(..))
import Data.Functor.Contravariant.Divisible (Divisible(..))
import qualified Data.IORef as IO
import Data.Kind (Type)
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as M
import Data.Semigroup (Semigroup(..))
@ -60,7 +61,7 @@ class MonadThrow m => MonadDejaFu m where
-- These references are always used from the same Haskell thread, so
-- it's safe to implement these using unsynchronised primitives with
-- relaxed-memory behaviours (like @IORef@s).
type Ref m :: * -> *
type Ref m :: Type -> Type
-- | Create a new reference holding a given initial value.
newRef :: a -> m (Ref m a)
@ -74,7 +75,7 @@ class MonadThrow m => MonadDejaFu m where
-- | A handle to a bound thread. If the monad doesn't support bound
-- threads (for example, if it's not based on @IO@), then this
-- should be some type which can't be constructed, like 'V1'.
type BoundThread m :: * -> *
type BoundThread m :: Type -> Type
-- | Fork a new bound thread, if the monad supports them.
forkBoundThread :: Maybe (m (BoundThread m a))

View File

@ -2,7 +2,7 @@
-- documentation, see http://haskell.org/cabal/users-guide/
name: dejafu
version: 2.4.0.1
version: 2.4.0.2
synopsis: A library for unit-testing concurrent programs.
description:
@ -33,7 +33,7 @@ source-repository head
source-repository this
type: git
location: https://github.com/barrucadu/dejafu.git
tag: dejafu-2.4.0.1
tag: dejafu-2.4.0.2
library
exposed-modules: Test.DejaFu

View File

@ -27,8 +27,8 @@ There are a few different packages under the Déjà Fu umbrella:
.. csv-table::
:header: "Package", "Version", "Summary"
":hackage:`concurrency`", "1.11.0.0", "Typeclasses, functions, and data types for concurrency and STM"
":hackage:`dejafu`", "2.4.0.1", "Systematic testing for Haskell concurrency"
":hackage:`concurrency`", "1.11.0.1", "Typeclasses, functions, and data types for concurrency and STM"
":hackage:`dejafu`", "2.4.0.2", "Systematic testing for Haskell concurrency"
":hackage:`hunit-dejafu`", "2.0.0.4", "Déjà Fu support for the HUnit test framework"
":hackage:`tasty-dejafu`", "2.0.0.7", "Déjà Fu support for the tasty test framework"

View File

@ -8,6 +8,7 @@ currently supported versions are:
.. csv-table::
:header: "GHC", "Stackage", "base"
"9.0", "", "4.14.0.0"
"8.8", "LTS 15.0", "4.13.0.0"
"8.6", "LTS 13.0", "4.12.0.0"
"8.4", "LTS 12.0", "4.11.0.0"