3636-----------------------------------------------------------------------------
3737
3838module Control.Parallel.Strategies (
39- -- * The strategy type
39+ -- * The strategy types
4040 Strategy
41+ , Strategy'
4142
4243 -- * Application of strategies
4344 , using -- :: a -> Strategy a -> a
@@ -279,26 +280,27 @@ instance Monad Eval where
279280-- value. This idiom is expressed by the 'using' function.
280281--
281282type Strategy a = a -> Eval a
283+ type Strategy' a b = a -> Eval b
282284
283285-- | Evaluate a value using the given 'Strategy'.
284286--
285287-- > x `using` s = runEval (s x)
286288--
287- using :: a -> Strategy a -> a
289+ using :: a -> Strategy' a b -> b
288290x `using` strat = runEval (strat x)
289291
290292-- | evaluate a value using the given 'Strategy'. This is simply
291293-- 'using' with the arguments reversed.
292294--
293- withStrategy :: Strategy a -> a -> a
295+ withStrategy :: Strategy' a b -> a -> b
294296withStrategy = flip using
295297
296298-- | Compose two strategies sequentially.
297299-- This is the analogue to function composition on strategies.
298300--
299301-- > strat2 `dot` strat1 == strat2 . withStrategy strat1
300302--
301- dot :: Strategy a -> Strategy a -> Strategy a
303+ dot :: Strategy' b c -> Strategy' a b -> Strategy' a c
302304strat2 `dot` strat1 = strat2 . runEval . strat1
303305
304306-- Proof of strat2 `dot` strat1 == strat2 . withStrategy strat1
@@ -407,7 +409,7 @@ rpar x = case (par# x) of { _ -> Done x }
407409-- spark that does no evaluation).
408410--
409411--
410- rparWith :: Strategy a -> Strategy a
412+ rparWith :: Strategy' a b -> Strategy' a b
411413#if __GLASGOW_HASKELL__ >= 702
412414rparWith s = rpar `dot` s
413415#else
@@ -419,12 +421,12 @@ rparWith s a = do l <- rpar (s a); return (case l of Done x -> x)
419421
420422-- | Evaluate the elements of a traversable data structure
421423-- according to the given strategy.
422- evalTraversable :: Traversable t => Strategy a -> Strategy (t a )
424+ evalTraversable :: Traversable t => Strategy' a b -> Strategy' (t a ) ( t b )
423425evalTraversable = traverse
424426{-# INLINE evalTraversable #-}
425427
426428-- | Like 'evalTraversable' but evaluates all elements in parallel.
427- parTraversable :: Traversable t => Strategy a -> Strategy (t a )
429+ parTraversable :: Traversable t => Strategy' a b -> Strategy' (t a ) ( t b )
428430parTraversable strat = evalTraversable (rparWith strat)
429431{-# INLINE parTraversable #-}
430432
@@ -433,7 +435,7 @@ parTraversable strat = evalTraversable (rparWith strat)
433435
434436-- | Evaluate each element of a list according to the given strategy.
435437-- Equivalent to 'evalTraversable' at the list type.
436- evalList :: Strategy a -> Strategy [a ]
438+ evalList :: Strategy' a b -> Strategy' [a ] [ b ]
437439evalList = evalTraversable
438440-- Alternative explicitly recursive definition:
439441-- evalList strat [] = return []
@@ -443,23 +445,23 @@ evalList = evalTraversable
443445
444446-- | Evaluate each element of a list in parallel according to given strategy.
445447-- Equivalent to 'parTraversable' at the list type.
446- parList :: Strategy a -> Strategy [a ]
448+ parList :: Strategy' a b -> Strategy' [a ] [ b ]
447449parList = parTraversable
448450-- Alternative definition via evalList:
449451-- parList strat = evalList (rparWith strat)
450452
451453-- | @'evaListSplitAt' n stratPref stratSuff@ evaluates the prefix
452454-- (of length @n@) of a list according to @stratPref@ and its the suffix
453455-- according to @stratSuff@.
454- evalListSplitAt :: Int -> Strategy [a ] -> Strategy [a ] -> Strategy [a ]
456+ evalListSplitAt :: Int -> Strategy' [a ] [ b ] -> Strategy' [a ] [ b ] -> Strategy' [a ] [ b ]
455457evalListSplitAt n stratPref stratSuff xs
456458 = let (ys,zs) = splitAt n xs in
457459 stratPref ys >>= \ ys' ->
458460 stratSuff zs >>= \ zs' ->
459461 return (ys' ++ zs')
460462
461463-- | Like 'evalListSplitAt' but evaluates both sublists in parallel.
462- parListSplitAt :: Int -> Strategy [a ] -> Strategy [a ] -> Strategy [a ]
464+ parListSplitAt :: Int -> Strategy' [a ] [ b ] -> Strategy' [a ] [ b ] -> Strategy' [a ] [ b ]
463465parListSplitAt n stratPref stratSuff = evalListSplitAt n (rparWith stratPref) (rparWith stratSuff)
464466
465467-- | Evaluate the first n elements of a list according to the given strategy.
@@ -491,7 +493,7 @@ parListNth n strat = evalListNth n (rparWith strat)
491493-- If the chunk size is 1 or less, 'parListChunk' is equivalent to
492494-- 'parList'
493495--
494- parListChunk :: Int -> Strategy a -> Strategy [a ]
496+ parListChunk :: Int -> Strategy' a b -> Strategy' [a ] [ b ]
495497parListChunk n strat xs
496498 | n <= 1 = parList strat xs
497499 | otherwise = concat `fmap` parList (evalList strat) (chunk n xs)
@@ -506,9 +508,9 @@ chunk n xs = as : chunk n bs where (as,bs) = splitAt n xs
506508-- | A combination of 'parList' and 'map', encapsulating a common pattern:
507509--
508510-- > parMap strat f = withStrategy (parList strat) . map f
509- --
511+ -- > parMap strat f = withStrategy (parList (strat . f))
510512parMap :: Strategy b -> (a -> b ) -> [a ] -> [b ]
511- parMap strat f = ( `using` parList strat) . map f
513+ parMap strat f = withStrategy ( parList ( strat . f))
512514
513515-- --------------------------------------------------------------------------
514516-- Strategies for lazy lists
@@ -535,7 +537,7 @@ evalBufferWHNF n0 xs0 = return (ret xs0 (start n0 xs0))
535537--
536538-- > evalBuffer n r0 == evalBuffer n rseq
537539--
538- evalBuffer :: Int -> Strategy a -> Strategy [a ]
540+ evalBuffer :: Int -> Strategy' a b -> Strategy' [a ] [ b ]
539541evalBuffer n strat = evalBufferWHNF n . map (withStrategy strat)
540542
541543-- Like evalBufferWHNF but sparks the list elements when pushing them
@@ -555,7 +557,7 @@ parBufferWHNF n0 xs0 = return (ret xs0 (start n0 xs0))
555557
556558-- | Like 'evalBuffer' but evaluates the list elements in parallel when
557559-- pushing them into the buffer.
558- parBuffer :: Int -> Strategy a -> Strategy [a ]
560+ parBuffer :: Int -> Strategy' a b -> Strategy' [a ] [ b ]
559561parBuffer n strat = parBufferWHNF n . map (withStrategy strat)
560562-- Alternative definition via evalBuffer (may compromise firing of RULES):
561563-- parBuffer n strat = evalBuffer n (rparWith strat)
@@ -573,109 +575,151 @@ parBuffer n strat = parBufferWHNF n . map (withStrategy strat)
573575-- --------------------------------------------------------------------------
574576-- Strategies for tuples
575577
576- evalTuple2 :: Strategy a -> Strategy b -> Strategy (a ,b )
578+ evalTuple2 :: Strategy' a a' -> Strategy' b b' -> Strategy' (a ,b ) ( a' , b' )
577579evalTuple2 strat1 strat2 (x1,x2) =
578580 pure (,) <*> strat1 x1 <*> strat2 x2
579581
580- evalTuple3 :: Strategy a -> Strategy b -> Strategy c -> Strategy (a ,b ,c )
582+ evalTuple3 :: Strategy' a a'
583+ -> Strategy' b b'
584+ -> Strategy' c c'
585+ -> Strategy' (a ,b ,c ) (a' ,b' ,c' )
581586evalTuple3 strat1 strat2 strat3 (x1,x2,x3) =
582587 pure (,,) <*> strat1 x1 <*> strat2 x2 <*> strat3 x3
583588
584- evalTuple4 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy (a ,b ,c ,d )
589+ evalTuple4 :: Strategy' a a'
590+ -> Strategy' b b'
591+ -> Strategy' c c'
592+ -> Strategy' d d'
593+ -> Strategy' (a ,b ,c ,d ) (a' ,b' ,c' ,d' )
585594evalTuple4 strat1 strat2 strat3 strat4 (x1,x2,x3,x4) =
586595 pure (,,,) <*> strat1 x1 <*> strat2 x2 <*> strat3 x3 <*> strat4 x4
587596
588- evalTuple5 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy (a ,b ,c ,d ,e )
597+ evalTuple5 :: Strategy' a a'
598+ -> Strategy' b b'
599+ -> Strategy' c c'
600+ -> Strategy' d d'
601+ -> Strategy' e e'
602+ -> Strategy' (a ,b ,c ,d ,e ) (a' ,b' ,c' ,d' ,e' )
589603evalTuple5 strat1 strat2 strat3 strat4 strat5 (x1,x2,x3,x4,x5) =
590604 pure (,,,,) <*> strat1 x1 <*> strat2 x2 <*> strat3 x3 <*> strat4 x4 <*> strat5 x5
591605
592- evalTuple6 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy (a ,b ,c ,d ,e ,f )
606+ evalTuple6 :: Strategy' a a'
607+ -> Strategy' b b'
608+ -> Strategy' c c'
609+ -> Strategy' d d'
610+ -> Strategy' e e'
611+ -> Strategy' f f'
612+ -> Strategy' (a ,b ,c ,d ,e ,f ) (a' ,b' ,c' ,d' ,e' ,f' )
593613evalTuple6 strat1 strat2 strat3 strat4 strat5 strat6 (x1,x2,x3,x4,x5,x6) =
594614 pure (,,,,,) <*> strat1 x1 <*> strat2 x2 <*> strat3 x3 <*> strat4 x4 <*> strat5 x5 <*> strat6 x6
595615
596- evalTuple7 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy g -> Strategy (a ,b ,c ,d ,e ,f ,g )
616+ evalTuple7 :: Strategy' a a'
617+ -> Strategy' b b'
618+ -> Strategy' c c'
619+ -> Strategy' d d'
620+ -> Strategy' e e'
621+ -> Strategy' f f'
622+ -> Strategy' g g'
623+ -> Strategy' (a ,b ,c ,d ,e ,f ,g ) (a' ,b' ,c' ,d' ,e' ,f' ,g' )
597624evalTuple7 strat1 strat2 strat3 strat4 strat5 strat6 strat7 (x1,x2,x3,x4,x5,x6,x7) =
598625 pure (,,,,,,) <*> strat1 x1 <*> strat2 x2 <*> strat3 x3 <*> strat4 x4 <*> strat5 x5 <*> strat6 x6 <*> strat7 x7
599626
600- evalTuple8 :: 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 )
627+ evalTuple8 :: Strategy' a a'
628+ -> Strategy' b b'
629+ -> Strategy' c c'
630+ -> Strategy' d d'
631+ -> Strategy' e e'
632+ -> Strategy' f f'
633+ -> Strategy' g g'
634+ -> Strategy' h h'
635+ -> Strategy' (a ,b ,c ,d ,e ,f ,g ,h ) (a' ,b' ,c' ,d' ,e' ,f' ,g' ,h' )
601636evalTuple8 strat1 strat2 strat3 strat4 strat5 strat6 strat7 strat8 (x1,x2,x3,x4,x5,x6,x7,x8) =
602637 pure (,,,,,,,) <*> strat1 x1 <*> strat2 x2 <*> strat3 x3 <*> strat4 x4 <*> strat5 x5 <*> strat6 x6 <*> strat7 x7 <*> strat8 x8
603638
604- evalTuple9 :: 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 )
639+ evalTuple9 :: Strategy' a a'
640+ -> Strategy' b b'
641+ -> Strategy' c c'
642+ -> Strategy' d d'
643+ -> Strategy' e e'
644+ -> Strategy' f f'
645+ -> Strategy' g g'
646+ -> Strategy' h h'
647+ -> Strategy' i i'
648+ -> Strategy' (a ,b ,c ,d ,e ,f ,g ,h ,i ) (a' ,b' ,c' ,d' ,e' ,f' ,g' ,h' ,i' )
605649evalTuple9 strat1 strat2 strat3 strat4 strat5 strat6 strat7 strat8 strat9 (x1,x2,x3,x4,x5,x6,x7,x8,x9) =
606650 pure (,,,,,,,,) <*> strat1 x1 <*> strat2 x2 <*> strat3 x3 <*> strat4 x4 <*> strat5 x5 <*> strat6 x6 <*> strat7 x7 <*> strat8 x8 <*> strat9 x9
607651
608- parTuple2 :: Strategy a -> Strategy b -> Strategy (a ,b )
652+ parTuple2 :: Strategy' a a' -> Strategy' b b' -> Strategy' (a ,b ) ( a' , b' )
609653parTuple2 strat1 strat2 =
610654 evalTuple2 (rparWith strat1) (rparWith strat2)
611655
612- parTuple3 :: Strategy a -> Strategy b -> Strategy c -> Strategy (a ,b ,c )
656+ parTuple3 :: Strategy' a a' -> Strategy' b b' -> Strategy' c c' -> Strategy' (a ,b ,c ) ( a' , b' , c' )
613657parTuple3 strat1 strat2 strat3 =
614658 evalTuple3 (rparWith strat1) (rparWith strat2) (rparWith strat3)
615659
616- parTuple4 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy (a ,b ,c ,d )
660+ parTuple4 :: Strategy' a a' -> Strategy' b b' -> Strategy' c c' -> Strategy' d d' -> Strategy' (a ,b ,c ,d ) ( a' , b' , c' , d' )
617661parTuple4 strat1 strat2 strat3 strat4 =
618662 evalTuple4 (rparWith strat1) (rparWith strat2) (rparWith strat3) (rparWith strat4)
619663
620- parTuple5 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy (a ,b ,c ,d ,e )
664+ parTuple5 :: Strategy' a a' -> Strategy' b b' -> Strategy' c c' -> Strategy' d d' -> Strategy' e e' -> Strategy' (a ,b ,c ,d ,e ) ( a' , b' , c' , d' , e' )
621665parTuple5 strat1 strat2 strat3 strat4 strat5 =
622666 evalTuple5 (rparWith strat1) (rparWith strat2) (rparWith strat3) (rparWith strat4) (rparWith strat5)
623667
624- parTuple6 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy (a ,b ,c ,d ,e ,f )
668+ parTuple6 :: Strategy' a a' -> Strategy' b b' -> Strategy' c c' -> Strategy' d d' -> Strategy' e e' -> Strategy' f f' -> Strategy' (a ,b ,c ,d ,e ,f ) ( a' , b' , c' , d' , e' , f' )
625669parTuple6 strat1 strat2 strat3 strat4 strat5 strat6 =
626670 evalTuple6 (rparWith strat1) (rparWith strat2) (rparWith strat3) (rparWith strat4) (rparWith strat5) (rparWith strat6)
627671
628- parTuple7 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy g -> Strategy (a ,b ,c ,d ,e ,f ,g )
672+ parTuple7 :: Strategy' a a' -> Strategy' b b' -> Strategy' c c' -> Strategy' d d' -> Strategy' e e' -> Strategy' f f' -> Strategy' g g' -> Strategy' (a ,b ,c ,d ,e ,f ,g ) ( a' , b' , c' , d' , e' , f' , g' )
629673parTuple7 strat1 strat2 strat3 strat4 strat5 strat6 strat7 =
630674 evalTuple7 (rparWith strat1) (rparWith strat2) (rparWith strat3) (rparWith strat4) (rparWith strat5) (rparWith strat6) (rparWith strat7)
631675
632- 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 )
676+ parTuple8 :: Strategy' a a' -> Strategy' b b' -> Strategy' c c' -> Strategy' d d' -> Strategy' e e' -> Strategy' f f' -> Strategy' g g' -> Strategy' h h' -> Strategy' (a ,b ,c ,d ,e ,f ,g ,h ) ( a' , b' , c' , d' , e' , f' , g' , h' )
633677parTuple8 strat1 strat2 strat3 strat4 strat5 strat6 strat7 strat8 =
634678 evalTuple8 (rparWith strat1) (rparWith strat2) (rparWith strat3) (rparWith strat4) (rparWith strat5) (rparWith strat6) (rparWith strat7) (rparWith strat8)
635679
636- 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 )
680+ parTuple9 :: Strategy' a a' -> Strategy' b b' -> Strategy' c c' -> Strategy' d d' -> Strategy' e e' -> Strategy' f f' -> Strategy' g g' -> Strategy' h h' -> Strategy' i i' -> Strategy' (a ,b ,c ,d ,e ,f ,g ,h ,i ) ( a' , b' , c' , d' , e' , f' , g' , h' , i' )
637681parTuple9 strat1 strat2 strat3 strat4 strat5 strat6 strat7 strat8 strat9 =
638682 evalTuple9 (rparWith strat1) (rparWith strat2) (rparWith strat3) (rparWith strat4) (rparWith strat5) (rparWith strat6) (rparWith strat7) (rparWith strat8) (rparWith strat9)
639683
640684-- --------------------------------------------------------------------------
641685-- Strategic function application
642686
643687{-
644- These are very handy when writing pipeline parallelism asa sequence of
688+ These are very handy when writing pipeline parallelism as a sequence of
645689@$@, @$|@ and @$||@'s. There is no need of naming intermediate values
646690in this case. The separation of algorithm from strategy is achieved by
647691allowing strategies only as second arguments to @$|@ and @$||@.
648692-}
649693
650694-- | Sequential function application. The argument is evaluated using
651695-- the given strategy before it is given to the function.
652- ($|) :: (a -> b ) -> Strategy a -> a -> b
696+ ($|) :: (b -> c ) -> Strategy' a b -> a -> c
653697f $| s = \ x -> let z = x `using` s in z `pseq` f z
654698
655699-- | Parallel function application. The argument is evaluated using
656700-- the given strategy, in parallel with the function application.
657- ($||) :: (a -> b ) -> Strategy a -> a -> b
701+ ($||) :: (b -> c ) -> Strategy' a b -> a -> c
658702f $|| s = \ x -> let z = x `using` s in z `par` f z
659703
660704-- | Sequential function composition. The result of
661705-- the second function is evaluated using the given strategy,
662706-- and then given to the first function.
663- (.|) :: (b -> c ) -> Strategy b -> (a -> b ) -> (a -> c )
707+ (.|) :: (c -> d ) -> Strategy' b c -> (a -> b ) -> (a -> d )
664708(.|) f s g = \ x -> let z = g x `using` s in
665709 z `pseq` f z
666710
667711-- | Parallel function composition. The result of the second
668712-- function is evaluated using the given strategy,
669713-- in parallel with the application of the first function.
670- (.||) :: (b -> c ) -> Strategy b -> (a -> b ) -> (a -> c )
714+ (.||) :: (c -> d ) -> Strategy' b c -> (a -> b ) -> (a -> d )
671715(.||) f s g = \ x -> let z = g x `using` s in
672716 z `par` f z
673717
674718-- | Sequential inverse function composition,
675719-- for those who read their programs from left to right.
676720-- The result of the first function is evaluated using the
677721-- given strategy, and then given to the second function.
678- (-|) :: (a -> b ) -> Strategy b -> (b -> c ) -> (a -> c )
722+ (-|) :: (a -> b ) -> Strategy' b c -> (c -> d ) -> (a -> d )
679723(-|) f s g = \ x -> let z = f x `using` s in
680724 z `pseq` g z
681725
@@ -684,15 +728,15 @@ f $|| s = \ x -> let z = x `using` s in z `par` f z
684728-- The result of the first function is evaluated using the
685729-- given strategy, in parallel with the application of the
686730-- second function.
687- (-||) :: (a -> b ) -> Strategy b -> (b -> c ) -> (a -> c )
731+ (-||) :: (a -> b ) -> Strategy' b c -> (c -> d ) -> (a -> d )
688732(-||) f s g = \ x -> let z = f x `using` s in
689733 z `par` g z
690734
691735-- -----------------------------------------------------------------------------
692736-- Old/deprecated stuff
693737
694738{-# DEPRECATED Done "The Strategy type is now a -> Eval a, not a -> Done" #-}
695- -- | DEPRECCATED : replaced by the 'Eval' monad
739+ -- | DEPRECATED : replaced by the 'Eval' monad
696740type Done = ()
697741
698742{-# DEPRECATED demanding "Use pseq or $| instead" #-}
0 commit comments