Skip to content

Commit cb65e93

Browse files
authored
Merge pull request #106 from input-output-hk/jdral/monadinspectmvar
New `MonadInspectMVar` class
2 parents dccf0a7 + 9c4ef3f commit cb65e93

File tree

4 files changed

+46
-3
lines changed

4 files changed

+46
-3
lines changed

io-classes/CHANGELOG.md

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,14 @@
11
# Revsion history of io-classes
22

3+
## next version
4+
5+
### Non-breaking changes
6+
7+
* Add new `MonadInspectMVar` class with an `inspectMVar` function for accessing
8+
an `MVar` in an underlying monad (if applicable). This is mainly useful for
9+
`io-sim`, since the underlying monad is `ST`. `IO` has no underlying monad, so
10+
the provided instance for `IO` defaults `inspectMVar` to `tryReadMVar`.
11+
312
## 1.1.0.0
413

514
### Breaking changes

io-classes/src/Control/Concurrent/Class/MonadMVar.hs

Lines changed: 23 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,12 @@
11
{-# LANGUAGE DefaultSignatures #-}
2+
{-# LANGUAGE FlexibleContexts #-}
23
{-# LANGUAGE QuantifiedConstraints #-}
34
{-# LANGUAGE TypeFamilyDependencies #-}
4-
{-# LANGUAGE TypeOperators #-}
55

6-
module Control.Concurrent.Class.MonadMVar (MonadMVar (..)) where
6+
module Control.Concurrent.Class.MonadMVar
7+
( MonadMVar (..)
8+
, MonadInspectMVar (..)
9+
) where
710

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

133+
--
134+
-- IO instance
135+
--
130136

131137
instance MonadMVar IO where
132138
type MVar IO = IO.MVar
@@ -181,8 +187,22 @@ instance ( MonadMask m
181187
modifyMVarMasked (WrappedMVar v) f = ReaderT $ \r ->
182188
modifyMVarMasked v (\a -> runReaderT (f a) r)
183189

190+
--
191+
-- MonadInspectMVar
192+
--
184193

185-
194+
-- | This type class is intended for
195+
-- ['io-sim'](https://hackage.haskell.org/package/io-sim), where one might want
196+
-- to access an 'MVar' in the underlying 'ST' monad.
197+
class (MonadMVar m, Monad (InspectMVarMonad m)) => MonadInspectMVar m where
198+
type InspectMVarMonad m :: Type -> Type
199+
-- | Return the value of an 'MVar' as an 'InspectMVarMonad' computation. Can
200+
-- be 'Nothing' if the 'MVar' is empty.
201+
inspectMVar :: proxy m -> MVar m a -> InspectMVarMonad m (Maybe a)
202+
203+
instance MonadInspectMVar IO where
204+
type InspectMVarMonad IO = IO
205+
inspectMVar _ = tryReadMVar
186206

187207
--
188208
-- Utilities

io-sim/CHANGELOG.md

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,11 @@
11
# Revsion history of io-sim
22

3+
## next version
4+
5+
### Non breaking changes
6+
7+
* Provide `MonadInspectMVar` instance for `IOSim`.
8+
39
## 1.1.0.0
410

511
### Non breaking changes

io-sim/src/Control/Monad/IOSim/Types.hs

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -567,6 +567,14 @@ instance MonadMVar (IOSim s) where
567567
tryReadMVar = tryReadMVarDefault
568568
isEmptyMVar = isEmptyMVarDefault
569569

570+
instance MonadInspectMVar (IOSim s) where
571+
type InspectMVarMonad (IOSim s) = ST s
572+
inspectMVar p (MVar tvar) = do
573+
st <- inspectTVar p tvar
574+
case st of
575+
MVarEmpty _ _ -> pure Nothing
576+
MVarFull x _ -> pure (Just x)
577+
570578
data Async s a = Async !ThreadId (STM s (Either SomeException a))
571579

572580
instance Eq (Async s a) where

0 commit comments

Comments
 (0)