Skip to content

Commit 2bd34cd

Browse files
garybnatefaubion
authored andcommitted
Updates dependencies for PureScript 0.10 (#74)
1 parent 91648de commit 2bd34cd

File tree

8 files changed

+89
-94
lines changed

8 files changed

+89
-94
lines changed

bower.json

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -17,12 +17,12 @@
1717
"package.json"
1818
],
1919
"dependencies": {
20-
"purescript-console": "^1.0.0",
21-
"purescript-exceptions": "^1.0.0",
22-
"purescript-functions": "^1.0.0",
23-
"purescript-parallel": "^1.0.0",
24-
"purescript-transformers": "^1.0.0",
25-
"purescript-unsafe-coerce": "^1.0.0"
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"
2626
},
2727
"devDependencies": {
2828
"purescript-partial": "^1.1.2"

package.json

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -7,10 +7,10 @@
77
},
88
"devDependencies": {
99
"jscs": "^3.0.7",
10-
"jshint": "^2.9.3",
10+
"jshint": "^2.9.4",
1111
"pulp": "^9.0.1",
1212
"purescript-psa": "^0.3.9",
13-
"purescript": "^0.9.3",
13+
"purescript": "^0.10.1",
1414
"rimraf": "^2.5.4"
1515
}
1616
}

src/Control/Monad/Aff.purs

Lines changed: 45 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
module Control.Monad.Aff
2-
( Aff()
2+
( Aff
33
, Canceler(..)
44
, PureAff(..)
55
, apathize
@@ -17,8 +17,8 @@ module Control.Monad.Aff
1717
, makeAff'
1818
, nonCanceler
1919
, runAff
20-
)
21-
where
20+
, ParAff(..)
21+
) where
2222

2323
import Prelude
2424

@@ -30,15 +30,16 @@ import Control.Monad.Eff (Eff)
3030
import Control.Monad.Eff.Class (class MonadEff)
3131
import Control.Monad.Eff.Exception (Error, EXCEPTION, throwException, error)
3232
import Control.Monad.Error.Class (class MonadError, throwError)
33-
import Control.Monad.Rec.Class (class MonadRec)
33+
import Control.Monad.Rec.Class (class MonadRec, Step(..))
3434
import Control.MonadPlus (class MonadZero, class MonadPlus)
35-
import Control.Parallel.Class (class MonadRace, class MonadPar)
36-
import Control.Plus (class Plus)
35+
import Control.Parallel (class Parallel)
36+
import Control.Plus (class Plus, empty)
3737

38-
import Data.Either (Either(..), either, isLeft)
38+
import Data.Either (Either(..), either)
3939
import Data.Foldable (class Foldable, foldl)
4040
import Data.Function.Uncurried (Fn2, Fn3, runFn2, runFn3)
4141
import Data.Monoid (class Monoid, mempty)
42+
import Data.Newtype (class Newtype)
4243

4344
import Unsafe.Coerce (unsafeCoerce)
4445

@@ -202,7 +203,10 @@ instance monadZero :: MonadZero (Aff e)
202203
instance monadPlusAff :: MonadPlus (Aff e)
203204

204205
instance monadRecAff :: MonadRec (Aff e) where
205-
tailRecM f a = runFn3 _tailRecM isLeft f a
206+
tailRecM f a = runFn3 _tailRecM isLoop f a
207+
where
208+
isLoop (Loop _) = true
209+
isLoop _ = false
206210

207211
instance monadContAff :: MonadCont (Aff e) where
208212
callCC f = makeAff (\eb cb -> void $ runAff eb cb (f \a -> makeAff (\_ _ -> cb a)))
@@ -213,20 +217,34 @@ instance semigroupCanceler :: Semigroup (Canceler e) where
213217
instance monoidCanceler :: Monoid (Canceler e) where
214218
mempty = Canceler (const (pure true))
215219

216-
instance monadParAff :: MonadPar (Aff e) where
217-
par f ma mb = do
220+
newtype ParAff e a = ParAff (Aff e a)
221+
222+
derive instance newtypeParAff :: Newtype (ParAff e a) _
223+
224+
instance semigroupParAff :: (Semigroup a) => Semigroup (ParAff e a) where
225+
append a b = append <$> a <*> b
226+
227+
instance monoidParAff :: (Monoid a) => Monoid (ParAff e a) where
228+
mempty = pure mempty
229+
230+
derive newtype instance functorParAff :: Functor (ParAff e)
231+
232+
instance applyParAff :: Apply (ParAff e) where
233+
apply (ParAff ff) (ParAff fa) = ParAff do
218234
va <- makeVar
219235
vb <- makeVar
220-
c1 <- forkAff (putOrKill va =<< attempt ma)
221-
c2 <- forkAff (putOrKill vb =<< attempt mb)
222-
f <$> (takeVar va) <*> (takeVar vb)
236+
c1 <- forkAff (putOrKill va =<< attempt ff)
237+
c2 <- forkAff (putOrKill vb =<< attempt fa)
238+
(takeVar va <*> takeVar vb) `cancelWith` (c1 <> c2)
223239
where
224240
putOrKill :: forall a. AVar a -> Either Error a -> Aff e Unit
225241
putOrKill v = either (killVar v) (putVar v)
226242

227-
instance monadRaceAff :: MonadRace (Aff e) where
228-
stall = throwError $ error "Stalled"
229-
race a1 a2 = do
243+
derive newtype instance applicativeParAff :: Applicative (ParAff e)
244+
245+
-- | Returns the first value, or the first error if both error.
246+
instance altParAff :: Alt (ParAff e) where
247+
alt (ParAff a1) (ParAff a2) = ParAff do
230248
va <- makeVar -- the `a` value
231249
ve <- makeVar -- the error count (starts at 0)
232250
putVar ve 0
@@ -237,9 +255,18 @@ instance monadRaceAff :: MonadRace (Aff e) where
237255
maybeKill :: forall a. AVar a -> AVar Int -> Error -> Aff e Unit
238256
maybeKill va ve err = do
239257
e <- takeVar ve
240-
if e == 1 then killVar va err else pure unit
258+
when (e == 1) $ killVar va err
241259
putVar ve (e + 1)
242260

261+
instance plusParAff :: Plus (ParAff e) where
262+
empty = ParAff empty
263+
264+
instance alternativeParAff :: Alternative (ParAff e)
265+
266+
instance parallelParAff :: Parallel (ParAff e) (Aff e) where
267+
parallel = ParAff
268+
sequential (ParAff ma) = ma
269+
243270
makeVar :: forall e a. Aff e (AVar a)
244271
makeVar = fromAVBox $ _makeVar nonCanceler
245272

@@ -281,4 +308,4 @@ foreign import _runAff :: forall e a. Fn3 (Error -> Eff e Unit) (a -> Eff e Unit
281308

282309
foreign import _liftEff :: forall e a. Fn2 (Canceler e) (Eff e a) (Aff e a)
283310

284-
foreign import _tailRecM :: forall e a b. Fn3 (Either a b -> Boolean) (a -> Aff e (Either a b)) a (Aff e b)
311+
foreign import _tailRecM :: forall e a b. Fn3 (Step a b -> Boolean) (a -> Aff e (Step a b)) a (Aff e b)

src/Control/Monad/Aff/Class.purs

Lines changed: 17 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -2,45 +2,45 @@ module Control.Monad.Aff.Class where
22

33
import Prelude
44

5-
import Control.Monad.Aff (Aff())
6-
import Control.Monad.Cont.Trans (ContT())
5+
import Control.Monad.Aff (Aff)
6+
import Control.Monad.Cont.Trans (ContT)
77
import Control.Monad.Eff.Class (class MonadEff)
8-
import Control.Monad.Except.Trans (ExceptT())
9-
import Control.Monad.List.Trans (ListT())
10-
import Control.Monad.Maybe.Trans (MaybeT())
11-
import Control.Monad.Reader.Trans (ReaderT())
12-
import Control.Monad.RWS.Trans (RWST())
13-
import Control.Monad.State.Trans (StateT())
14-
import Control.Monad.Trans (lift)
15-
import Control.Monad.Writer.Trans (WriterT())
8+
import Control.Monad.Except.Trans (ExceptT)
9+
import Control.Monad.List.Trans (ListT)
10+
import Control.Monad.Maybe.Trans (MaybeT)
11+
import Control.Monad.Reader.Trans (ReaderT)
12+
import Control.Monad.RWS.Trans (RWST)
13+
import Control.Monad.State.Trans (StateT)
14+
import Control.Monad.Trans.Class (lift)
15+
import Control.Monad.Writer.Trans (WriterT)
1616

1717
import Data.Monoid (class Monoid)
1818

19-
class (MonadEff eff m) <= MonadAff eff m where
19+
class MonadEff eff m <= MonadAff eff m | m -> eff where
2020
liftAff :: forall a. Aff eff a -> m a
2121

2222
instance monadAffAff :: MonadAff e (Aff e) where
2323
liftAff = id
2424

25-
instance monadAffContT :: (MonadAff eff m) => MonadAff eff (ContT r m) where
25+
instance monadAffContT :: MonadAff eff m => MonadAff eff (ContT r m) where
2626
liftAff = lift <<< liftAff
2727

28-
instance monadAffExceptT :: (MonadAff eff m) => MonadAff eff (ExceptT e m) where
28+
instance monadAffExceptT :: MonadAff eff m => MonadAff eff (ExceptT e m) where
2929
liftAff = lift <<< liftAff
3030

31-
instance monadAffListT :: (MonadAff eff m) => MonadAff eff (ListT m) where
31+
instance monadAffListT :: MonadAff eff m => MonadAff eff (ListT m) where
3232
liftAff = lift <<< liftAff
3333

34-
instance monadAffMaybe :: (MonadAff eff m) => MonadAff eff (MaybeT m) where
34+
instance monadAffMaybe :: MonadAff eff m => MonadAff eff (MaybeT m) where
3535
liftAff = lift <<< liftAff
3636

37-
instance monadAffReader :: (MonadAff eff m) => MonadAff eff (ReaderT r m) where
37+
instance monadAffReader :: MonadAff eff m => MonadAff eff (ReaderT r m) where
3838
liftAff = lift <<< liftAff
3939

4040
instance monadAffRWS :: (MonadAff eff m, Monoid w) => MonadAff eff (RWST r w s m) where
4141
liftAff = lift <<< liftAff
4242

43-
instance monadAffState :: (MonadAff eff m) => MonadAff eff (StateT s m) where
43+
instance monadAffState :: MonadAff eff m => MonadAff eff (StateT s m) where
4444
liftAff = lift <<< liftAff
4545

4646
instance monadAffWriter :: (MonadAff eff m, Monoid w) => MonadAff eff (WriterT w m) where

src/Control/Monad/Aff/Internal.js

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -33,14 +33,14 @@ exports._takeVar = function (nonCanceler, avar) {
3333
};
3434

3535
exports._peekVar = function (nonCanceler, avar) {
36-
return function(success, error) {
36+
return function (success, error) {
3737
if (avar.error !== undefined) {
3838
error(avar.error);
3939
} else if (avar.producers.length > 0) {
4040
var producer = avar.producers[0];
4141
producer(success, error);
4242
} else {
43-
avar.consumers.push({peek: true, success: success, error: error});
43+
avar.consumers.push({ peek: true, success: success, error: error });
4444
}
4545
return nonCanceler;
4646
};

src/Control/Monad/Aff/Unsafe.js

Lines changed: 0 additions & 30 deletions
This file was deleted.

src/Control/Monad/Aff/Unsafe.purs

Lines changed: 4 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,7 @@
11
module Control.Monad.Aff.Unsafe where
22

3-
import Prelude (Unit())
4-
import Control.Monad.Aff (Aff())
3+
import Control.Monad.Aff (Aff)
4+
import Unsafe.Coerce (unsafeCoerce)
55

6-
foreign import unsafeTrace :: forall e a. a -> Aff e Unit
7-
8-
foreign import unsafeInterleaveAff :: forall e1 e2 a. Aff e1 a -> Aff e2 a
6+
unsafeCoerceAff :: forall e1 e2 a. Aff e1 a -> Aff e2 a
7+
unsafeCoerceAff = unsafeCoerce

test/Test/Main.purs

Lines changed: 13 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -3,8 +3,6 @@ module Test.Main where
33
import Prelude
44

55
import Control.Alt ((<|>))
6-
import Control.Apply ((*>))
7-
import Control.Parallel.Class (parallel, runParallel)
86
import Control.Monad.Aff (Aff, runAff, makeAff, launchAff, later, later', forkAff, forkAll, Canceler(..), cancel, attempt, finally, apathize)
97
import Control.Monad.Aff.AVar (AVAR, makeVar, makeVar', putVar, modifyVar, takeVar, peekVar, killVar)
108
import Control.Monad.Aff.Console (CONSOLE, log)
@@ -13,8 +11,9 @@ import Control.Monad.Eff (Eff)
1311
import Control.Monad.Eff.Console (log) as Eff
1412
import Control.Monad.Eff.Exception (EXCEPTION, throwException, error, message, try)
1513
import Control.Monad.Error.Class (throwError)
16-
import Control.Monad.Rec.Class (tailRecM)
17-
import Data.Either (Either(..), either, fromLeft, fromRight)
14+
import Control.Monad.Rec.Class (Step(..), tailRecM)
15+
import Control.Parallel (parallel, sequential)
16+
import Data.Either (either, fromLeft, fromRight)
1817
import Data.Unfoldable (replicate)
1918
import Partial.Unsafe (unsafePartial)
2019

@@ -116,24 +115,24 @@ test_finally = do
116115

117116
test_parRace :: TestAVar Unit
118117
test_parRace = do
119-
s <- runParallel (parallel (later' 100 $ pure "Success: Early bird got the worm") <|>
118+
s <- sequential (parallel (later' 100 $ pure "Success: Early bird got the worm") <|>
120119
parallel (later' 200 $ pure "Failure: Late bird got the worm"))
121120
log s
122121

123122
test_parError :: TestAVar Unit
124123
test_parError = do
125-
e <- attempt $ runParallel (parallel (throwError (error ("Oh noes!"))) *> pure unit)
124+
e <- attempt $ sequential (parallel (throwError (error ("Oh noes!"))) *> pure unit)
126125
either (const $ log "Success: Exception propagated") (const $ log "Failure: Exception missing") e
127126

128127
test_parRaceKill1 :: TestAVar Unit
129128
test_parRaceKill1 = do
130-
s <- runParallel (parallel (later' 100 $ throwError (error ("Oh noes!"))) <|>
129+
s <- sequential (parallel (later' 100 $ throwError (error ("Oh noes!"))) <|>
131130
parallel (later' 200 $ pure "Success: Early error was ignored in favor of late success"))
132131
log s
133132

134133
test_parRaceKill2 :: TestAVar Unit
135134
test_parRaceKill2 = do
136-
e <- attempt $ runParallel (parallel (later' 100 $ throwError (error ("Oh noes!"))) <|>
135+
e <- attempt $ sequential (parallel (later' 100 $ throwError (error ("Oh noes!"))) <|>
137136
parallel (later' 200 $ throwError (error ("Oh noes!"))))
138137
either (const $ log "Success: Killing both kills it dead") (const $ log "Failure: It's alive!!!") e
139138

@@ -168,7 +167,7 @@ test_cancelRunLater = do
168167

169168
test_cancelParallel :: TestAVar Unit
170169
test_cancelParallel = do
171-
c <- forkAff <<< runParallel $ parallel (later' 100 $ log "Failure: #1 should not get through") <|>
170+
c <- forkAff <<< sequential $ parallel (later' 100 $ log "Failure: #1 should not get through") <|>
172171
parallel (later' 100 $ log "Failure: #2 should not get through")
173172
v <- c `cancel` (error "Must cancel")
174173
log (if v then "Success: Canceling composite of two Parallel succeeded"
@@ -184,19 +183,19 @@ test_syncTailRecM = do
184183
where
185184
go { n: 0, v } = do
186185
modifyVar (const true) v
187-
pure (Right 0)
188-
go { n, v } = pure (Left { n: n - 1, v })
186+
pure (Done 0)
187+
go { n, v } = pure (Loop { n: n - 1, v })
189188

190189
loopAndBounce :: forall eff. Int -> Aff (console :: CONSOLE | eff) Unit
191190
loopAndBounce n = do
192191
res <- tailRecM go n
193192
log $ "Done: " <> show res
194193
where
195-
go 0 = pure (Right 0)
194+
go 0 = pure (Done 0)
196195
go n | mod n 30000 == 0 = do
197196
later' 10 (pure unit)
198-
pure (Left (n - 1))
199-
go n = pure (Left (n - 1))
197+
pure (Loop (n - 1))
198+
go n = pure (Loop (n - 1))
200199

201200
all :: forall eff. Int -> Aff (console :: CONSOLE, avar :: AVAR | eff) Unit
202201
all n = do

0 commit comments

Comments
 (0)