File: Test.hs

package info (click to toggle)
haskell-concurrent-extra 0.7.0.12-4
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 184 kB
  • sloc: haskell: 1,040; makefile: 6
file content (106 lines) | stat: -rw-r--r-- 3,191 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
{-# LANGUAGE CPP, NoImplicitPrelude, ScopedTypeVariables #-}

module Control.Concurrent.Event.Test ( tests ) where

-------------------------------------------------------------------------------
-- Imports
-------------------------------------------------------------------------------

-- from base:
import Control.Exception  ( catch, throwTo, ErrorCall(..) )
import Control.Concurrent ( forkIO )
import Control.Monad      ( return, mapM_, replicateM, replicateM_ )
import Data.Function      ( ($) )
import Data.Int           ( Int )
import Data.Bool          ( not )
import Prelude            ( toInteger, (*) )

#if __GLASGOW_HASKELL__ < 700
import Prelude            ( fromInteger )
import Control.Monad      ( (>>=), (>>), fail )
#endif

-- from concurrent-extra:
import qualified Control.Concurrent.Event as Event
import TestUtils

-- from HUnit:
import Test.HUnit ( Assertion, assert )

-- from test-framework:
import Test.Framework  ( Test )

-- from test-framework-hunit:
import Test.Framework.Providers.HUnit ( testCase )


-------------------------------------------------------------------------------
-- Tests for Event
-------------------------------------------------------------------------------

tests :: [Test]
tests = [ testCase "set wait a"    $ test_event_1 1 1
        , testCase "set wait b"    $ test_event_1 5 1
        , testCase "set wait c"    $ test_event_1 1 5
        , testCase "set wait d"    $ test_event_1 5 5
        , testCase "conc set wait" $ test_event_2
        , testCase "multi wake"    $ test_event_3 10
        , testCase "exception"     $ test_event_4
        , testCase "wait timeout"  $ test_event_5
        , testCase "wait blocks"   $ test_event_6
        ]

-- Set an event 's' times then wait for it 'w' times. This should
-- terminate within a few moments.
test_event_1 :: Int -> Int -> Assertion
test_event_1 s w = assert $ within (10 * a_moment) $ do
  e <- Event.new
  replicateM_ s $ Event.set  e
  replicateM_ w $ Event.wait e

test_event_2 :: Assertion
test_event_2 = assert $ within (10 * a_moment) $ do
  e1 <- Event.new
  e2 <- Event.new
  _ <- forkIO $ do
    Event.wait e1
    Event.set  e2
  wait_a_moment
  Event.set  e1
  Event.wait e2

-- Waking multiple threads with a single Event.
test_event_3 :: Int -> Assertion
test_event_3 n = assert $ within (10 * a_moment) $ do
  e1 <- Event.new
  es <- replicateM n $ do
    e2 <- Event.new
    _ <- forkIO $ do
      Event.wait e1
      Event.set  e2
    return e2
  wait_a_moment
  Event.set e1
  mapM_ Event.wait es

-- Exception handling while waiting for an Event.
test_event_4 :: Assertion
test_event_4 = assert $ within (10 * a_moment) $ do
  e1 <- Event.new
  e2 <- Event.new
  helperId <- forkIO $ Event.wait e1 `catch` \(_ :: ErrorCall) ->
                                                 Event.set e2
  wait_a_moment
  throwTo helperId $ ErrorCall "Boo!"
  Event.wait e2

test_event_5 :: Assertion
test_event_5 = assert $ within (10 * a_moment) $ do
  e <- Event.new
  notTimedOut <- Event.waitTimeout e $ toInteger a_moment
  return $ not notTimedOut

test_event_6 :: Assertion
test_event_6 = assert $ notWithin (10 * a_moment) $ do
  e <- Event.new
  Event.wait e