Skip to content

Commit 2d70794

Browse files
committed
MonadSTM: split into submodules
Follow a similar module structure as the "stm" package.
1 parent 43f77b4 commit 2d70794

File tree

17 files changed

+1960
-1755
lines changed

17 files changed

+1960
-1755
lines changed

io-classes/io-classes.cabal

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -37,6 +37,15 @@ library
3737
Control.Monad.Class.MonadSay
3838
Control.Monad.Class.MonadST
3939
Control.Monad.Class.MonadSTM
40+
Control.Concurrent.Class.MonadSTM
41+
Control.Concurrent.Class.MonadSTM.TArray
42+
Control.Concurrent.Class.MonadSTM.TBQueue
43+
Control.Concurrent.Class.MonadSTM.TChan
44+
Control.Concurrent.Class.MonadSTM.TMVar
45+
Control.Concurrent.Class.MonadSTM.TQueue
46+
Control.Concurrent.Class.MonadSTM.TSem
47+
Control.Concurrent.Class.MonadSTM.TVar
48+
Control.Monad.Class.MonadSTM.Internal
4049
Control.Monad.Class.MonadThrow
4150
Control.Monad.Class.MonadTime
4251
Control.Monad.Class.MonadTimer
Lines changed: 14 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,14 @@
1+
-- | This module corresponds to `Control.Concurrent.STM` in "stm" package
2+
--
3+
module Control.Concurrent.Class.MonadSTM
4+
(module STM)
5+
where
6+
7+
import Control.Monad.Class.MonadSTM as STM
8+
import Control.Concurrent.Class.MonadSTM.TVar as STM
9+
import Control.Concurrent.Class.MonadSTM.TMVar as STM
10+
import Control.Concurrent.Class.MonadSTM.TChan as STM
11+
import Control.Concurrent.Class.MonadSTM.TQueue as STM
12+
import Control.Concurrent.Class.MonadSTM.TBQueue as STM
13+
import Control.Concurrent.Class.MonadSTM.TArray as STM
14+
Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,7 @@
1+
{-# LANGUAGE ExplicitNamespaces #-}
2+
3+
-- | This module corresponds to `Control.Concurrent.STM.TArray` in "stm" package
4+
--
5+
module Control.Concurrent.Class.MonadSTM.TArray (type TArray) where
6+
7+
import Control.Monad.Class.MonadSTM.Internal
Lines changed: 28 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,28 @@
1+
{-# LANGUAGE ExplicitNamespaces #-}
2+
3+
-- | This module corresponds to `Control.Concurrent.STM.TVar` in "stm" package
4+
--
5+
module Control.Concurrent.Class.MonadSTM.TBQueue
6+
( -- * MonadSTM
7+
type TBQueue
8+
, newTBQueue
9+
, newTBQueueIO
10+
, readTBQueue
11+
, tryReadTBQueue
12+
, peekTBQueue
13+
, tryPeekTBQueue
14+
, flushTBQueue
15+
, writeTBQueue
16+
, lengthTBQueue
17+
, isEmptyTBQueue
18+
, isFullTBQueue
19+
, unGetTBQueue
20+
-- * MonadLabelledSTM
21+
, labelTBQueue
22+
, labelTBQueueIO
23+
-- * MonadTraceSTM
24+
, traceTBQueue
25+
, traceTBQueueIO
26+
) where
27+
28+
import Control.Monad.Class.MonadSTM.Internal
Lines changed: 26 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,26 @@
1+
{-# LANGUAGE ExplicitNamespaces #-}
2+
3+
-- | This module corresponds to `Control.Concurrent.STM.TChan` in "stm" package
4+
--
5+
module Control.Concurrent.Class.MonadSTM.TChan
6+
( -- * MonadSTM
7+
-- ** TChans
8+
type TChan
9+
-- * Construction
10+
, newTChan
11+
, newBroadcastTChan
12+
, newTChanIO
13+
, newBroadcastTChanIO
14+
, dupTChan
15+
, cloneTChan
16+
-- ** Reading and writing
17+
, readTChan
18+
, tryReadTChan
19+
, peekTChan
20+
, tryPeekTChan
21+
, writeTChan
22+
, unGetTChan
23+
, isEmptyTChan
24+
) where
25+
26+
import Control.Monad.Class.MonadSTM.Internal
Lines changed: 26 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,26 @@
1+
{-# LANGUAGE ExplicitNamespaces #-}
2+
3+
-- | This module corresponds to `Control.Concurrent.STM.TMVar` in "stm" package
4+
--
5+
module Control.Concurrent.Class.MonadSTM.TMVar
6+
( -- * MonadSTM
7+
type TMVar
8+
, newTMVar
9+
, newEmptyTMVar
10+
, takeTMVar
11+
, tryTakeTMVar
12+
, putTMVar
13+
, tryPutTMVar
14+
, readTMVar
15+
, tryReadTMVar
16+
, swapTMVar
17+
, isEmptyTMVar
18+
-- * MonadLabelledSTM
19+
, labelTMVar
20+
, labelTMVarIO
21+
-- * MonadTraceSTM
22+
, traceTMVar
23+
, traceTMVarIO
24+
) where
25+
26+
import Control.Monad.Class.MonadSTM.Internal
Lines changed: 25 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,25 @@
1+
{-# LANGUAGE ExplicitNamespaces #-}
2+
3+
-- | This module corresponds to `Control.Concurrnet.STM.TVar` in "stm" package
4+
--
5+
module Control.Concurrent.Class.MonadSTM.TQueue
6+
( -- * MonadSTM
7+
type TQueue
8+
, newTQueue
9+
, newTQueueIO
10+
, readTQueue
11+
, tryReadTQueue
12+
, peekTQueue
13+
, tryPeekTQueue
14+
, writeTQueue
15+
, unGetTQueue
16+
, isEmptyTQueue
17+
-- * MonadLabelledSTM
18+
, labelTQueue
19+
, labelTQueueIO
20+
-- * MonadTraceSTM
21+
, traceTQueue
22+
, traceTQueueIO
23+
) where
24+
25+
import Control.Monad.Class.MonadSTM.Internal
Lines changed: 20 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,20 @@
1+
{-# LANGUAGE ExplicitNamespaces #-}
2+
3+
-- | This module corresponds to `Control.Concurrent.STM.TSem` in "stm" package
4+
--
5+
module Control.Concurrent.Class.MonadSTM.TSem
6+
( -- * MonadSTM
7+
type TSem
8+
, newTSem
9+
, waitTSem
10+
, signalTSem
11+
, signalTSemN
12+
-- * MonadLabelledSTM
13+
, labelTSem
14+
, labelTSemIO
15+
-- * MonadTraceSTM
16+
, traceTSem
17+
, traceTSemIO
18+
) where
19+
20+
import Control.Monad.Class.MonadSTM.Internal
Lines changed: 26 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,26 @@
1+
{-# LANGUAGE ExplicitNamespaces #-}
2+
3+
-- | This module corresponds to `Control.Concurrent.STM.TVar` in "stm" package
4+
--
5+
module Control.Concurrent.Class.MonadSTM.TVar
6+
( -- * MonadSTM
7+
type TVar
8+
, newTVar
9+
, newTVarIO
10+
, readTVar
11+
, readTVarIO
12+
, writeTVar
13+
, modifyTVar
14+
, modifyTVar'
15+
, stateTVar
16+
, swapTVar
17+
, check
18+
-- * MonadLabelSTM
19+
, labelTVar
20+
, labelTVarIO
21+
-- * MonadTraceSTM
22+
, traceTVar
23+
, traceTVarIO
24+
) where
25+
26+
import Control.Monad.Class.MonadSTM.Internal

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

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -16,6 +16,7 @@ module Control.Monad.Class.MonadMVar
1616
, isEmptyMVarDefault
1717
) where
1818

19+
import Control.Concurrent.Class.MonadSTM.TVar
1920
import qualified Control.Concurrent.MVar as IO
2021
import Control.Exception (SomeAsyncException (..))
2122
import Control.Monad.Class.MonadSTM

0 commit comments

Comments
 (0)