@@ -432,19 +432,33 @@ rpar x = case (par# x) of { _ -> Done x }
432432#endif
433433{-# INLINE rpar #-}
434434
435- -- | instead of saying @rpar `dot` strat@, you can say
436- -- @rparWith strat@. Compared to 'rpar', 'rparWith'
435+ -- | Perform a computation in parallel using a strategy.
437436--
438- -- * does not exit the `Eval` monad
439- --
440- -- * does not have a built-in `rseq`, so for example `rparWith r0`
441- -- behaves as you might expect (it is a strategy that creates a
442- -- spark that does no evaluation).
437+ -- @
438+ -- rparWith strat x
439+ -- @
443440--
441+ -- will spark a thread to perform @strat x@ in parallel. Note
442+ -- that @rparWith strat@ is /not/ the same as @rpar `dot` strat@.
443+ -- Specifically, @rpar `dot` strat@ always produces a value in
444+ -- WHNF, while @rparWith strat@ need not.
444445--
446+ -- > rparWith r0 = r0
447+ -- > rparWith rpar = rpar
448+ -- > rparWith rseq = rpar
445449rparWith :: Strategy a -> Strategy a
446450#if __GLASGOW_HASKELL__ >= 702
447- rparWith s = rpar `dot` s
451+ -- The intermediate `Lift` box is necessary, in order to avoid a built-in
452+ -- `rseq` in `rparWith`. In particular, we want rparWith r0 = r0, not
453+ -- rparWith r0 = rpar.
454+ rparWith s a = do
455+ l <- rpar r
456+ return (case l of Lift x -> x)
457+
458+ where
459+ r = runEval (Lift <$> s a)
460+
461+ data Lift a = Lift a
448462#else
449463rparWith s a = do l <- rpar (s a); return (case l of Done x -> x)
450464#endif
0 commit comments