Add Applicative constraint to classes for pre-AMP GHC

This commit is contained in:
Michael Walker 2015-08-14 15:20:03 +01:00
parent 0e558b271f
commit 4a76ecedcc
2 changed files with 5 additions and 2 deletions

View File

@ -12,6 +12,7 @@ module Control.Monad.Conc.Class
, killThread
) where
import Control.Applicative (Applicative)
import Control.Concurrent (forkIO)
import Control.Concurrent.MVar (MVar, readMVar, newEmptyMVar, putMVar, tryPutMVar, takeMVar, tryTakeMVar)
import Control.Exception (Exception, AsyncException(ThreadKilled), SomeException)
@ -51,7 +52,8 @@ import qualified Control.Monad.Writer.Strict as WS
--
-- Every @MonadConc@ has an associated 'MonadSTM', transactions of
-- which can be run atomically.
class ( Monad m, MonadCatch m, MonadThrow m, MonadMask m
class ( Applicative m, Monad m
, MonadCatch m, MonadThrow m, MonadMask m
, MonadSTM (STMLike m)
, Eq (ThreadId m), Show (ThreadId m)) => MonadConc m where
-- | The associated 'MonadSTM' for this class.

View File

@ -4,6 +4,7 @@
-- with 'MonadConc'.
module Control.Monad.STM.Class where
import Control.Applicative (Applicative)
import Control.Concurrent.STM (STM)
import Control.Concurrent.STM.TVar (TVar, newTVar, readTVar, writeTVar)
import Control.Exception (Exception)
@ -30,7 +31,7 @@ import qualified Control.Monad.Writer.Strict as WS
--
-- A minimal implementation consists of 'retry', 'orElse', 'newCTVar',
-- 'readCTVar', and 'writeCTVar'.
class (Monad m, MonadCatch m, MonadThrow m) => MonadSTM m where
class (Applicative m, Monad m, MonadCatch m, MonadThrow m) => MonadSTM m where
-- | The mutable reference type. These behave like 'TVar's, in that
-- they always contain a value and updates are non-blocking and
-- synchronised.