File: State.hs

package info (click to toggle)
haskell-lifted-async 0.10.2.6-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 140 kB
  • sloc: haskell: 1,177; makefile: 2
file content (167 lines) | stat: -rw-r--r-- 4,915 bytes parent folder | download
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
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
{-# LANGUAGE TemplateHaskell #-}
module Test.Async.State
  ( stateTestGroup
  ) where
import Control.Monad (void, when)
import Control.Monad.State (runStateT, get, modify, liftIO)
import Data.Maybe (isJust, isNothing)

import Control.Concurrent.Lifted
import Control.Exception.Lifted as E
import Test.Tasty.ExpectedFailure

import Control.Concurrent.Async.Lifted
import Test.Async.Common

stateTestGroup :: TestTree
stateTestGroup = $(testGroupGenerator)

case_async_waitCatch :: Assertion
case_async_waitCatch = do
  (r, s) <- flip runStateT value $ do
    a <- async $ modify (+1) >> return value
    waitCatch a
  case r of
    Left _  -> assertFailure "An exception must not be raised."
    Right e -> do
      e @?= value
      s @?= value + 1

case_async_wait :: Assertion
case_async_wait = do
  (r, s) <- flip runStateT value $ do
    a <- async $ modify (+1) >> return value
    wait a
  r @?= value
  s @?= value + 1

case_async_exwaitCatch :: Assertion
case_async_exwaitCatch = do
  (r, s) <- flip runStateT value $ do
    a <- async $ modify (+1) >> throwIO TestException
    waitCatch a
  case r of
    Left e  -> do
      fromException e @?= Just TestException
      s @?= value
    Right _ -> assertFailure "An exception must be raised."

case_async_exwait :: Assertion
case_async_exwait =
  void $ flip runStateT value $ do
    a <- async $ modify (+1) >> throwIO TestException
    (wait a >> liftIO (assertFailure "An exception must be raised"))
      `E.catch` \e -> do
        liftIO $ e @?= TestException
        s <- get
        liftIO $ s @?= value

case_withAsync_waitCatch :: Assertion
case_withAsync_waitCatch =
  void $ flip runStateT value $ do
    withAsync (modify (+1) >> return value) $ \a -> do
      r <- waitCatch a
      case r of
        Left _  -> liftIO $ assertFailure "An exception must not be raised."
        Right e -> do
          liftIO $ e @?= value
          s <- get
          liftIO $ s @?= value + 1

case_withAsync_wait2 :: Assertion
case_withAsync_wait2 = do
  (r, s) <- flip runStateT value $ do
    a <- withAsync (modify (+1) >> threadDelay 1000000) $ return
    waitCatch a
  case r of
    Left e  -> do
      fromException e @?= Just AsyncCancelled
      s @?= value
    Right _ -> assertFailure "An exception must be raised."

case_async_cancel :: Assertion
case_async_cancel = sequence_ $ replicate 1000 run
  where
    run = do
      (r, s) <- flip runStateT value $ do
        a <- async $ modify (+1) >> return value
        cancelWith a TestException
        waitCatch a
      case r of
        Left e -> do
          fromException e @?= Just TestException
          s @?= value
        Right r' -> do
          r' @?= value
          s @?= value + 1

case_async_poll :: Assertion
case_async_poll =
  void $ flip runStateT value $ do
    a <- async (threadDelay 1000000)
    r <- poll a
    when (isJust r) $
      liftIO $ assertFailure "The result must be nothing."
    r' <- poll a   -- poll twice, just to check we don't deadlock
    when (isJust r') $
      liftIO $ assertFailure "The result must be Nothing."

case_async_poll2 :: Assertion
case_async_poll2 =
  void $ flip runStateT value $ do
    a <- async (return value)
    void $ wait a
    r <- poll a
    when (isNothing r) $
      liftIO $ assertFailure "The result must not be Nothing."
    r' <- poll a   -- poll twice, just to check we don't deadlock
    when (isNothing r') $
      liftIO $ assertFailure "The result must not be Nothing."

case_withAsync_waitEither :: Assertion
case_withAsync_waitEither = do
  (_, s) <- flip runStateT value $ do
    withAsync (modify (+1)) $ \a ->
      waitEither a a
  liftIO $ s @?= value + 1

case_withAsync_waitEither_ :: Assertion
case_withAsync_waitEither_ = do
  ((), s) <- flip runStateT value $ do
    withAsync (modify (+1)) $ \a ->
      waitEither_ a a
  liftIO $ s @?= value

case_withAsync_waitBoth1 :: Assertion
case_withAsync_waitBoth1 = do
  (_, s) <- flip runStateT value $ do
    withAsync (return value) $ \a ->
      withAsync (modify (+1)) $ \b ->
        waitBoth a b
  liftIO $ s @?= value + 1

case_withAsync_waitBoth2 :: Assertion
case_withAsync_waitBoth2 = do
  (_, s) <- flip runStateT value $ do
    withAsync (modify (+1)) $ \a ->
      withAsync (return value) $ \b ->
        waitBoth a b
  liftIO $ s @?= value

test_ignored :: [TestTree]
test_ignored =
  [ ignoreTestBecause "see #26" $ testCase "link" $ do
    r <- try $ flip runStateT value $ do
      a <- async $ threadDelay 1000000 >> return value
      link a
      cancelWith a TestException
      wait a
    case r of
      Left e -> case fromException e of
        Just (ExceptionInLinkedThread _ e') ->
          fromException e' @?= Just TestException
        Nothing -> assertFailure $
          "expected ExceptionInLinkedThread _ TestException"
            ++ " but got " ++ show e
      Right _ -> assertFailure "An exception must be raised."
  ]