mirror of
https://github.com/barrucadu/dejafu.git
synced 2024-11-23 22:23:18 +03:00
Drop support for GHC<7.10.
This also drops the use of CPP to avoid import warnings, which was a horrible practice I should never have adopted anyway.
This commit is contained in:
parent
11dec5243a
commit
50e2868cc2
@ -1,4 +1,3 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE RankNTypes #-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
@ -56,11 +55,6 @@ import qualified Control.Monad.Writer.Lazy as WL
|
||||
import qualified Control.Monad.Writer.Strict as WS
|
||||
import qualified Data.Atomics as A
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Control.Applicative (Applicative)
|
||||
import Data.Monoid (Monoid, mempty)
|
||||
#endif
|
||||
|
||||
-- | @MonadConc@ is an abstraction over GHC's typical concurrency
|
||||
-- abstraction. It captures the interface of concurrency monads in
|
||||
-- terms of how they can operate on shared state and in the presence
|
||||
|
@ -1,4 +1,3 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
|
||||
-- | This module provides an abstraction over 'STM', which can be used
|
||||
@ -21,11 +20,6 @@ import qualified Control.Monad.State.Strict as SS
|
||||
import qualified Control.Monad.Writer.Lazy as WL
|
||||
import qualified Control.Monad.Writer.Strict as WS
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Control.Applicative (Applicative)
|
||||
import Data.Monoid (Monoid)
|
||||
#endif
|
||||
|
||||
-- | @MonadSTM@ is an abstraction over 'STM'.
|
||||
--
|
||||
-- This class does not provide any way to run transactions, rather
|
||||
|
@ -1,19 +1,9 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
-- | Extra list functions and list-like types.
|
||||
module Data.List.Extra where
|
||||
|
||||
import Control.DeepSeq (NFData(..))
|
||||
import Data.Traversable (fmapDefault, foldMapDefault)
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Control.Applicative ((<$>), (<*>))
|
||||
import Data.Foldable (Foldable(..))
|
||||
import Data.Traversable (Traversable(..))
|
||||
#else
|
||||
-- Why does this give a redundancy warning? It's necessary in order to
|
||||
-- define the toList function in the Foldable instance for NonEmpty!
|
||||
import Data.Foldable (toList)
|
||||
#endif
|
||||
import Data.Traversable (fmapDefault, foldMapDefault)
|
||||
|
||||
-- * Regular lists
|
||||
|
||||
@ -38,10 +28,7 @@ instance Functor NonEmpty where
|
||||
instance Foldable NonEmpty where
|
||||
foldMap = foldMapDefault
|
||||
|
||||
#if __GLASGOW_HASKELL__ >= 710
|
||||
-- toList isn't in Foldable until GHC 7.10
|
||||
toList (a :| as) = a : as
|
||||
#endif
|
||||
|
||||
instance Traversable NonEmpty where
|
||||
traverse f (a:|as) = (:|) <$> f a <*> traverse f as
|
||||
@ -51,7 +38,7 @@ instance NFData a => NFData (NonEmpty a) where
|
||||
|
||||
-- | Convert a 'NonEmpty' to a regular non-empty list.
|
||||
toList :: NonEmpty a -> [a]
|
||||
toList (a :| as) = a : as
|
||||
toList = Data.Foldable.toList
|
||||
|
||||
-- | Convert a regular non-empty list to a 'NonEmpty'. This is
|
||||
-- necessarily partial.
|
||||
|
@ -1,4 +1,3 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE RankNTypes #-}
|
||||
|
||||
-- | Deterministic testing for concurrent computations.
|
||||
@ -231,16 +230,10 @@ import Control.Monad (when, unless)
|
||||
import Data.Function (on)
|
||||
import Data.List (intercalate, intersperse, minimumBy)
|
||||
import Data.List.Extra
|
||||
import Data.Monoid ((<>))
|
||||
import Data.Ord (comparing)
|
||||
import Test.DejaFu.Deterministic
|
||||
import Test.DejaFu.SCT
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Control.Applicative ((<$>))
|
||||
import Data.Foldable (Foldable(..))
|
||||
#endif
|
||||
|
||||
-- | The default memory model: @TotalStoreOrder@
|
||||
defaultMemType :: MemType
|
||||
defaultMemType = TotalStoreOrder
|
||||
|
@ -1,4 +1,3 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||
{-# LANGUAGE RankNTypes #-}
|
||||
@ -55,10 +54,6 @@ import qualified Control.Monad.Catch as Ca
|
||||
import qualified Control.Monad.Conc.Class as C
|
||||
import qualified Control.Monad.IO.Class as IO
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Control.Applicative (Applicative(..), (<$>))
|
||||
#endif
|
||||
|
||||
{-# ANN module ("HLint: ignore Avoid lambda" :: String) #-}
|
||||
{-# ANN module ("HLint: ignore Use const" :: String) #-}
|
||||
|
||||
|
@ -1,4 +1,3 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE RankNTypes #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
|
||||
@ -70,10 +69,6 @@ import Test.DejaFu.Deterministic.Internal.Threading
|
||||
|
||||
import qualified Data.Map.Strict as M
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Control.Applicative ((<$>), (<*>))
|
||||
#endif
|
||||
|
||||
{-# ANN module ("HLint: ignore Use record patterns" :: String) #-}
|
||||
{-# ANN module ("HLint: ignore Use const" :: String) #-}
|
||||
|
||||
|
@ -1,4 +1,3 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE ExistentialQuantification #-}
|
||||
{-# LANGUAGE RankNTypes #-}
|
||||
|
||||
@ -14,9 +13,7 @@ import Data.List (sort, nub, intercalate)
|
||||
import Data.List.Extra
|
||||
import Test.DejaFu.Internal
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Control.Applicative (Applicative(..))
|
||||
#endif
|
||||
import Prelude
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
-- * The @Conc@ Monad
|
||||
|
@ -1,5 +1,4 @@
|
||||
{-# LANGUAGE BangPatterns #-}
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE GADTs #-}
|
||||
|
||||
-- | Operations over @CRef@s and @CVar@s
|
||||
@ -17,11 +16,6 @@ import Test.DejaFu.Internal
|
||||
import qualified Data.IntMap.Strict as I
|
||||
import qualified Data.Map.Strict as M
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Data.Foldable (mapM_)
|
||||
import Prelude hiding (mapM_)
|
||||
#endif
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
-- * Manipulating @CRef@s
|
||||
|
||||
|
@ -1,4 +1,3 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE ExistentialQuantification #-}
|
||||
{-# LANGUAGE RankNTypes #-}
|
||||
|
||||
@ -13,10 +12,6 @@ import Test.DejaFu.Deterministic.Internal.Common
|
||||
|
||||
import qualified Data.Map.Strict as M
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Control.Applicative ((<$>))
|
||||
#endif
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
-- * Threads
|
||||
|
||||
|
@ -1,4 +1,3 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||
{-# LANGUAGE RankNTypes #-}
|
||||
|
||||
@ -121,10 +120,6 @@ import qualified Data.Map.Strict as M
|
||||
import qualified Data.Sequence as Sq
|
||||
import qualified Data.Set as S
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Control.Applicative ((<$>), (<*>))
|
||||
#endif
|
||||
|
||||
-- | A bounding function takes the scheduling decisions so far and a
|
||||
-- decision chosen to come next, and returns if that decision is
|
||||
-- within the bound.
|
||||
|
@ -1,5 +1,3 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
|
||||
-- | Internal utilities and types for BPOR.
|
||||
module Test.DejaFu.SCT.Internal where
|
||||
|
||||
@ -17,10 +15,6 @@ import qualified Data.Map.Strict as M
|
||||
import qualified Data.Sequence as Sq
|
||||
import qualified Data.Set as S
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Control.Applicative ((<$>), (<*>))
|
||||
#endif
|
||||
|
||||
-- * BPOR state
|
||||
|
||||
-- | One step of the execution, including information for backtracking
|
||||
|
@ -1,4 +1,3 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||
{-# LANGUAGE RankNTypes #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
@ -32,10 +31,6 @@ import Test.DejaFu.STM.Internal
|
||||
|
||||
import qualified Control.Monad.STM.Class as C
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Control.Applicative (Applicative)
|
||||
#endif
|
||||
|
||||
{-# ANN module ("HLint: ignore Use record patterns" :: String) #-}
|
||||
|
||||
newtype STMLike n r a = S { runSTM :: M n r a } deriving (Functor, Applicative, Monad)
|
||||
|
@ -1,4 +1,3 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE ExistentialQuantification #-}
|
||||
{-# LANGUAGE RankNTypes #-}
|
||||
|
||||
@ -11,13 +10,8 @@ import Control.Monad.Cont (Cont, runCont)
|
||||
import Data.List (nub)
|
||||
import Data.Maybe (fromMaybe)
|
||||
import Data.Typeable (cast)
|
||||
import Test.DejaFu.Internal
|
||||
import Test.DejaFu.Deterministic.Internal.Common (CTVarId, IdSource, TAction(..), TTrace, nextCTVId)
|
||||
|
||||
#if __GLASGOW_HASKELL__ < 710
|
||||
import Data.Foldable (Foldable(..))
|
||||
import Data.Monoid (mempty)
|
||||
#endif
|
||||
import Test.DejaFu.Internal
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
-- The @STMLike@ monad
|
||||
|
@ -7,8 +7,6 @@ packages:
|
||||
- dejafu
|
||||
- dejafu-tests
|
||||
|
||||
extra-deps:
|
||||
# Needed for building with lts-2
|
||||
- atomic-primops-0.8.0.2
|
||||
extra-deps: []
|
||||
|
||||
resolver: lts-4.2
|
||||
resolver: lts-5.5
|
||||
|
Loading…
Reference in New Issue
Block a user