Skip to content

Commit 39fab44

Browse files
committed
Change naming for the use case of qualified imports, added module comments
1 parent 4711a73 commit 39fab44

File tree

3 files changed

+69
-28
lines changed

3 files changed

+69
-28
lines changed

src/Control/Concurrent/Async/Timer.hs

+18-5
Original file line numberDiff line numberDiff line change
@@ -1,11 +1,24 @@
1+
{-|
2+
Module : Control.Concurrent.Async.Timer
3+
Description : Public API for asynchronous Timers
4+
Copyright : (c) Moritz Clasmeier 2016, 2018
5+
License : BSD3
6+
Maintainer : [email protected]
7+
Stability : experimental
8+
Portability : POSIX
9+
10+
This module exports the public API for asynchronous timers.
11+
-}
12+
113
module Control.Concurrent.Async.Timer
214
( Timer
3-
, defaultTimerConf
4-
, timerConfSetInitDelay
5-
, timerConfSetInterval
15+
, TimerConf
16+
, defaultConf
17+
, setInitDelay
18+
, setInterval
619
, withAsyncTimer
7-
, timerWait
8-
, timerReset
20+
, wait
21+
, reset
922
) where
1023

1124
import Control.Concurrent.Async.Timer.Internal

src/Control/Concurrent/Async/Timer/Internal.hs

+39-13
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,16 @@
1+
{-|
2+
Module : Control.Concurrent.Async.Timer.Internal
3+
Description : Implementation of asynchronous Timers
4+
Copyright : (c) Moritz Clasmeier 2016, 2018
5+
License : BSD3
6+
Maintainer : [email protected]
7+
Stability : experimental
8+
Portability : POSIX
9+
10+
This module contains the internal implementation of asynchronous
11+
timers.
12+
-}
13+
114
{-# LANGUAGE LambdaCase #-}
215

316
module Control.Concurrent.Async.Timer.Internal where
@@ -17,6 +30,8 @@ import UnliftIO.STM
1730
data Timer = Timer { timerMVar :: MVar ()
1831
, timerControl :: TBQueue TimerCommand }
1932

33+
-- | Timer commands that can be sent over a timer control channel to
34+
-- an asynchronous timer.
2035
data TimerCommand = TimerReset deriving (Show, Eq)
2136

2237
-- | Type of a timer configuration.
@@ -25,24 +40,29 @@ data TimerConf = TimerConf { _timerConfInitDelay :: Int
2540

2641
-- | Sleep 'dt' milliseconds.
2742
millisleep :: MonadIO m => Int -> m ()
28-
millisleep dt = threadDelay (fromIntegral dt * 10 ^ 3)
43+
millisleep dt = threadDelay (dt * 10 ^ 3)
2944

3045
-- | Default timer configuration specifies no initial delay and an
3146
-- interval delay of 1s.
32-
defaultTimerConf :: TimerConf
33-
defaultTimerConf = TimerConf { _timerConfInitDelay = 0
34-
, _timerConfInterval = 1000 }
47+
defaultConf :: TimerConf
48+
defaultConf = TimerConf { _timerConfInitDelay = 0
49+
, _timerConfInterval = 1000 }
3550

3651
-- | Set the initial delay in the provided timer configuration.
37-
timerConfSetInitDelay :: Int -> TimerConf -> TimerConf
38-
timerConfSetInitDelay n conf = conf { _timerConfInitDelay = n }
52+
setInitDelay :: Int -> TimerConf -> TimerConf
53+
setInitDelay n conf = conf { _timerConfInitDelay = n }
3954

4055
-- | Set the interval delay in the provided timer configuration.
41-
timerConfSetInterval :: Int -> TimerConf -> TimerConf
42-
timerConfSetInterval n conf = conf { _timerConfInterval = n }
56+
setInterval :: Int -> TimerConf -> TimerConf
57+
setInterval n conf = conf { _timerConfInterval = n }
4358

4459
-- | Timer loop to be executed within in a timer thread.
45-
timerLoop :: MonadUnliftIO m => Int -> Int -> Timer -> m ()
60+
timerLoop
61+
:: MonadUnliftIO m
62+
=> Int
63+
-> Int
64+
-> Timer
65+
-> m ()
4666
timerLoop initDelay intervalDelay timer = go initDelay
4767

4868
where go delay = do
@@ -59,12 +79,18 @@ timerLoop initDelay intervalDelay timer = go initDelay
5979
readCmd = atomically $ readTBQueue (timerControl timer)
6080

6181
-- | Wait for the next synchronization event on the givem timer.
62-
timerWait :: MonadUnliftIO m => Timer -> m ()
63-
timerWait = void . takeMVar . timerMVar
82+
wait
83+
:: MonadUnliftIO m
84+
=> Timer
85+
-> m ()
86+
wait = void . takeMVar . timerMVar
6487

6588
-- | Reset the provided timer.
66-
timerReset :: MonadUnliftIO m => Timer -> m ()
67-
timerReset timer =
89+
reset
90+
:: MonadUnliftIO m
91+
=> Timer
92+
-> m ()
93+
reset timer =
6894
atomically $ writeTBQueue (timerControl timer) TimerReset
6995

7096
-- | Spawn a timer thread based on the provided timer configuration

test/Spec.hs

+12-10
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@ module Main where
22

33
import Control.Concurrent
44
import Control.Concurrent.Async
5-
import Control.Concurrent.Async.Timer
5+
import qualified Control.Concurrent.Async.Timer as Timer
66
import Control.Exception
77
import Control.Monad
88
import Criterion.Measurement
@@ -39,19 +39,20 @@ timedAssert delay before after = do
3939

4040
testTimerReset :: IO ()
4141
testTimerReset = do
42-
let conf = defaultTimerConf & timerConfSetInitDelay 1000
43-
& timerConfSetInterval 1000 -- ms
42+
let conf = Timer.defaultConf
43+
& Timer.setInitDelay 1000
44+
& Timer.setInterval 1000 -- ms
4445
noOfTicks = 3
4546

4647
counter <- newIORef 0
4748

4849
_handle <- async $
49-
withAsyncTimer conf $ \ timer ->
50+
Timer.withAsyncTimer conf $ \ timer ->
5051
forM_ [1..noOfTicks] $ \ idx -> do
5152
when (idx == 2) $ do
5253
threadDelay (5 * 10^5)
53-
timerReset timer
54-
timerWait timer
54+
Timer.reset timer
55+
Timer.wait timer
5556
modifyIORef counter (+ 1)
5657

5758
timedAssert (2 * 10^6 + 5 * 10^5)
@@ -60,16 +61,17 @@ testTimerReset = do
6061

6162
testSimpleTimerTicks :: IO ()
6263
testSimpleTimerTicks = do
63-
let conf = defaultTimerConf & timerConfSetInitDelay 0
64-
& timerConfSetInterval 1000 -- ms
64+
let conf = Timer.defaultConf
65+
& Timer.setInitDelay 0
66+
& Timer.setInterval 1000 -- ms
6567
noOfTicks = 3
6668

6769
counter <- newIORef 0
6870
times <- newIORef []
6971

70-
withAsyncTimer conf $ \ timer ->
72+
Timer.withAsyncTimer conf $ \ timer ->
7173
forM_ [1..noOfTicks] $ \_ -> do
72-
timerWait timer
74+
Timer.wait timer
7375
void $ forkIO $ myAction counter times
7476

7577
threadDelay (5 * 10^5)

0 commit comments

Comments
 (0)