@@ -3,7 +3,7 @@ module Test.Main where
33import Prelude
44
55import Control.Alt ((<|>))
6- import Control.Monad.Aff (Aff , runAff , makeAff , launchAff , later , later' , forkAff , forkAll , Canceler (..), cancel , attempt , finally , apathize )
6+ import Control.Monad.Aff (Aff , runAff , makeAff , launchAff , delay , forkAff , forkAll , Canceler (..), cancel , attempt , finally , apathize )
77import Control.Monad.Aff.AVar (AVAR , makeVar , makeVar' , putVar , modifyVar , takeVar , peekVar , killVar )
88import Control.Monad.Aff.Console (CONSOLE , log )
99import Control.Monad.Eff (Eff )
@@ -14,16 +14,17 @@ import Control.Monad.Rec.Class (Step(..), tailRecM)
1414import Control.Parallel (parallel , sequential )
1515import Data.Either (either , fromLeft , fromRight )
1616import Data.Maybe (Maybe (..))
17+ import Data.Time.Duration (Milliseconds (..))
1718import Data.Unfoldable (replicate )
1819import Partial.Unsafe (unsafePartial )
1920
2021type Test a = forall e . Aff (console :: CONSOLE | e ) a
2122type TestAVar a = forall e . Aff (console :: CONSOLE , avar :: AVAR | e ) a
2223
23- timeout :: Int → TestAVar Unit → TestAVar Unit
24+ timeout :: Milliseconds → TestAVar Unit → TestAVar Unit
2425timeout ms aff = do
2526 exn <- makeVar
26- clr1 <- forkAff (later' ms ( putVar exn (Just " Timed out" ) ))
27+ clr1 <- forkAff (delay ms *> putVar exn (Just " Timed out" ))
2728 clr2 <- forkAff (aff *> putVar exn Nothing )
2829 res ← takeVar exn
2930 log (show res)
@@ -37,7 +38,8 @@ replicateArray = replicate
3738test_sequencing :: Int -> Test Unit
3839test_sequencing 0 = log " Done"
3940test_sequencing n = do
40- later' 100 (log (show (n / 10 ) <> " seconds left" ))
41+ delay $ Milliseconds 100.0
42+ log (show (n / 10 ) <> " seconds left" )
4143 test_sequencing (n - 1 )
4244
4345foreign import synchronousUnexpectedThrowError :: forall e . Eff e Unit
@@ -75,30 +77,30 @@ test_apathize = do
7577test_putTakeVar :: TestAVar Unit
7678test_putTakeVar = do
7779 v <- makeVar
78- _ <- forkAff (later $ putVar v 1.0 )
80+ _ <- forkAff (delay ( Milliseconds 0.0 ) *> putVar v 1.0 )
7981 a <- takeVar v
8082 log (" Success: Value " <> show a)
8183
8284test_peekVar :: TestAVar Unit
8385test_peekVar = do
84- timeout 1000 do
86+ timeout ( Milliseconds 1000.0 ) do
8587 v <- makeVar
86- _ <- forkAff (later $ putVar v 1.0 )
88+ _ <- forkAff (delay ( Milliseconds 0.0 ) *> putVar v 1.0 )
8789 a1 <- peekVar v
8890 a2 <- takeVar v
8991 when (a1 /= a2) do
9092 throwError (error " Something horrible went wrong - peeked var is not equal to taken var" )
9193 log (" Success: Peeked value not consumed" )
9294
93- timeout 1000 do
95+ timeout ( Milliseconds 1000.0 ) do
9496 w <- makeVar
9597 putVar w true
9698 b <- peekVar w
9799 when (not b) do
98100 throwError (error " Something horrible went wrong - peeked var is not true" )
99101 log (" Success: Peeked value read from written var" )
100102
101- timeout 1000 do
103+ timeout ( Milliseconds 1000.0 ) do
102104 x <- makeVar
103105 res <- makeVar' 1
104106 _ <- forkAff do
@@ -116,7 +118,7 @@ test_peekVar = do
116118
117119test_killFirstForked :: Test Unit
118120test_killFirstForked = do
119- c <- forkAff (later' 100 $ pure " Failure: This should have been killed!" )
121+ c <- forkAff (delay ( Milliseconds 100.0 ) $> " Failure: This should have been killed!" )
120122 b <- c `cancel` (error " Just die" )
121123 log (if b then " Success: Killed first forked" else " Failure: Couldn't kill first forked" )
122124
@@ -144,8 +146,8 @@ test_finally = do
144146
145147test_parRace :: TestAVar Unit
146148test_parRace = do
147- s <- sequential (parallel (later' 100 $ pure " Success: Early bird got the worm" ) <|>
148- parallel (later' 200 $ pure " Failure: Late bird got the worm" ))
149+ s <- sequential (parallel (delay ( Milliseconds 100.0 ) $> " Success: Early bird got the worm" ) <|>
150+ parallel (delay ( Milliseconds 200.0 ) $> " Failure: Late bird got the worm" ))
149151 log s
150152
151153test_parError :: TestAVar Unit
@@ -155,14 +157,14 @@ test_parError = do
155157
156158test_parRaceKill1 :: TestAVar Unit
157159test_parRaceKill1 = do
158- s <- sequential (parallel (later' 100 $ throwError (error (" Oh noes!" ))) <|>
159- parallel (later' 200 $ pure " Success: Early error was ignored in favor of late success" ))
160+ s <- sequential (parallel (delay ( Milliseconds 100.0 ) *> throwError (error (" Oh noes!" ))) <|>
161+ parallel (delay ( Milliseconds 200.0 ) $> " Success: Early error was ignored in favor of late success" ))
160162 log s
161163
162164test_parRaceKill2 :: TestAVar Unit
163165test_parRaceKill2 = do
164- e <- attempt $ sequential (parallel (later' 100 $ throwError (error (" Oh noes!" ))) <|>
165- parallel (later' 200 $ throwError (error (" Oh noes!" ))))
166+ e <- attempt $ sequential (parallel (delay ( Milliseconds 100.0 ) *> throwError (error (" Oh noes!" ))) <|>
167+ parallel (delay ( Milliseconds 200.0 ) *> throwError (error (" Oh noes!" ))))
166168 either (const $ log " Success: Killing both kills it dead" ) (const $ log " Failure: It's alive!!!" ) e
167169
168170test_semigroupCanceler :: Test Unit
@@ -174,30 +176,32 @@ test_semigroupCanceler =
174176 log (if v then " Success: Canceled semigroup composite canceler"
175177 else " Failure: Could not cancel semigroup composite canceler" )
176178
177- test_cancelLater :: TestAVar Unit
178- test_cancelLater = do
179- c <- forkAff $ (do _ <- pure " Binding"
180- _ <- later' 100 $ log (" Failure: Later was not canceled!" )
181- pure " Binding" )
179+ test_cancelDelay :: TestAVar Unit
180+ test_cancelDelay = do
181+ c <- forkAff do
182+ _ <- pure " Binding"
183+ delay (Milliseconds 100.0 )
184+ log $ " Failure: Delay was not canceled!"
185+ pure " Binding"
182186 v <- cancel c (error " Cause" )
183- log (if v then " Success: Canceled later " else " Failure: Did not cancel later " )
187+ log (if v then " Success: Canceled delay " else " Failure: Did not cancel delay " )
184188
185- test_cancelLaunchLater :: forall e . Eff (console :: CONSOLE , exception :: EXCEPTION | e ) Unit
186- test_cancelLaunchLater = do
187- c <- launchAff $ later' 100 $ log (" Failure: Later was not canceled!" )
189+ test_cancelLaunchDelay :: forall e . Eff (console :: CONSOLE , exception :: EXCEPTION | e ) Unit
190+ test_cancelLaunchDelay = do
191+ c <- launchAff $ delay ( Milliseconds 100.0 ) *> log (" Failure: Delay was not canceled!" )
188192 void $ launchAff $ (do v <- cancel c (error " Cause" )
189- log (if v then " Success: Canceled later " else " Failure: Did not cancel later " ))
193+ log (if v then " Success: Canceled delay " else " Failure: Did not cancel delay " ))
190194
191- test_cancelRunLater :: forall e . Eff (console :: CONSOLE | e ) Unit
192- test_cancelRunLater = do
193- c <- runAff (const (pure unit)) (const (pure unit)) $ later' 100 $ log (" Failure: Later was not canceled!" )
195+ test_cancelRunDelay :: forall e . Eff (console :: CONSOLE | e ) Unit
196+ test_cancelRunDelay = do
197+ c <- runAff (const (pure unit)) (const (pure unit)) $ delay ( Milliseconds 100.0 ) *> log (" Failure: Delay was not canceled!" )
194198 void $ try $ launchAff $ (do v <- cancel c (error " Cause" )
195- log (if v then " Success: Canceled later " else " Failure: Did not cancel later " ))
199+ log (if v then " Success: Canceled delay " else " Failure: Did not cancel delay " ))
196200
197201test_cancelParallel :: TestAVar Unit
198202test_cancelParallel = do
199- c <- forkAff <<< sequential $ parallel (later' 100 $ log " Failure: #1 should not get through" ) <|>
200- parallel (later' 100 $ log " Failure: #2 should not get through" )
203+ c <- forkAff <<< sequential $ parallel (delay ( Milliseconds 100.0 ) *> log " Failure: #1 should not get through" ) <|>
204+ parallel (delay ( Milliseconds 100.0 ) *> log " Failure: #2 should not get through" )
201205 v <- c `cancel` (error " Must cancel" )
202206 log (if v then " Success: Canceling composite of two Parallel succeeded"
203207 else " Failure: Canceling composite of two Parallel failed" )
@@ -206,19 +210,21 @@ test_cancelRaceLeft :: TestAVar Unit
206210test_cancelRaceLeft = do
207211 var <- makeVar
208212 c <- sequential
209- $ parallel (later' 250 $ putVar var true )
210- <|> parallel (later' 100 $ pure unit)
211- later' 500 $ putVar var false
213+ $ parallel (delay (Milliseconds 250.0 ) *> putVar var true )
214+ <|> parallel (delay (Milliseconds 100.0 ))
215+ delay (Milliseconds 500.0 )
216+ putVar var false
212217 l <- takeVar var
213218 when l $ throwError (error " Failure: left side ran even though it lost the race" )
214219
215220test_cancelRaceRight :: TestAVar Unit
216221test_cancelRaceRight = do
217222 var <- makeVar
218223 c <- sequential
219- $ parallel (later' 100 $ pure unit)
220- <|> parallel (later' 250 $ putVar var true )
221- later' 500 $ putVar var false
224+ $ parallel (delay (Milliseconds 100.0 ))
225+ <|> parallel (delay (Milliseconds 250.0 ) *> putVar var true )
226+ delay (Milliseconds 500.0 )
227+ putVar var false
222228 l <- takeVar var
223229 when l $ throwError (error " Failure: right side ran even though it lost the race" )
224230
@@ -242,7 +248,7 @@ loopAndBounce n = do
242248 where
243249 go 0 = pure (Done 0 )
244250 go k | mod k 30000 == 0 = do
245- later' 10 (pure unit )
251+ delay ( Milliseconds 10.0 )
246252 pure (Loop (k - 1 ))
247253 go k = pure (Loop (k - 1 ))
248254
@@ -255,20 +261,17 @@ all n = do
255261
256262cancelAll :: forall eff . Int -> Aff (console :: CONSOLE , avar :: AVAR | eff ) Unit
257263cancelAll n = do
258- canceler <- forkAll $ replicateArray n (later' 100000 ( log " oops" ) )
264+ canceler <- forkAll $ replicateArray n (delay ( Milliseconds 100000.0 ) *> log " oops" )
259265 canceled <- cancel canceler (error " bye" )
260266 log (" Cancelled all: " <> show canceled)
261267
262- delay :: forall eff . Int -> Aff eff Unit
263- delay n = later' n (pure unit)
264-
265268main :: Eff (console :: CONSOLE , avar :: AVAR , exception :: EXCEPTION ) Unit
266269main = do
267- Eff .log " Testing kill of later launched in separate Aff"
268- test_cancelLaunchLater
270+ Eff .log " Testing kill of delay launched in separate Aff"
271+ test_cancelLaunchDelay
269272
270- Eff .log " Testing kill of later run in separate Aff"
271- test_cancelRunLater
273+ Eff .log " Testing kill of delay run in separate Aff"
274+ test_cancelRunDelay
272275
273276 void $ runAff throwException (const (pure unit)) $ do
274277 log " Testing sequencing"
@@ -283,11 +286,12 @@ main = do
283286 log " Testing attempt"
284287 test_attempt
285288
286- log " Testing later"
287- later $ log " Success: It happened later"
289+ log " Testing delay"
290+ delay (Milliseconds 0.0 )
291+ log " Success: It happened later"
288292
289- log " Testing kill of later "
290- test_cancelLater
293+ log " Testing kill of delay "
294+ test_cancelDelay
291295
292296 log " Testing kill of first forked"
293297 test_killFirstForked
@@ -335,7 +339,7 @@ main = do
335339 test_syncTailRecM
336340
337341 log " pre-delay"
338- delay 1000
342+ delay ( Milliseconds 1000.0 )
339343 log " post-delay"
340344
341345 loopAndBounce 1000000
0 commit comments