Skip to content

Commit

Permalink
Replace later with delay
Browse files Browse the repository at this point in the history
  • Loading branch information
natefaubion committed Mar 28, 2017
1 parent 6da848d commit 1ed0d75
Show file tree
Hide file tree
Showing 4 changed files with 76 additions and 76 deletions.
3 changes: 2 additions & 1 deletion bower.json
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,8 @@
"purescript-functions": "^3.0.0",
"purescript-parallel": "^3.0.0",
"purescript-transformers": "^3.0.0",
"purescript-unsafe-coerce": "^3.0.0"
"purescript-unsafe-coerce": "^3.0.0",
"purescript-datetime": "^3.0.0"
},
"devDependencies": {
"purescript-partial": "^1.2.0"
Expand Down
24 changes: 12 additions & 12 deletions src/Control/Monad/Aff.js
Original file line number Diff line number Diff line change
Expand Up @@ -36,29 +36,29 @@ exports._cancelWith = function (nonCanceler, aff, canceler1) {
};
};

exports._setTimeout = function (nonCanceler, millis, aff) {
exports._delay = function (nonCanceler, millis) {
var set = setTimeout;
var clear = clearTimeout;
if (millis <= 0 && typeof setImmediate === "function") {
set = setImmediate;
clear = clearImmediate;
}
return function (success, error) {
var canceler;

var timeout = set(function () {
canceler = aff(success, error);
return function (success) {
var timedOut = false;
var timer = set(function () {
timedOut = true;
success();
}, millis);

return function (e) {
return function (s, f) {
if (canceler !== undefined) {
return canceler(e)(s, f);
return function () {
return function (s) {
if (timedOut) {
s(false);
} else {
clear(timeout);
clear(timer);
s(true);
return nonCanceler;
}
return nonCanceler;
};
};
};
Expand Down
17 changes: 6 additions & 11 deletions src/Control/Monad/Aff.purs
Original file line number Diff line number Diff line change
Expand Up @@ -9,8 +9,7 @@ module Control.Monad.Aff
, finally
, forkAff
, forkAll
, later
, later'
, delay
, launchAff
, liftEff'
, makeAff
Expand Down Expand Up @@ -39,6 +38,7 @@ import Data.Foldable (class Foldable, foldl)
import Data.Function.Uncurried (Fn2, Fn3, runFn2, runFn3)
import Data.Monoid (class Monoid, mempty)
import Data.Newtype (class Newtype)
import Data.Time.Duration (Milliseconds(..))
import Data.Tuple (Tuple(..), fst, snd)

import Unsafe.Coerce (unsafeCoerce)
Expand Down Expand Up @@ -108,14 +108,9 @@ makeAff h = makeAff' (\e a -> const nonCanceler <$> h e a)
makeAff' :: forall e a. ((Error -> Eff e Unit) -> (a -> Eff e Unit) -> Eff e (Canceler e)) -> Aff e a
makeAff' h = _makeAff h

-- | Runs the asynchronous computation off the current execution context.
later :: forall e a. Aff e a -> Aff e a
later = later' 0

-- | Runs the specified asynchronous computation later, by the specified
-- | number of milliseconds.
later' :: forall e a. Int -> Aff e a -> Aff e a
later' n aff = runFn3 _setTimeout nonCanceler n aff
-- | Pauses execuation of the current computation for the specified number of milliseconds.
delay :: forall e. Milliseconds -> Aff e Unit
delay (Milliseconds n) = runFn2 _delay nonCanceler n

-- | Compute `aff1`, followed by `aff2` regardless of whether `aff1` terminated successfully.
finally :: forall e a b. Aff e a -> Aff e b -> Aff e a
Expand Down Expand Up @@ -292,7 +287,7 @@ fromAVBox = unsafeCoerce

foreign import _cancelWith :: forall e a. Fn3 (Canceler e) (Aff e a) (Canceler e) (Aff e a)

foreign import _setTimeout :: forall e a. Fn3 (Canceler e) Int (Aff e a) (Aff e a)
foreign import _delay :: forall e a. Fn2 (Canceler e) Number (Aff e a)

foreign import _unsafeInterleaveAff :: forall e1 e2 a. Aff e1 a -> Aff e2 a

Expand Down
108 changes: 56 additions & 52 deletions test/Test/Main.purs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ module Test.Main where
import Prelude

import Control.Alt ((<|>))
import Control.Monad.Aff (Aff, runAff, makeAff, launchAff, later, later', forkAff, forkAll, Canceler(..), cancel, attempt, finally, apathize)
import Control.Monad.Aff (Aff, runAff, makeAff, launchAff, delay, forkAff, forkAll, Canceler(..), cancel, attempt, finally, apathize)
import Control.Monad.Aff.AVar (AVAR, makeVar, makeVar', putVar, modifyVar, takeVar, peekVar, killVar)
import Control.Monad.Aff.Console (CONSOLE, log)
import Control.Monad.Eff (Eff)
Expand All @@ -14,16 +14,17 @@ import Control.Monad.Rec.Class (Step(..), tailRecM)
import Control.Parallel (parallel, sequential)
import Data.Either (either, fromLeft, fromRight)
import Data.Maybe (Maybe(..))
import Data.Time.Duration (Milliseconds(..))
import Data.Unfoldable (replicate)
import Partial.Unsafe (unsafePartial)

type Test a = forall e. Aff (console :: CONSOLE | e) a
type TestAVar a = forall e. Aff (console :: CONSOLE, avar :: AVAR | e) a

timeout :: Int TestAVar Unit TestAVar Unit
timeout :: Milliseconds TestAVar Unit TestAVar Unit
timeout ms aff = do
exn <- makeVar
clr1 <- forkAff (later' ms (putVar exn (Just "Timed out")))
clr1 <- forkAff (delay ms *> putVar exn (Just "Timed out"))
clr2 <- forkAff (aff *> putVar exn Nothing)
res ← takeVar exn
log (show res)
Expand All @@ -37,7 +38,8 @@ replicateArray = replicate
test_sequencing :: Int -> Test Unit
test_sequencing 0 = log "Done"
test_sequencing n = do
later' 100 (log (show (n / 10) <> " seconds left"))
delay $ Milliseconds 100.0
log (show (n / 10) <> " seconds left")
test_sequencing (n - 1)

foreign import synchronousUnexpectedThrowError :: forall e. Eff e Unit
Expand Down Expand Up @@ -75,30 +77,30 @@ test_apathize = do
test_putTakeVar :: TestAVar Unit
test_putTakeVar = do
v <- makeVar
_ <- forkAff (later $ putVar v 1.0)
_ <- forkAff (delay (Milliseconds 0.0) *> putVar v 1.0)
a <- takeVar v
log ("Success: Value " <> show a)

test_peekVar :: TestAVar Unit
test_peekVar = do
timeout 1000 do
timeout (Milliseconds 1000.0) do
v <- makeVar
_ <- forkAff (later $ putVar v 1.0)
_ <- forkAff (delay (Milliseconds 0.0) *> putVar v 1.0)
a1 <- peekVar v
a2 <- takeVar v
when (a1 /= a2) do
throwError (error "Something horrible went wrong - peeked var is not equal to taken var")
log ("Success: Peeked value not consumed")

timeout 1000 do
timeout (Milliseconds 1000.0) do
w <- makeVar
putVar w true
b <- peekVar w
when (not b) do
throwError (error "Something horrible went wrong - peeked var is not true")
log ("Success: Peeked value read from written var")

timeout 1000 do
timeout (Milliseconds 1000.0) do
x <- makeVar
res <- makeVar' 1
_ <- forkAff do
Expand All @@ -116,7 +118,7 @@ test_peekVar = do

test_killFirstForked :: Test Unit
test_killFirstForked = do
c <- forkAff (later' 100 $ pure "Failure: This should have been killed!")
c <- forkAff (delay (Milliseconds 100.0) $> "Failure: This should have been killed!")
b <- c `cancel` (error "Just die")
log (if b then "Success: Killed first forked" else "Failure: Couldn't kill first forked")

Expand Down Expand Up @@ -144,8 +146,8 @@ test_finally = do

test_parRace :: TestAVar Unit
test_parRace = do
s <- sequential (parallel (later' 100 $ pure "Success: Early bird got the worm") <|>
parallel (later' 200 $ pure "Failure: Late bird got the worm"))
s <- sequential (parallel (delay (Milliseconds 100.0) $> "Success: Early bird got the worm") <|>
parallel (delay (Milliseconds 200.0) $> "Failure: Late bird got the worm"))
log s

test_parError :: TestAVar Unit
Expand All @@ -155,14 +157,14 @@ test_parError = do

test_parRaceKill1 :: TestAVar Unit
test_parRaceKill1 = do
s <- sequential (parallel (later' 100 $ throwError (error ("Oh noes!"))) <|>
parallel (later' 200 $ pure "Success: Early error was ignored in favor of late success"))
s <- sequential (parallel (delay (Milliseconds 100.0) *> throwError (error ("Oh noes!"))) <|>
parallel (delay (Milliseconds 200.0) $> "Success: Early error was ignored in favor of late success"))
log s

test_parRaceKill2 :: TestAVar Unit
test_parRaceKill2 = do
e <- attempt $ sequential (parallel (later' 100 $ throwError (error ("Oh noes!"))) <|>
parallel (later' 200 $ throwError (error ("Oh noes!"))))
e <- attempt $ sequential (parallel (delay (Milliseconds 100.0) *> throwError (error ("Oh noes!"))) <|>
parallel (delay (Milliseconds 200.0) *> throwError (error ("Oh noes!"))))
either (const $ log "Success: Killing both kills it dead") (const $ log "Failure: It's alive!!!") e

test_semigroupCanceler :: Test Unit
Expand All @@ -174,30 +176,32 @@ test_semigroupCanceler =
log (if v then "Success: Canceled semigroup composite canceler"
else "Failure: Could not cancel semigroup composite canceler")

test_cancelLater :: TestAVar Unit
test_cancelLater = do
c <- forkAff $ (do _ <- pure "Binding"
_ <- later' 100 $ log ("Failure: Later was not canceled!")
pure "Binding")
test_cancelDelay :: TestAVar Unit
test_cancelDelay = do
c <- forkAff do
_ <- pure "Binding"
delay (Milliseconds 100.0)
log $ "Failure: Delay was not canceled!"
pure "Binding"
v <- cancel c (error "Cause")
log (if v then "Success: Canceled later" else "Failure: Did not cancel later")
log (if v then "Success: Canceled delay" else "Failure: Did not cancel delay")

test_cancelLaunchLater :: forall e. Eff (console :: CONSOLE, exception :: EXCEPTION | e) Unit
test_cancelLaunchLater = do
c <- launchAff $ later' 100 $ log ("Failure: Later was not canceled!")
test_cancelLaunchDelay :: forall e. Eff (console :: CONSOLE, exception :: EXCEPTION | e) Unit
test_cancelLaunchDelay = do
c <- launchAff $ delay (Milliseconds 100.0) *> log ("Failure: Delay was not canceled!")
void $ launchAff $ (do v <- cancel c (error "Cause")
log (if v then "Success: Canceled later" else "Failure: Did not cancel later"))
log (if v then "Success: Canceled delay" else "Failure: Did not cancel delay"))

test_cancelRunLater :: forall e. Eff (console :: CONSOLE | e) Unit
test_cancelRunLater = do
c <- runAff (const (pure unit)) (const (pure unit)) $ later' 100 $ log ("Failure: Later was not canceled!")
test_cancelRunDelay :: forall e. Eff (console :: CONSOLE | e) Unit
test_cancelRunDelay = do
c <- runAff (const (pure unit)) (const (pure unit)) $ delay (Milliseconds 100.0) *> log ("Failure: Delay was not canceled!")
void $ try $ launchAff $ (do v <- cancel c (error "Cause")
log (if v then "Success: Canceled later" else "Failure: Did not cancel later"))
log (if v then "Success: Canceled delay" else "Failure: Did not cancel delay"))

test_cancelParallel :: TestAVar Unit
test_cancelParallel = do
c <- forkAff <<< sequential $ parallel (later' 100 $ log "Failure: #1 should not get through") <|>
parallel (later' 100 $ log "Failure: #2 should not get through")
c <- forkAff <<< sequential $ parallel (delay (Milliseconds 100.0) *> log "Failure: #1 should not get through") <|>
parallel (delay (Milliseconds 100.0) *> log "Failure: #2 should not get through")
v <- c `cancel` (error "Must cancel")
log (if v then "Success: Canceling composite of two Parallel succeeded"
else "Failure: Canceling composite of two Parallel failed")
Expand All @@ -206,19 +210,21 @@ test_cancelRaceLeft :: TestAVar Unit
test_cancelRaceLeft = do
var <- makeVar
c <- sequential
$ parallel (later' 250 $ putVar var true)
<|> parallel (later' 100 $ pure unit)
later' 500 $ putVar var false
$ parallel (delay (Milliseconds 250.0) *> putVar var true)
<|> parallel (delay (Milliseconds 100.0))
delay (Milliseconds 500.0)
putVar var false
l <- takeVar var
when l $ throwError (error "Failure: left side ran even though it lost the race")

test_cancelRaceRight :: TestAVar Unit
test_cancelRaceRight = do
var <- makeVar
c <- sequential
$ parallel (later' 100 $ pure unit)
<|> parallel (later' 250 $ putVar var true)
later' 500 $ putVar var false
$ parallel (delay (Milliseconds 100.0))
<|> parallel (delay (Milliseconds 250.0) *> putVar var true)
delay (Milliseconds 500.0)
putVar var false
l <- takeVar var
when l $ throwError (error "Failure: right side ran even though it lost the race")

Expand All @@ -242,7 +248,7 @@ loopAndBounce n = do
where
go 0 = pure (Done 0)
go k | mod k 30000 == 0 = do
later' 10 (pure unit)
delay (Milliseconds 10.0)
pure (Loop (k - 1))
go k = pure (Loop (k - 1))

Expand All @@ -255,20 +261,17 @@ all n = do

cancelAll :: forall eff. Int -> Aff (console :: CONSOLE, avar :: AVAR | eff) Unit
cancelAll n = do
canceler <- forkAll $ replicateArray n (later' 100000 (log "oops"))
canceler <- forkAll $ replicateArray n (delay (Milliseconds 100000.0) *> log "oops")
canceled <- cancel canceler (error "bye")
log ("Cancelled all: " <> show canceled)

delay :: forall eff. Int -> Aff eff Unit
delay n = later' n (pure unit)

main :: Eff (console :: CONSOLE, avar :: AVAR, exception :: EXCEPTION) Unit
main = do
Eff.log "Testing kill of later launched in separate Aff"
test_cancelLaunchLater
Eff.log "Testing kill of delay launched in separate Aff"
test_cancelLaunchDelay

Eff.log "Testing kill of later run in separate Aff"
test_cancelRunLater
Eff.log "Testing kill of delay run in separate Aff"
test_cancelRunDelay

void $ runAff throwException (const (pure unit)) $ do
log "Testing sequencing"
Expand All @@ -283,11 +286,12 @@ main = do
log "Testing attempt"
test_attempt

log "Testing later"
later $ log "Success: It happened later"
log "Testing delay"
delay (Milliseconds 0.0)
log "Success: It happened later"

log "Testing kill of later"
test_cancelLater
log "Testing kill of delay"
test_cancelDelay

log "Testing kill of first forked"
test_killFirstForked
Expand Down Expand Up @@ -335,7 +339,7 @@ main = do
test_syncTailRecM

log "pre-delay"
delay 1000
delay (Milliseconds 1000.0)
log "post-delay"

loopAndBounce 1000000
Expand Down

0 comments on commit 1ed0d75

Please sign in to comment.