Skip to content

Commit

Permalink
Merge pull request #106 from input-output-hk/jdral/monadinspectmvar
Browse files Browse the repository at this point in the history
New `MonadInspectMVar` class
  • Loading branch information
coot committed Jun 2, 2023
2 parents dccf0a7 + 9c4ef3f commit cb65e93
Show file tree
Hide file tree
Showing 4 changed files with 46 additions and 3 deletions.
9 changes: 9 additions & 0 deletions io-classes/CHANGELOG.md
@@ -1,5 +1,14 @@
# Revsion history of io-classes

## next version

### Non-breaking changes

* Add new `MonadInspectMVar` class with an `inspectMVar` function for accessing
an `MVar` in an underlying monad (if applicable). This is mainly useful for
`io-sim`, since the underlying monad is `ST`. `IO` has no underlying monad, so
the provided instance for `IO` defaults `inspectMVar` to `tryReadMVar`.

## 1.1.0.0

### Breaking changes
Expand Down
26 changes: 23 additions & 3 deletions io-classes/src/Control/Concurrent/Class/MonadMVar.hs
@@ -1,9 +1,12 @@
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE TypeFamilyDependencies #-}
{-# LANGUAGE TypeOperators #-}

module Control.Concurrent.Class.MonadMVar (MonadMVar (..)) where
module Control.Concurrent.Class.MonadMVar
( MonadMVar (..)
, MonadInspectMVar (..)
) where

import qualified Control.Concurrent.MVar as IO
import Control.Monad.Class.MonadThrow
Expand Down Expand Up @@ -127,6 +130,9 @@ class Monad m => MonadMVar m where
return b
{-# INLINE modifyMVarMasked #-}

--
-- IO instance
--

instance MonadMVar IO where
type MVar IO = IO.MVar
Expand Down Expand Up @@ -181,8 +187,22 @@ instance ( MonadMask m
modifyMVarMasked (WrappedMVar v) f = ReaderT $ \r ->
modifyMVarMasked v (\a -> runReaderT (f a) r)

--
-- MonadInspectMVar
--


-- | This type class is intended for
-- ['io-sim'](https://hackage.haskell.org/package/io-sim), where one might want
-- to access an 'MVar' in the underlying 'ST' monad.
class (MonadMVar m, Monad (InspectMVarMonad m)) => MonadInspectMVar m where
type InspectMVarMonad m :: Type -> Type
-- | Return the value of an 'MVar' as an 'InspectMVarMonad' computation. Can
-- be 'Nothing' if the 'MVar' is empty.
inspectMVar :: proxy m -> MVar m a -> InspectMVarMonad m (Maybe a)

instance MonadInspectMVar IO where
type InspectMVarMonad IO = IO
inspectMVar _ = tryReadMVar

--
-- Utilities
Expand Down
6 changes: 6 additions & 0 deletions io-sim/CHANGELOG.md
@@ -1,5 +1,11 @@
# Revsion history of io-sim

## next version

### Non breaking changes

* Provide `MonadInspectMVar` instance for `IOSim`.

## 1.1.0.0

### Non breaking changes
Expand Down
8 changes: 8 additions & 0 deletions io-sim/src/Control/Monad/IOSim/Types.hs
Expand Up @@ -567,6 +567,14 @@ instance MonadMVar (IOSim s) where
tryReadMVar = tryReadMVarDefault
isEmptyMVar = isEmptyMVarDefault

instance MonadInspectMVar (IOSim s) where
type InspectMVarMonad (IOSim s) = ST s
inspectMVar p (MVar tvar) = do
st <- inspectTVar p tvar
case st of
MVarEmpty _ _ -> pure Nothing
MVarFull x _ -> pure (Just x)

data Async s a = Async !ThreadId (STM s (Either SomeException a))

instance Eq (Async s a) where
Expand Down

0 comments on commit cb65e93

Please sign in to comment.