Merge branch '0.2-compat'

This commit is contained in:
Michael Walker 2016-04-28 23:02:49 +01:00
commit 6757a2a857
5 changed files with 41 additions and 5 deletions

View File

@ -83,12 +83,41 @@ import Control.Monad
import Control.Monad.Catch (finally, try, onException)
import Control.Monad.Conc.Class
import Control.Monad.STM.Class
#if MIN_VERSION_dejafu(0,3,0)
import Control.Concurrent.Classy.STM.TMVar (newEmptyTMVar, putTMVar, readTMVar)
#else
import Control.Concurrent.STM.CTMVar (CTMVar, newEmptyCTMVar, putCTMVar, readCTMVar)
#endif
#if !MIN_VERSION_base(4,8,0)
import Data.Traversable
#endif
#if !MIN_VERSION_dejafu(0,3,0)
type MVar m = CVar m
newEmptyMVar :: MonadConc m => m (MVar m a)
newEmptyMVar = newEmptyCVar
putMVar :: MonadConc m => MVar m a -> a -> m ()
putMVar = putCVar
takeMVar :: MonadConc m => MVar m a -> m a
takeMVar = takeCVar
type STM m = STMLike m
type TMVar m = CTMVar m
newEmptyTMVar :: MonadSTM stm => stm (TMVar stm a)
newEmptyTMVar = newEmptyCTMVar
putTMVar :: MonadSTM stm => TMVar stm a -> a -> stm ()
putTMVar = putCTMVar
readTMVar :: MonadSTM stm => TMVar stm a -> stm a
readTMVar = readCTMVar
#endif
-----------------------------------------------------------------------------------------
-- Asynchronous and Concurrent Actions

View File

@ -44,7 +44,7 @@ library
-- other-modules:
-- other-extensions:
build-depends: base >=4.5 && <5
, dejafu == 0.3.*
, dejafu >= 0.2
, exceptions
-- hs-source-dirs:
default-language: Haskell2010

View File

@ -40,7 +40,7 @@ library
-- other-modules:
-- other-extensions:
build-depends: base >=4.5 && <5
, dejafu == 0.3.*
, dejafu >= 0.2
, HUnit
-- hs-source-dirs:
default-language: Haskell2010

View File

@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
@ -146,12 +147,18 @@ testDejafusIO' = testio
--------------------------------------------------------------------------------
-- Tasty integration
#if MIN_VERSION_dejafu(0,3,0)
type Trc = Trace ThreadId ThreadAction Lookahead
#else
type Trc = Trace
#endif
data ConcTest where
ConcTest :: Show a => [(Either Failure a, Trace ThreadId ThreadAction Lookahead)] -> Predicate a -> ConcTest
ConcTest :: Show a => [(Either Failure a, Trc)] -> Predicate a -> ConcTest
deriving Typeable
data ConcIOTest where
ConcIOTest :: Show a => IO [(Either Failure a, Trace ThreadId ThreadAction Lookahead)] -> Predicate a -> ConcIOTest
ConcIOTest :: Show a => IO [(Either Failure a, Trc)] -> Predicate a -> ConcIOTest
deriving Typeable
instance IsTest ConcTest where

View File

@ -40,7 +40,7 @@ library
-- other-modules:
-- other-extensions:
build-depends: base >=4.5 && <5
, dejafu == 0.3.*
, dejafu >= 0.2
, tasty
-- hs-source-dirs:
default-language: Haskell2010