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 (99 lines) | stat: -rw-r--r-- 2,774 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
{-# LANGUAGE CPP
           , NoImplicitPrelude
           , ScopedTypeVariables
  #-}

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

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

-- from base:
import Prelude            ( (*) )
import Control.Concurrent ( forkIO )
import Control.Monad      ( return, (>>=), (>>) )
import Data.Bool          ( Bool(False, True), not, (&&) )
import Data.Function      ( ($), (.) )
import Data.Functor       ( fmap )
import Data.IORef         ( newIORef, writeIORef, readIORef )

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

-- from concurrent-extra:
import qualified Control.Concurrent.Lock as Lock
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 Lock
-------------------------------------------------------------------------------

tests :: [Test]
tests = [ testCase "acquire release"    test_lock_1
        , testCase "acquire acquire"    test_lock_2
        , testCase "new release"        test_lock_3
        , testCase "new unlocked"       test_lock_4
        , testCase "newAcquired locked" test_lock_5
        , testCase "acq rel unlocked"   test_lock_6
        , testCase "conc release"       test_lock_7
        , testCase "wait"               test_lock_8
        ]

test_lock_1 :: Assertion
test_lock_1 = assert $ within a_moment $ do
  l <- Lock.new
  Lock.acquire l
  Lock.release l

test_lock_2 :: Assertion
test_lock_2 = assert $ notWithin (10 * a_moment) $ do
  l <- Lock.new
  Lock.acquire l
  Lock.acquire l

test_lock_3 :: Assertion
test_lock_3 = assertException "" $ Lock.new >>= Lock.release

test_lock_4 :: Assertion
test_lock_4 = assert $ Lock.new >>= fmap not . Lock.locked

test_lock_5 :: Assertion
test_lock_5 = assert $ Lock.newAcquired >>= Lock.locked

test_lock_6 :: Assertion
test_lock_6 = assert $ do
  l <- Lock.new
  Lock.acquire l
  Lock.release l
  fmap not $ Lock.locked l

test_lock_7 :: Assertion
test_lock_7 = assert . within (1000 * a_moment) $ do
  l <- Lock.newAcquired
  _ <- forkIO $ wait_a_moment >> Lock.release l
  Lock.acquire l

test_lock_8 :: Assertion
test_lock_8 = assert $ do
  ioRef <- newIORef False
  l <- Lock.newAcquired
  _ <- forkIO $ do wait_a_moment
                   writeIORef ioRef True
                   Lock.release l
  Lock.wait l
  set <- readIORef ioRef
  locked <- Lock.locked l
  return $ set && not locked