Skip to content

Commit c347744

Browse files
committed
Updates for 0.11
1 parent 23797b4 commit c347744

File tree

6 files changed

+33
-29
lines changed

6 files changed

+33
-29
lines changed

bower.json

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -17,14 +17,14 @@
1717
"package.json"
1818
],
1919
"dependencies": {
20-
"purescript-console": "^2.0.0",
21-
"purescript-exceptions": "^2.0.0",
22-
"purescript-functions": "^2.0.0",
23-
"purescript-parallel": "^2.0.0",
24-
"purescript-transformers": "^2.0.1",
25-
"purescript-unsafe-coerce": "^2.0.0"
20+
"purescript-console": "^3.0.0",
21+
"purescript-exceptions": "^3.0.0",
22+
"purescript-functions": "^3.0.0",
23+
"purescript-parallel": "^3.0.0",
24+
"purescript-transformers": "^3.0.0",
25+
"purescript-unsafe-coerce": "^3.0.0"
2626
},
2727
"devDependencies": {
28-
"purescript-partial": "^1.1.2"
28+
"purescript-partial": "^1.2.0"
2929
}
3030
}

package.json

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -9,8 +9,8 @@
99
"jscs": "^3.0.7",
1010
"jshint": "^2.9.4",
1111
"pulp": "^10.0.0",
12-
"purescript-psa": "^0.4.0",
13-
"purescript": "^0.10.1",
12+
"purescript-psa": "^0.5.0-rc.1",
13+
"purescript": "^0.11.0",
1414
"rimraf": "^2.5.4"
1515
}
1616
}

src/Control/Monad/Aff.purs

Lines changed: 13 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -25,10 +25,10 @@ import Prelude
2525
import Control.Alt (class Alt)
2626
import Control.Alternative (class Alternative)
2727
import Control.Monad.Aff.Internal (AVBox, AVar, _killVar, _putVar, _takeVar, _makeVar)
28-
import Control.Monad.Eff (Eff)
28+
import Control.Monad.Eff (Eff, kind Effect)
2929
import Control.Monad.Eff.Class (class MonadEff)
3030
import Control.Monad.Eff.Exception (Error, EXCEPTION, throwException, error)
31-
import Control.Monad.Error.Class (class MonadError, throwError)
31+
import Control.Monad.Error.Class (class MonadThrow, class MonadError, throwError)
3232
import Control.Monad.Rec.Class (class MonadRec, Step(..))
3333
import Control.MonadPlus (class MonadZero, class MonadPlus)
3434
import Control.Parallel (class Parallel)
@@ -46,7 +46,7 @@ import Unsafe.Coerce (unsafeCoerce)
4646
-- | errors or produces a value of type `a`.
4747
-- |
4848
-- | This is moral equivalent of `ErrorT (ContT Unit (Eff e)) a`.
49-
foreign import data Aff :: # ! -> * -> *
49+
foreign import data Aff :: # Effect -> Type -> Type
5050

5151
-- | A pure asynchronous computation, having no effects other than
5252
-- | asynchronous computation.
@@ -79,12 +79,12 @@ cancelWith aff c = runFn3 _cancelWith nonCanceler aff c
7979
-- | If you do need to handle exceptions, you can use `runAff` instead, or
8080
-- | you can handle the exception within the Aff computation, using
8181
-- | `catchError` (or any of the other mechanisms).
82-
launchAff :: forall e a. Aff e a -> Eff (err :: EXCEPTION | e) (Canceler e)
82+
launchAff :: forall e a. Aff e a -> Eff (exception :: EXCEPTION | e) (Canceler e)
8383
launchAff = lowerEx <<< runAff throwException (const (pure unit)) <<< liftEx
8484
where
85-
liftEx :: Aff e a -> Aff (err :: EXCEPTION | e) a
85+
liftEx :: Aff e a -> Aff (exception :: EXCEPTION | e) a
8686
liftEx = _unsafeInterleaveAff
87-
lowerEx :: Eff (err :: EXCEPTION | e) (Canceler (err :: EXCEPTION | e)) -> Eff (err :: EXCEPTION | e) (Canceler e)
87+
lowerEx :: Eff (exception :: EXCEPTION | e) (Canceler (exception :: EXCEPTION | e)) -> Eff (exception :: EXCEPTION | e) (Canceler e)
8888
lowerEx = map (Canceler <<< map _unsafeInterleaveAff <<< cancel)
8989

9090
-- | Runs the asynchronous computation. You must supply an error callback and a
@@ -120,7 +120,7 @@ later' n aff = runFn3 _setTimeout nonCanceler n aff
120120
finally :: forall e a b. Aff e a -> Aff e b -> Aff e a
121121
finally aff1 aff2 = do
122122
x <- attempt aff1
123-
aff2
123+
_ <- aff2
124124
either throwError pure x
125125

126126
-- | Forks the specified asynchronous computation so subsequent computations
@@ -148,7 +148,7 @@ apathize :: forall e a. Aff e a -> Aff e Unit
148148
apathize a = const unit <$> attempt a
149149

150150
-- | Lifts a synchronous computation and makes explicit any failure from exceptions.
151-
liftEff' :: forall e a. Eff (err :: EXCEPTION | e) a -> Aff e (Either Error a)
151+
liftEff' :: forall e a. Eff (exception :: EXCEPTION | e) a -> Aff e (Either Error a)
152152
liftEff' eff = attempt (_unsafeInterleaveAff (runFn2 _liftEff nonCanceler eff))
153153

154154
-- | A constant canceller that always returns false.
@@ -182,11 +182,14 @@ instance monadAff :: Monad (Aff e)
182182
instance monadEffAff :: MonadEff e (Aff e) where
183183
liftEff eff = runFn2 _liftEff nonCanceler eff
184184

185-
-- | Allows users to catch and throw errors on the error channel of the
185+
-- | Allows users to throw errors on the error channel of the
186186
-- | asynchronous computation. See documentation in `purescript-transformers`.
187-
instance monadErrorAff :: MonadError Error (Aff e) where
187+
instance monadThrowAff :: MonadThrow Error (Aff e) where
188188
throwError e = runFn2 _throwError nonCanceler e
189189

190+
-- | Allows users to catch errors on the error channel of the
191+
-- | asynchronous computation. See documentation in `purescript-transformers`.
192+
instance monadErrorAff :: MonadError Error (Aff e) where
190193
catchError aff ex = attempt aff >>= either ex pure
191194

192195
instance altAff :: Alt (Aff e) where

src/Control/Monad/Aff/AVar.purs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -17,13 +17,14 @@ import Prelude
1717
import Control.Monad.Aff (Aff, nonCanceler)
1818
import Control.Monad.Aff.Internal (AVar) as Exports
1919
import Control.Monad.Aff.Internal (AVBox, AVar, _killVar, _putVar, _takeVar, _peekVar, _makeVar)
20+
import Control.Monad.Eff (kind Effect)
2021
import Control.Monad.Eff.Exception (Error())
2122

2223
import Data.Function.Uncurried (runFn3, runFn2)
2324

2425
import Unsafe.Coerce (unsafeCoerce)
2526

26-
foreign import data AVAR :: !
27+
foreign import data AVAR :: Effect
2728

2829
type AffAVar e a = Aff (avar :: AVAR | e) a
2930

src/Control/Monad/Aff/Internal.purs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -14,9 +14,9 @@ import Control.Monad.Eff.Exception (Error)
1414

1515
import Data.Function.Uncurried (Fn2, Fn3)
1616

17-
foreign import data AVar :: * -> *
17+
foreign import data AVar :: Type -> Type
1818

19-
foreign import data AVBox :: * -> *
19+
foreign import data AVBox :: Type -> Type
2020

2121
foreign import _makeVar :: forall c a. c -> AVBox (AVar a)
2222

test/Test/Main.purs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -75,15 +75,15 @@ test_apathize = do
7575
test_putTakeVar :: TestAVar Unit
7676
test_putTakeVar = do
7777
v <- makeVar
78-
forkAff (later $ putVar v 1.0)
78+
_ <- forkAff (later $ putVar v 1.0)
7979
a <- takeVar v
8080
log ("Success: Value " <> show a)
8181

8282
test_peekVar :: TestAVar Unit
8383
test_peekVar = do
8484
timeout 1000 do
8585
v <- makeVar
86-
forkAff (later $ putVar v 1.0)
86+
_ <- forkAff (later $ putVar v 1.0)
8787
a1 <- peekVar v
8888
a2 <- takeVar v
8989
when (a1 /= a2) do
@@ -101,7 +101,7 @@ test_peekVar = do
101101
timeout 1000 do
102102
x <- makeVar
103103
res <- makeVar' 1
104-
forkAff do
104+
_ <- forkAff do
105105
c <- peekVar x
106106
putVar x 1000
107107
d <- peekVar x
@@ -176,13 +176,13 @@ test_semigroupCanceler =
176176

177177
test_cancelLater :: TestAVar Unit
178178
test_cancelLater = do
179-
c <- forkAff $ (do pure "Binding"
179+
c <- forkAff $ (do _ <- pure "Binding"
180180
_ <- later' 100 $ log ("Failure: Later was not canceled!")
181181
pure "Binding")
182182
v <- cancel c (error "Cause")
183183
log (if v then "Success: Canceled later" else "Failure: Did not cancel later")
184184

185-
test_cancelLaunchLater :: forall e. Eff (console :: CONSOLE, err :: EXCEPTION | e) Unit
185+
test_cancelLaunchLater :: forall e. Eff (console :: CONSOLE, exception :: EXCEPTION | e) Unit
186186
test_cancelLaunchLater = do
187187
c <- launchAff $ later' 100 $ log ("Failure: Later was not canceled!")
188188
void $ launchAff $ (do v <- cancel c (error "Cause")
@@ -229,7 +229,7 @@ loopAndBounce n = do
229229
all :: forall eff. Int -> Aff (console :: CONSOLE, avar :: AVAR | eff) Unit
230230
all n = do
231231
var <- makeVar' 0
232-
forkAll $ replicateArray n (modifyVar (_ + 1) var)
232+
_ <- forkAll $ replicateArray n (modifyVar (_ + 1) var)
233233
count <- takeVar var
234234
log ("Forked " <> show count)
235235

@@ -242,7 +242,7 @@ cancelAll n = do
242242
delay :: forall eff. Int -> Aff eff Unit
243243
delay n = later' n (pure unit)
244244

245-
main :: Eff (console :: CONSOLE, avar :: AVAR, err :: EXCEPTION) Unit
245+
main :: Eff (console :: CONSOLE, avar :: AVAR, exception :: EXCEPTION) Unit
246246
main = do
247247
Eff.log "Testing kill of later launched in separate Aff"
248248
test_cancelLaunchLater

0 commit comments

Comments
 (0)