mirror of
https://github.com/barrucadu/dejafu.git
synced 2024-11-27 13:39:16 +03:00
Fix new hlint warnings
This commit is contained in:
parent
7aa407df47
commit
a0801d65eb
@ -17,7 +17,7 @@ import Control.Exception (Exception, MaskingState(..),
|
||||
SomeException, fromException)
|
||||
import Data.List (intersect)
|
||||
import Data.Map.Strict (Map)
|
||||
import Data.Maybe (fromMaybe, isJust)
|
||||
import Data.Maybe (isJust)
|
||||
|
||||
import Test.DejaFu.Common
|
||||
import Test.DejaFu.Conc.Internal.Common
|
||||
@ -117,7 +117,7 @@ goto a = M.adjust $ \thread -> thread { _continuation = a }
|
||||
-- from the parent thread. This ID must not already be in use!
|
||||
launch :: ThreadId -> ThreadId -> ((forall b. M n r b -> M n r b) -> Action n r) -> Threads n r -> Threads n r
|
||||
launch parent tid a threads = launch' ms tid a threads where
|
||||
ms = fromMaybe Unmasked $ _masking <$> M.lookup parent threads
|
||||
ms = maybe Unmasked _masking (M.lookup parent threads)
|
||||
|
||||
-- | Start a thread with the given ID and masking state. This must not already be in use!
|
||||
launch' :: MaskingState -> ThreadId -> ((forall b. M n r b -> M n r b) -> Action n r) -> Threads n r -> Threads n r
|
||||
|
@ -1,6 +1,7 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE LambdaCase #-}
|
||||
{-# LANGUAGE RankNTypes #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
{-# LANGUAGE TypeSynonymInstances #-}
|
||||
@ -17,7 +18,7 @@
|
||||
-- License : MIT
|
||||
-- Maintainer : Michael Walker <mike@barrucadu.co.uk>
|
||||
-- Stability : stable
|
||||
-- Portability : CPP, FlexibleContexts, FlexibleInstances, ImpredicativeTypes, RankNTypes, ScopedTypeVariables, TypeSynonymInstances
|
||||
-- Portability : CPP, FlexibleContexts, FlexibleInstances, ImpredicativeTypes, LambdaCase, RankNTypes, ScopedTypeVariables, TypeSynonymInstances
|
||||
--
|
||||
-- This module allows using Deja Fu predicates with HUnit to test the
|
||||
-- behaviour of concurrent systems.
|
||||
@ -139,7 +140,7 @@ instance Assertable (Conc.ConcIO ()) where
|
||||
assertString . showErr $ assertableP traces
|
||||
|
||||
assertableP :: Predicate (Either HUnitFailure ())
|
||||
assertableP = alwaysTrue $ \r -> case r of
|
||||
assertableP = alwaysTrue $ \case
|
||||
Right (Left HUnitFailure {}) -> False
|
||||
_ -> True
|
||||
|
||||
|
@ -2,6 +2,7 @@
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE GADTs #-}
|
||||
{-# LANGUAGE LambdaCase #-}
|
||||
{-# LANGUAGE RankNTypes #-}
|
||||
{-# LANGUAGE TypeSynonymInstances #-}
|
||||
|
||||
@ -17,7 +18,7 @@
|
||||
-- License : MIT
|
||||
-- Maintainer : Michael Walker <mike@barrucadu.co.uk>
|
||||
-- Stability : stable
|
||||
-- Portability : CPP, FlexibleContexts, FlexibleInstances, GADTs, ImpredicativeTypes, RankNTypes, TypeSynonymInstances
|
||||
-- Portability : CPP, FlexibleContexts, FlexibleInstances, GADTs, ImpredicativeTypes, LambdaCase, RankNTypes, TypeSynonymInstances
|
||||
--
|
||||
-- This module allows using Deja Fu predicates with Tasty to test the
|
||||
-- behaviour of concurrent systems.
|
||||
@ -143,7 +144,7 @@ concOptions =
|
||||
]
|
||||
|
||||
assertableP :: Predicate (Maybe String)
|
||||
assertableP = alwaysTrue $ \r -> case r of
|
||||
assertableP = alwaysTrue $ \case
|
||||
Right (Just _) -> False
|
||||
_ -> True
|
||||
|
||||
|
Loading…
Reference in New Issue
Block a user