Skip to content

Commit e2de397

Browse files
committed
Use more spark# and seq#
Like it says on the tin. This should lead to more consistent behavior among strategies.
1 parent 9ea4c07 commit e2de397

File tree

1 file changed

+67
-26
lines changed

1 file changed

+67
-26
lines changed

Control/Parallel/Strategies.hs

Lines changed: 67 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -145,15 +145,14 @@ import Data.Traversable
145145
import Control.Applicative
146146
#endif
147147
import Control.Parallel
148-
import Control.DeepSeq (NFData(rnf))
148+
import Control.DeepSeq (NFData, force)
149149

150150
#if MIN_VERSION_base(4,4,0)
151151
import System.IO.Unsafe (unsafeDupablePerformIO)
152-
import Control.Exception (evaluate)
153152
#else
154153
import System.IO.Unsafe (unsafePerformIO)
155-
import Control.Monad
156154
#endif
155+
import Control.Monad
157156

158157
import qualified Control.Seq
159158

@@ -202,25 +201,36 @@ infixl 0 `using` -- lowest precedence and associate to the left
202201
#if __GLASGOW_HASKELL__ >= 702
203202

204203
newtype Eval a = Eval {unEval_ :: IO a}
205-
deriving (Functor, Applicative, Monad)
204+
deriving Functor
206205
-- GHC 7.2.1 added the seq# and spark# primitives, that we use in
207206
-- the Eval monad implementation in order to get the correct
208207
-- strictness behaviour.
209208

209+
instance Applicative Eval where
210+
pure x = r0 x
211+
(<*>) = ap
212+
213+
instance Monad Eval where
214+
return x = pure x
215+
Eval m >>= f = Eval (m >>= unEval_ . f)
216+
210217
-- | Pull the result out of the monad.
211218
runEval :: Eval a -> a
212219
# if MIN_VERSION_base(4,4,0)
213220
runEval = unsafeDupablePerformIO . unEval_
214221
# else
215222
runEval = unsafePerformIO . unEval_
216223
# endif
224+
-- Staged inline for RULES
225+
{-# INLINE [1] runEval #-}
217226
#else
218227

219228
data Eval a = Done a
220229

221230
-- | Pull the result out of the monad.
222231
runEval :: Eval a -> a
223232
runEval (Done x) = x
233+
{-# INLINE [1] runEval #-}
224234

225235
instance Functor Eval where
226236
fmap = liftM
@@ -259,6 +269,11 @@ instance Monad Eval where
259269

260270
#endif
261271

272+
{-# RULES
273+
"runEval/r0" forall x. runEval (r0 x) = x
274+
"runEval/rpar" forall x. runEval (rpar x) = x
275+
"runEval/rseq" forall x. runEval (rseq x) = x
276+
#-}
262277

263278
-- -----------------------------------------------------------------------------
264279
-- Strategies
@@ -286,12 +301,14 @@ type Strategy a = a -> Eval a
286301
--
287302
using :: a -> Strategy a -> a
288303
x `using` strat = runEval (strat x)
304+
{-# INLINABLE using #-}
289305

290306
-- | evaluate a value using the given 'Strategy'. This is simply
291307
-- 'using' with the arguments reversed.
292308
--
293309
withStrategy :: Strategy a -> a -> a
294310
withStrategy = flip using
311+
{-# INLINABLE withStrategy #-}
295312

296313
-- | Compose two strategies sequentially.
297314
-- This is the analogue to function composition on strategies.
@@ -300,6 +317,7 @@ withStrategy = flip using
300317
--
301318
dot :: Strategy a -> Strategy a -> Strategy a
302319
strat2 `dot` strat1 = strat2 . runEval . strat1
320+
{-# INLINABLE dot #-}
303321

304322
-- Proof of strat2 `dot` strat1 == strat2 . withStrategy strat1
305323
--
@@ -327,7 +345,8 @@ strat2 `dot` strat1 = strat2 . runEval . strat1
327345
-- Thanks to 'evalSeq', the type @Control.Seq.Strategy a@ is a subtype
328346
-- of @'Strategy' a@.
329347
evalSeq :: SeqStrategy a -> Strategy a
330-
evalSeq strat x = strat x `pseq` return x
348+
evalSeq sstrat x = rseq (sstrat x) >> return x
349+
{-# INLINABLE evalSeq #-}
331350

332351
-- | A name for @Control.Seq.Strategy@, for documentation only.
333352
type SeqStrategy a = Control.Seq.Strategy a
@@ -340,7 +359,13 @@ type SeqStrategy a = Control.Seq.Strategy a
340359
-- > r0 == evalSeq Control.Seq.r0
341360
--
342361
r0 :: Strategy a
343-
r0 x = return x
362+
#if __GLASGOW_HASKELL__ >= 702
363+
r0 x = Eval (return x)
364+
#else
365+
r0 = Done
366+
#endif
367+
-- Staged INLINE for RULES
368+
{-# INLINABLE [1] r0 #-}
344369

345370
-- Proof of r0 == evalSeq Control.Seq.r0
346371
--
@@ -356,12 +381,15 @@ r0 x = return x
356381
--
357382
rseq :: Strategy a
358383
#if __GLASGOW_HASKELL__ >= 702
359-
rseq x = Eval (evaluate x)
384+
-- The bang pattern here works around GHC Trac #15226
385+
rseq x = Eval $ IO $ \s ->
386+
case seq# x s of
387+
(# s', !x' #) -> (# s', x' #)
360388
#else
361389
rseq x = x `seq` return x
362390
#endif
363-
-- Staged NOINLINE so we can match on rseq in RULES
364-
{-# NOINLINE [1] rseq #-}
391+
-- Staged INLINE for RULES
392+
{-# INLINABLE [1] rseq #-}
365393

366394

367395
-- Proof of rseq == evalSeq Control.Seq.rseq
@@ -377,7 +405,8 @@ rseq x = x `seq` return x
377405
-- > rdeepseq == evalSeq Control.Seq.rdeepseq
378406
--
379407
rdeepseq :: NFData a => Strategy a
380-
rdeepseq x = do rseq (rnf x); return x
408+
rdeepseq x = rseq (force x)
409+
{-# INLINABLE rdeepseq #-}
381410

382411
-- Proof of rdeepseq == evalSeq Control.Seq.rdeepseq
383412
--
@@ -395,7 +424,8 @@ rpar x = Eval $ IO $ \s -> spark# x s
395424
#else
396425
rpar x = case (par# x) of { _ -> Done x }
397426
#endif
398-
{-# INLINE rpar #-}
427+
-- Staged inline for RULES
428+
{-# INLINABLE [1] rpar #-}
399429

400430
-- | instead of saying @rpar `dot` strat@, you can say
401431
-- @rparWith strat@. Compared to 'rpar', 'rparWith'
@@ -413,6 +443,7 @@ rparWith s = rpar `dot` s
413443
#else
414444
rparWith s a = do l <- rpar (s a); return (case l of Done x -> x)
415445
#endif
446+
{-# INLINABLE rparWith #-}
416447

417448
-- --------------------------------------------------------------------------
418449
-- Strategy combinators for Traversable data types
@@ -421,12 +452,11 @@ rparWith s a = do l <- rpar (s a); return (case l of Done x -> x)
421452
-- according to the given strategy.
422453
evalTraversable :: Traversable t => Strategy a -> Strategy (t a)
423454
evalTraversable = traverse
424-
{-# INLINE evalTraversable #-}
425455

426456
-- | Like 'evalTraversable' but evaluates all elements in parallel.
427457
parTraversable :: Traversable t => Strategy a -> Strategy (t a)
428458
parTraversable strat = evalTraversable (rparWith strat)
429-
{-# INLINE parTraversable #-}
459+
{-# INLINABLE parTraversable #-}
430460

431461
-- --------------------------------------------------------------------------
432462
-- Strategies for lists
@@ -445,6 +475,7 @@ evalList = evalTraversable
445475
-- Equivalent to 'parTraversable' at the list type.
446476
parList :: Strategy a -> Strategy [a]
447477
parList = parTraversable
478+
{-# INLINABLE parList #-}
448479
-- Alternative definition via evalList:
449480
-- parList strat = evalList (rparWith strat)
450481

@@ -461,6 +492,7 @@ evalListSplitAt n stratPref stratSuff xs
461492
-- | Like 'evalListSplitAt' but evaluates both sublists in parallel.
462493
parListSplitAt :: Int -> Strategy [a] -> Strategy [a] -> Strategy [a]
463494
parListSplitAt n stratPref stratSuff = evalListSplitAt n (rparWith stratPref) (rparWith stratSuff)
495+
{-# INLINABLE parListSplitAt #-}
464496

465497
-- | Evaluate the first n elements of a list according to the given strategy.
466498
evalListN :: Int -> Strategy a -> Strategy [a]
@@ -469,6 +501,7 @@ evalListN n strat = evalListSplitAt n (evalList strat) r0
469501
-- | Like 'evalListN' but evaluates the first n elements in parallel.
470502
parListN :: Int -> Strategy a -> Strategy [a]
471503
parListN n strat = evalListN n (rparWith strat)
504+
{-# INLINABLE parListN #-}
472505

473506
-- | Evaluate the nth element of a list (if there is such) according to
474507
-- the given strategy.
@@ -481,6 +514,7 @@ evalListNth n strat = evalListSplitAt n r0 (evalListN 1 strat)
481514
-- | Like 'evalListN' but evaluates the nth element in parallel.
482515
parListNth :: Int -> Strategy a -> Strategy [a]
483516
parListNth n strat = evalListNth n (rparWith strat)
517+
{-# INLINABLE parListNth #-}
484518

485519
-- | Divides a list into chunks, and applies the strategy
486520
-- @'evalList' strat@ to each chunk in parallel.
@@ -509,6 +543,7 @@ chunk n xs = as : chunk n bs where (as,bs) = splitAt n xs
509543
--
510544
parMap :: Strategy b -> (a -> b) -> [a] -> [b]
511545
parMap strat f = (`using` parList strat) . map f
546+
{-# INLINABLE parMap #-}
512547

513548
-- --------------------------------------------------------------------------
514549
-- Strategies for lazy lists
@@ -557,17 +592,16 @@ parBufferWHNF n0 xs0 = return (ret xs0 (start n0 xs0))
557592
-- pushing them into the buffer.
558593
parBuffer :: Int -> Strategy a -> Strategy [a]
559594
parBuffer n strat = parBufferWHNF n . map (withStrategy strat)
595+
{-# INLINABLE parBuffer #-}
560596
-- Alternative definition via evalBuffer (may compromise firing of RULES):
561597
-- parBuffer n strat = evalBuffer n (rparWith strat)
562598

563599
-- Deforest the intermediate list in parBuffer/evalBuffer when it is
564600
-- unnecessary:
565601

566602
{-# NOINLINE [1] evalBuffer #-}
567-
{-# NOINLINE [1] parBuffer #-}
568603
{-# RULES
569604
"evalBuffer/rseq" forall n . evalBuffer n rseq = evalBufferWHNF n
570-
"parBuffer/rseq" forall n . parBuffer n rseq = parBufferWHNF n
571605
#-}
572606

573607
-- --------------------------------------------------------------------------
@@ -608,40 +642,48 @@ evalTuple9 strat1 strat2 strat3 strat4 strat5 strat6 strat7 strat8 strat9 (x1,x2
608642
parTuple2 :: Strategy a -> Strategy b -> Strategy (a,b)
609643
parTuple2 strat1 strat2 =
610644
evalTuple2 (rparWith strat1) (rparWith strat2)
645+
{-# INLINABLE parTuple2 #-}
611646

612647
parTuple3 :: Strategy a -> Strategy b -> Strategy c -> Strategy (a,b,c)
613648
parTuple3 strat1 strat2 strat3 =
614649
evalTuple3 (rparWith strat1) (rparWith strat2) (rparWith strat3)
650+
{-# INLINABLE parTuple3 #-}
615651

616652
parTuple4 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy (a,b,c,d)
617653
parTuple4 strat1 strat2 strat3 strat4 =
618654
evalTuple4 (rparWith strat1) (rparWith strat2) (rparWith strat3) (rparWith strat4)
655+
{-# INLINABLE parTuple4 #-}
619656

620657
parTuple5 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy (a,b,c,d,e)
621658
parTuple5 strat1 strat2 strat3 strat4 strat5 =
622659
evalTuple5 (rparWith strat1) (rparWith strat2) (rparWith strat3) (rparWith strat4) (rparWith strat5)
660+
{-# INLINABLE parTuple5 #-}
623661

624662
parTuple6 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy (a,b,c,d,e,f)
625663
parTuple6 strat1 strat2 strat3 strat4 strat5 strat6 =
626664
evalTuple6 (rparWith strat1) (rparWith strat2) (rparWith strat3) (rparWith strat4) (rparWith strat5) (rparWith strat6)
665+
{-# INLINABLE parTuple6 #-}
627666

628667
parTuple7 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy g -> Strategy (a,b,c,d,e,f,g)
629668
parTuple7 strat1 strat2 strat3 strat4 strat5 strat6 strat7 =
630669
evalTuple7 (rparWith strat1) (rparWith strat2) (rparWith strat3) (rparWith strat4) (rparWith strat5) (rparWith strat6) (rparWith strat7)
670+
{-# INLINABLE parTuple7 #-}
631671

632672
parTuple8 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy g -> Strategy h -> Strategy (a,b,c,d,e,f,g,h)
633673
parTuple8 strat1 strat2 strat3 strat4 strat5 strat6 strat7 strat8 =
634674
evalTuple8 (rparWith strat1) (rparWith strat2) (rparWith strat3) (rparWith strat4) (rparWith strat5) (rparWith strat6) (rparWith strat7) (rparWith strat8)
675+
{-# INLINABLE parTuple8 #-}
635676

636677
parTuple9 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy g -> Strategy h -> Strategy i -> Strategy (a,b,c,d,e,f,g,h,i)
637678
parTuple9 strat1 strat2 strat3 strat4 strat5 strat6 strat7 strat8 strat9 =
638679
evalTuple9 (rparWith strat1) (rparWith strat2) (rparWith strat3) (rparWith strat4) (rparWith strat5) (rparWith strat6) (rparWith strat7) (rparWith strat8) (rparWith strat9)
680+
{-# INLINABLE parTuple9 #-}
639681

640682
-- --------------------------------------------------------------------------
641683
-- Strategic function application
642684

643685
{-
644-
These are very handy when writing pipeline parallelism asa sequence of
686+
These are very handy when writing pipeline parallelism as a sequence of
645687
@$@, @$|@ and @$||@'s. There is no need of naming intermediate values
646688
in this case. The separation of algorithm from strategy is achieved by
647689
allowing strategies only as second arguments to @$|@ and @$||@.
@@ -650,43 +692,42 @@ allowing strategies only as second arguments to @$|@ and @$||@.
650692
-- | Sequential function application. The argument is evaluated using
651693
-- the given strategy before it is given to the function.
652694
($|) :: (a -> b) -> Strategy a -> a -> b
653-
f $| s = \ x -> let z = x `using` s in z `pseq` f z
695+
f $| s = runEval . (return . f <=< rseq <=< s)
654696

655697
-- | Parallel function application. The argument is evaluated using
656698
-- the given strategy, in parallel with the function application.
657699
($||) :: (a -> b) -> Strategy a -> a -> b
658-
f $|| s = \ x -> let z = x `using` s in z `par` f z
700+
f $|| s = runEval . (return . f <=< rpar <=< s)
701+
{-# INLINABLE ($||) #-}
659702

660703
-- | Sequential function composition. The result of
661704
-- the second function is evaluated using the given strategy,
662705
-- and then given to the first function.
663706
(.|) :: (b -> c) -> Strategy b -> (a -> b) -> (a -> c)
664-
(.|) f s g = \ x -> let z = g x `using` s in
665-
z `pseq` f z
707+
(.|) f s g = runEval . (return . f <=< rseq <=< s . g)
666708

667709
-- | Parallel function composition. The result of the second
668710
-- function is evaluated using the given strategy,
669711
-- in parallel with the application of the first function.
670712
(.||) :: (b -> c) -> Strategy b -> (a -> b) -> (a -> c)
671-
(.||) f s g = \ x -> let z = g x `using` s in
672-
z `par` f z
713+
(.||) f s g = runEval . (return . f <=< rpar <=< s . g)
714+
{-# INLINABLE (.||) #-}
673715

674716
-- | Sequential inverse function composition,
675717
-- for those who read their programs from left to right.
676718
-- The result of the first function is evaluated using the
677719
-- given strategy, and then given to the second function.
678720
(-|) :: (a -> b) -> Strategy b -> (b -> c) -> (a -> c)
679-
(-|) f s g = \ x -> let z = f x `using` s in
680-
z `pseq` g z
721+
(-|) f s g = runEval . (return . g <=< rseq <=< s . f)
681722

682723
-- | Parallel inverse function composition,
683724
-- for those who read their programs from left to right.
684725
-- The result of the first function is evaluated using the
685726
-- given strategy, in parallel with the application of the
686727
-- second function.
687728
(-||) :: (a -> b) -> Strategy b -> (b -> c) -> (a -> c)
688-
(-||) f s g = \ x -> let z = f x `using` s in
689-
z `par` g z
729+
(-||) f s g = runEval . (return . g <=< rpar <=< s . f)
730+
{-# INLINABLE (-||) #-}
690731

691732
-- -----------------------------------------------------------------------------
692733
-- Old/deprecated stuff

0 commit comments

Comments
 (0)