{-# LANGUAGE BangPatterns, CPP, MagicHash, UnboxedTuples #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE RecursiveDo #-}
module Control.Parallel.Strategies (
Strategy
, using
, withStrategy
, usingIO
, withStrategyIO
, dot
, r0
, rseq
, rdeepseq
, rpar
, rparWith
, evalSeq
, SeqStrategy
, evalTraversable
, parTraversable
, parFmap
, evalList
, parList
, evalListN
, parListN
, evalListNth
, parListNth
, evalListSplitAt
, parListSplitAt
, parListChunk
, parMap
, evalBuffer
, parBuffer
, evalTuple2
, evalTuple3
, evalTuple4
, evalTuple5
, evalTuple6
, evalTuple7
, evalTuple8
, evalTuple9
, parTuple2
, parTuple3
, parTuple4
, parTuple5
, parTuple6
, parTuple7
, parTuple8
, parTuple9
, ($|)
, ($||)
, (.|)
, (.||)
, (-|)
, (-||)
, Eval
, parEval
, runEval
, runEvalIO
,
Done, demanding, sparking, (>|), (>||),
rwhnf, unEval,
seqTraverse, parTraverse,
seqList,
seqPair, parPair,
seqTriple, parTriple,
NFData
) where
#if defined(__MHS__) || !MIN_VERSION_base(4,8,0)
import Data.Traversable
#endif
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative
#endif
import Control.Parallel
import Control.DeepSeq (NFData(rnf))
import Control.Monad.Fix (MonadFix (..))
#if defined(__GLASGOW_HASKELL__) && MIN_VERSION_base(4,4,0)
import System.IO.Unsafe (unsafeDupablePerformIO)
import Control.Exception (evaluate)
#else
import System.IO.Unsafe (unsafePerformIO)
import Control.Monad
#endif
import qualified Control.Seq
#ifdef __GLASGOW_HASKELL__
import GHC.Exts
import GHC.IO (IO (..))
#endif
infixr 9 `dot`
infixl 0 `using`
infixl 0 `usingIO`
#if __GLASGOW_HASKELL__ >= 702
newtype Eval a = Eval {forall a. Eval a -> IO a
unEval_ :: IO a}
deriving ((forall a b. (a -> b) -> Eval a -> Eval b)
-> (forall a b. a -> Eval b -> Eval a) -> Functor Eval
forall a b. a -> Eval b -> Eval a
forall a b. (a -> b) -> Eval a -> Eval b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> Eval a -> Eval b
fmap :: forall a b. (a -> b) -> Eval a -> Eval b
$c<$ :: forall a b. a -> Eval b -> Eval a
<$ :: forall a b. a -> Eval b -> Eval a
Functor, Functor Eval
Functor Eval =>
(forall a. a -> Eval a)
-> (forall a b. Eval (a -> b) -> Eval a -> Eval b)
-> (forall a b c. (a -> b -> c) -> Eval a -> Eval b -> Eval c)
-> (forall a b. Eval a -> Eval b -> Eval b)
-> (forall a b. Eval a -> Eval b -> Eval a)
-> Applicative Eval
forall a. a -> Eval a
forall a b. Eval a -> Eval b -> Eval a
forall a b. Eval a -> Eval b -> Eval b
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall a b c. (a -> b -> c) -> Eval a -> Eval b -> Eval c
forall (f :: * -> *).
Functor f =>
(forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
$cpure :: forall a. a -> Eval a
pure :: forall a. a -> Eval a
$c<*> :: forall a b. Eval (a -> b) -> Eval a -> Eval b
<*> :: forall a b. Eval (a -> b) -> Eval a -> Eval b
$cliftA2 :: forall a b c. (a -> b -> c) -> Eval a -> Eval b -> Eval c
liftA2 :: forall a b c. (a -> b -> c) -> Eval a -> Eval b -> Eval c
$c*> :: forall a b. Eval a -> Eval b -> Eval b
*> :: forall a b. Eval a -> Eval b -> Eval b
$c<* :: forall a b. Eval a -> Eval b -> Eval a
<* :: forall a b. Eval a -> Eval b -> Eval a
Applicative, Applicative Eval
Applicative Eval =>
(forall a b. Eval a -> (a -> Eval b) -> Eval b)
-> (forall a b. Eval a -> Eval b -> Eval b)
-> (forall a. a -> Eval a)
-> Monad Eval
forall a. a -> Eval a
forall a b. Eval a -> Eval b -> Eval b
forall a b. Eval a -> (a -> Eval b) -> Eval b
forall (m :: * -> *).
Applicative m =>
(forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
$c>>= :: forall a b. Eval a -> (a -> Eval b) -> Eval b
>>= :: forall a b. Eval a -> (a -> Eval b) -> Eval b
$c>> :: forall a b. Eval a -> Eval b -> Eval b
>> :: forall a b. Eval a -> Eval b -> Eval b
$creturn :: forall a. a -> Eval a
return :: forall a. a -> Eval a
Monad)
runEval :: Eval a -> a
# if MIN_VERSION_base(4,4,0)
runEval :: forall a. Eval a -> a
runEval = IO a -> a
forall a. IO a -> a
unsafeDupablePerformIO (IO a -> a) -> (Eval a -> IO a) -> Eval a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Eval a -> IO a
forall a. Eval a -> IO a
unEval_
# else
runEval = unsafePerformIO . unEval_
# endif
runEvalIO :: Eval a -> IO a
runEvalIO :: forall a. Eval a -> IO a
runEvalIO = Eval a -> IO a
forall a. Eval a -> IO a
unEval_
instance MonadFix Eval where
mfix :: forall a. (a -> Eval a) -> Eval a
mfix a -> Eval a
k = IO a -> Eval a
forall a. IO a -> Eval a
Eval (IO a -> Eval a) -> IO a -> Eval a
forall a b. (a -> b) -> a -> b
$ (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, a #)) -> IO a)
-> (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
forall a b. (a -> b) -> a -> b
$ \ State# RealWorld
s ->
let ans :: Evret a
ans = Eval a -> State# RealWorld -> Evret a
forall a. Eval a -> State# RealWorld -> Evret a
liftEv (a -> Eval a
k a
r) State# RealWorld
s
Evret State# RealWorld
_ a
r = Evret a
ans
in
case Evret a
ans of Evret State# RealWorld
s' a
x -> (# State# RealWorld
s', a
x #)
data Evret a = Evret (State# RealWorld) a
liftEv :: Eval a -> State# RealWorld -> Evret a
liftEv :: forall a. Eval a -> State# RealWorld -> Evret a
liftEv (Eval (IO State# RealWorld -> (# State# RealWorld, a #)
m)) = \State# RealWorld
s -> case State# RealWorld -> (# State# RealWorld, a #)
m State# RealWorld
s of (# State# RealWorld
s', a
r #) -> State# RealWorld -> a -> Evret a
forall a. State# RealWorld -> a -> Evret a
Evret State# RealWorld
s' a
r
#else
data Eval a = Done a
runEval :: Eval a -> a
runEval (Done x) = x
runEvalIO :: Eval a -> IO a
runEvalIO (Done x) = return x
instance Functor Eval where
fmap = liftM
instance Applicative Eval where
pure = Done
(<*>) = ap
instance Monad Eval where
return = pure
# ifdef __GLASGOW_HASKELL__
Done x >>= k = lazy (k x)
# else
Done x >>= k = k x
# endif
instance MonadFix Eval where
mfix f = let r = f (runEval r) in r
{-# RULES "lazy Done" forall x . lazy (Done x) = Done x #-}
#endif
type Strategy a = a -> Eval a
using :: a -> Strategy a -> a
a
x using :: forall a. a -> Strategy a -> a
`using` Strategy a
strat = Eval a -> a
forall a. Eval a -> a
runEval (Strategy a
strat a
x)
withStrategy :: Strategy a -> a -> a
withStrategy :: forall a. Strategy a -> a -> a
withStrategy = (a -> Strategy a -> a) -> Strategy a -> a -> a
forall a b c. (a -> b -> c) -> b -> a -> c
flip a -> Strategy a -> a
forall a. a -> Strategy a -> a
using
usingIO :: a -> Strategy a -> IO a
a
x usingIO :: forall a. a -> Strategy a -> IO a
`usingIO` Strategy a
strat = Eval a -> IO a
forall a. Eval a -> IO a
runEvalIO (Strategy a
strat a
x)
withStrategyIO :: Strategy a -> a -> IO a
withStrategyIO :: forall a. Strategy a -> a -> IO a
withStrategyIO = (a -> Strategy a -> IO a) -> Strategy a -> a -> IO a
forall a b c. (a -> b -> c) -> b -> a -> c
flip a -> Strategy a -> IO a
forall a. a -> Strategy a -> IO a
usingIO
{-# DEPRECATED dot "'dot' is an unintuitive composition operator. Use 'Control.Monad.<=<` instead." #-}
dot :: Strategy a -> Strategy a -> Strategy a
Strategy a
strat2 dot :: forall a. Strategy a -> Strategy a -> Strategy a
`dot` Strategy a
strat1 = Strategy a
strat2 Strategy a -> (a -> a) -> Strategy a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Eval a -> a
forall a. Eval a -> a
runEval (Eval a -> a) -> Strategy a -> a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Strategy a
strat1
evalSeq :: SeqStrategy a -> Strategy a
evalSeq :: forall a. SeqStrategy a -> Strategy a
evalSeq SeqStrategy a
strat a
x = SeqStrategy a
strat a
x () -> Eval a -> Eval a
forall a b. a -> b -> b
`pseq` a -> Eval a
forall a. a -> Eval a
forall (m :: * -> *) a. Monad m => a -> m a
return a
x
type SeqStrategy a = Control.Seq.Strategy a
r0 :: Strategy a
r0 :: forall a. a -> Eval a
r0 a
x = a -> Eval a
forall a. a -> Eval a
forall (m :: * -> *) a. Monad m => a -> m a
return a
x
rseq :: Strategy a
#if __GLASGOW_HASKELL__ >= 702
rseq :: forall a. a -> Eval a
rseq a
x = IO a -> Eval a
forall a. IO a -> Eval a
Eval (a -> IO a
forall a. a -> IO a
evaluate a
x)
#else
rseq x = x `seq` return x
#endif
{-# NOINLINE [1] rseq #-}
rdeepseq :: NFData a => Strategy a
rdeepseq :: forall a. NFData a => Strategy a
rdeepseq a
x = do Strategy ()
forall a. a -> Eval a
rseq (a -> ()
forall a. NFData a => a -> ()
rnf a
x); a -> Eval a
forall a. a -> Eval a
forall (m :: * -> *) a. Monad m => a -> m a
return a
x
rpar :: Strategy a
#ifdef __GLASGOW_HASKELL__
#if __GLASGOW_HASKELL__ >= 702
rpar :: forall a. a -> Eval a
rpar a
x = IO a -> Eval a
forall a. IO a -> Eval a
Eval (IO a -> Eval a) -> IO a -> Eval a
forall a b. (a -> b) -> a -> b
$ (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO ((State# RealWorld -> (# State# RealWorld, a #)) -> IO a)
-> (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s -> a -> State# RealWorld -> (# State# RealWorld, a #)
forall a d. a -> State# d -> (# State# d, a #)
spark# a
x State# RealWorld
s
#else
rpar x = case (par# x) of _ -> Done x
#endif
#else
rpar x = case par x () of () -> Done x
#endif
{-# INLINE rpar #-}
rparWith :: Strategy a -> Strategy a
rparWith :: forall a. Strategy a -> Strategy a
rparWith Strategy a
strat = Eval a -> Eval a
forall a. Eval a -> Eval a
parEval (Eval a -> Eval a) -> Strategy a -> Strategy a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Strategy a
strat
parEval :: Eval a -> Eval a
parEval :: forall a. Eval a -> Eval a
parEval Eval a
m = do
Lift a
l <- Strategy (Lift a)
forall a. a -> Eval a
rpar Lift a
r
a -> Eval a
forall a. a -> Eval a
forall (m :: * -> *) a. Monad m => a -> m a
return (case Lift a
l of Lift a
x -> a
x)
where
r :: Lift a
r = Eval (Lift a) -> Lift a
forall a. Eval a -> a
runEval (a -> Lift a
forall a. a -> Lift a
Lift (a -> Lift a) -> Eval a -> Eval (Lift a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Eval a
m)
data Lift a = Lift a
evalTraversable :: Traversable t => Strategy a -> Strategy (t a)
evalTraversable :: forall (t :: * -> *) a.
Traversable t =>
Strategy a -> Strategy (t a)
evalTraversable = (a -> Eval a) -> t a -> Eval (t a)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b)
traverse
{-# INLINE evalTraversable #-}
parTraversable :: Traversable t => Strategy a -> Strategy (t a)
parTraversable :: forall (t :: * -> *) a.
Traversable t =>
Strategy a -> Strategy (t a)
parTraversable Strategy a
strat = Strategy a -> Strategy (t a)
forall (t :: * -> *) a.
Traversable t =>
Strategy a -> Strategy (t a)
evalTraversable (Strategy a -> Strategy a
forall a. Strategy a -> Strategy a
rparWith Strategy a
strat)
{-# INLINE parTraversable #-}
evalList :: Strategy a -> Strategy [a]
evalList :: forall a. Strategy a -> Strategy [a]
evalList = Strategy a -> Strategy [a]
forall (t :: * -> *) a.
Traversable t =>
Strategy a -> Strategy (t a)
evalTraversable
parList :: Strategy a -> Strategy [a]
parList :: forall a. Strategy a -> Strategy [a]
parList = Strategy a -> Strategy [a]
forall (t :: * -> *) a.
Traversable t =>
Strategy a -> Strategy (t a)
parTraversable
evalListSplitAt :: Int -> Strategy [a] -> Strategy [a] -> Strategy [a]
evalListSplitAt :: forall a. Int -> Strategy [a] -> Strategy [a] -> Strategy [a]
evalListSplitAt Int
n Strategy [a]
stratPref Strategy [a]
stratSuff [a]
xs
= let ([a]
ys,[a]
zs) = Int -> [a] -> ([a], [a])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
n [a]
xs in
Strategy [a]
stratPref [a]
ys Eval [a] -> Strategy [a] -> Eval [a]
forall a b. Eval a -> (a -> Eval b) -> Eval b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \[a]
ys' ->
Strategy [a]
stratSuff [a]
zs Eval [a] -> Strategy [a] -> Eval [a]
forall a b. Eval a -> (a -> Eval b) -> Eval b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \[a]
zs' ->
Strategy [a]
forall a. a -> Eval a
forall (m :: * -> *) a. Monad m => a -> m a
return ([a]
ys' [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ [a]
zs')
parListSplitAt :: Int -> Strategy [a] -> Strategy [a] -> Strategy [a]
parListSplitAt :: forall a. Int -> Strategy [a] -> Strategy [a] -> Strategy [a]
parListSplitAt Int
n Strategy [a]
stratPref Strategy [a]
stratSuff = Int -> Strategy [a] -> Strategy [a] -> Strategy [a]
forall a. Int -> Strategy [a] -> Strategy [a] -> Strategy [a]
evalListSplitAt Int
n (Strategy [a] -> Strategy [a]
forall a. Strategy a -> Strategy a
rparWith Strategy [a]
stratPref) (Strategy [a] -> Strategy [a]
forall a. Strategy a -> Strategy a
rparWith Strategy [a]
stratSuff)
evalListN :: Int -> Strategy a -> Strategy [a]
evalListN :: forall a. Int -> Strategy a -> Strategy [a]
evalListN Int
n Strategy a
strat = Int -> Strategy [a] -> Strategy [a] -> Strategy [a]
forall a. Int -> Strategy [a] -> Strategy [a] -> Strategy [a]
evalListSplitAt Int
n (Strategy a -> Strategy [a]
forall a. Strategy a -> Strategy [a]
evalList Strategy a
strat) Strategy [a]
forall a. a -> Eval a
r0
parListN :: Int -> Strategy a -> Strategy [a]
parListN :: forall a. Int -> Strategy a -> Strategy [a]
parListN Int
n Strategy a
strat = Int -> Strategy a -> Strategy [a]
forall a. Int -> Strategy a -> Strategy [a]
evalListN Int
n (Strategy a -> Strategy a
forall a. Strategy a -> Strategy a
rparWith Strategy a
strat)
evalListNth :: Int -> Strategy a -> Strategy [a]
evalListNth :: forall a. Int -> Strategy a -> Strategy [a]
evalListNth Int
n Strategy a
strat = Int -> Strategy [a] -> Strategy [a] -> Strategy [a]
forall a. Int -> Strategy [a] -> Strategy [a] -> Strategy [a]
evalListSplitAt Int
n Strategy [a]
forall a. a -> Eval a
r0 (Int -> Strategy a -> Strategy [a]
forall a. Int -> Strategy a -> Strategy [a]
evalListN Int
1 Strategy a
strat)
parListNth :: Int -> Strategy a -> Strategy [a]
parListNth :: forall a. Int -> Strategy a -> Strategy [a]
parListNth Int
n Strategy a
strat = Int -> Strategy a -> Strategy [a]
forall a. Int -> Strategy a -> Strategy [a]
evalListNth Int
n (Strategy a -> Strategy a
forall a. Strategy a -> Strategy a
rparWith Strategy a
strat)
parListChunk :: Int -> Strategy a -> Strategy [a]
parListChunk :: forall a. Int -> Strategy a -> Strategy [a]
parListChunk Int
n Strategy a
strat
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
1 = Strategy a -> Strategy [a]
forall a. Strategy a -> Strategy [a]
parList Strategy a
strat
| Bool
otherwise = Strategy [a]
go
where
go :: Strategy [a]
go [] = Strategy [a]
forall a. a -> Eval a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
go [a]
as = mdo
[a]
bs <- Strategy [a]
forall a. a -> Eval a
rpar Strategy [a] -> Strategy [a]
forall a b. (a -> b) -> a -> b
$ Eval [a] -> [a]
forall a. Eval a -> a
runEval (Eval [a] -> [a]) -> Eval [a] -> [a]
forall a b. (a -> b) -> a -> b
$ Strategy a -> [a] -> Int -> Strategy [a]
forall a. Strategy a -> [a] -> Int -> Strategy [a]
evalChunk Strategy a
strat [a]
more Int
n [a]
as
[a]
more <- Strategy [a]
go (Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
drop Int
n [a]
as)
Strategy [a]
forall a. a -> Eval a
forall (m :: * -> *) a. Monad m => a -> m a
return [a]
bs
evalChunk :: Strategy a -> [a] -> Int -> Strategy [a]
evalChunk :: forall a. Strategy a -> [a] -> Int -> Strategy [a]
evalChunk Strategy a
strat = \[a]
end ->
let
go :: t -> Strategy [a]
go !t
_n [] = Strategy [a]
forall a. a -> Eval a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [a]
end
go t
0 [a]
_ = Strategy [a]
forall a. a -> Eval a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [a]
end
go t
n (a
a:[a]
as) = (:) (a -> [a] -> [a]) -> Eval a -> Eval ([a] -> [a])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Strategy a
strat a
a Eval ([a] -> [a]) -> Eval [a] -> Eval [a]
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> t -> Strategy [a]
go (t
n t -> t -> t
forall a. Num a => a -> a -> a
- t
1) [a]
as
in Int -> Strategy [a]
forall {t}. (Eq t, Num t) => t -> Strategy [a]
go
parMap :: Strategy b -> (a -> b) -> [a] -> [b]
parMap :: forall b a. Strategy b -> (a -> b) -> [a] -> [b]
parMap Strategy b
strat a -> b
f = ([b] -> Strategy [b] -> [b]
forall a. a -> Strategy a -> a
`using` Strategy b -> Strategy [b]
forall a. Strategy a -> Strategy [a]
parList Strategy b
strat) ([b] -> [b]) -> ([a] -> [b]) -> [a] -> [b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> b) -> [a] -> [b]
forall a b. (a -> b) -> [a] -> [b]
map a -> b
f
parFmap :: Traversable t => Strategy b -> (a -> b) -> t a -> t b
parFmap :: forall (t :: * -> *) b a.
Traversable t =>
Strategy b -> (a -> b) -> t a -> t b
parFmap Strategy b
strat a -> b
f = (t b -> Strategy (t b) -> t b
forall a. a -> Strategy a -> a
`using` Strategy b -> Strategy (t b)
forall (t :: * -> *) a.
Traversable t =>
Strategy a -> Strategy (t a)
parTraversable Strategy b
strat) (t b -> t b) -> (t a -> t b) -> t a -> t b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> b) -> t a -> t b
forall a b. (a -> b) -> t a -> t b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f
evalBuffer :: Int -> Strategy a -> Strategy [a]
evalBuffer :: forall a. Int -> Strategy a -> Strategy [a]
evalBuffer Int
n0 Strategy a
strat [a]
xs0 = [a] -> Eval [a]
forall a. a -> Eval a
forall (m :: * -> *) a. Monad m => a -> m a
return ([a] -> [a] -> [a]
forall {a} {a}. [a] -> [a] -> [a]
ret [a]
tied (Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
drop Int
n0 [a]
tied))
where
tied :: [a]
tied = (a -> [a] -> [a]) -> [a] -> [a] -> [a]
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr a -> [a] -> [a]
go [] [a]
xs0
where
go :: a -> [a] -> [a]
go a
x [a]
r = Eval [a] -> [a]
forall a. Eval a -> a
runEval ((a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
r) (a -> [a]) -> Eval a -> Eval [a]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Strategy a
strat a
x)
ret :: [a] -> [a] -> [a]
ret (a
x : [a]
xs) (a
_y : [a]
ys) = a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a] -> [a] -> [a]
ret [a]
xs [a]
ys
ret [a]
xs [a]
_ = [a]
xs
parBuffer :: Int -> Strategy a -> Strategy [a]
parBuffer :: forall a. Int -> Strategy a -> Strategy [a]
parBuffer Int
n Strategy a
strat = Int -> Strategy a -> Strategy [a]
forall a. Int -> Strategy a -> Strategy [a]
evalBuffer Int
n (Strategy a -> Strategy a
forall a. Strategy a -> Strategy a
rparWith Strategy a
strat)
evalTuple2 :: Strategy a -> Strategy b -> Strategy (a,b)
evalTuple2 :: forall a b. Strategy a -> Strategy b -> Strategy (a, b)
evalTuple2 Strategy a
strat1 Strategy b
strat2 (a
x1,b
x2) =
(a -> b -> (a, b)) -> Eval (a -> b -> (a, b))
forall a. a -> Eval a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (,) Eval (a -> b -> (a, b)) -> Eval a -> Eval (b -> (a, b))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy a
strat1 a
x1 Eval (b -> (a, b)) -> Eval b -> Eval (a, b)
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy b
strat2 b
x2
evalTuple3 :: Strategy a -> Strategy b -> Strategy c -> Strategy (a,b,c)
evalTuple3 :: forall a b c.
Strategy a -> Strategy b -> Strategy c -> Strategy (a, b, c)
evalTuple3 Strategy a
strat1 Strategy b
strat2 Strategy c
strat3 (a
x1,b
x2,c
x3) =
(a -> b -> c -> (a, b, c)) -> Eval (a -> b -> c -> (a, b, c))
forall a. a -> Eval a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (,,) Eval (a -> b -> c -> (a, b, c))
-> Eval a -> Eval (b -> c -> (a, b, c))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy a
strat1 a
x1 Eval (b -> c -> (a, b, c)) -> Eval b -> Eval (c -> (a, b, c))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy b
strat2 b
x2 Eval (c -> (a, b, c)) -> Eval c -> Eval (a, b, c)
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy c
strat3 c
x3
evalTuple4 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy (a,b,c,d)
evalTuple4 :: forall a b c d.
Strategy a
-> Strategy b -> Strategy c -> Strategy d -> Strategy (a, b, c, d)
evalTuple4 Strategy a
strat1 Strategy b
strat2 Strategy c
strat3 Strategy d
strat4 (a
x1,b
x2,c
x3,d
x4) =
(a -> b -> c -> d -> (a, b, c, d))
-> Eval (a -> b -> c -> d -> (a, b, c, d))
forall a. a -> Eval a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (,,,) Eval (a -> b -> c -> d -> (a, b, c, d))
-> Eval a -> Eval (b -> c -> d -> (a, b, c, d))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy a
strat1 a
x1 Eval (b -> c -> d -> (a, b, c, d))
-> Eval b -> Eval (c -> d -> (a, b, c, d))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy b
strat2 b
x2 Eval (c -> d -> (a, b, c, d)) -> Eval c -> Eval (d -> (a, b, c, d))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy c
strat3 c
x3 Eval (d -> (a, b, c, d)) -> Eval d -> Eval (a, b, c, d)
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy d
strat4 d
x4
evalTuple5 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy (a,b,c,d,e)
evalTuple5 :: forall a b c d e.
Strategy a
-> Strategy b
-> Strategy c
-> Strategy d
-> Strategy e
-> Strategy (a, b, c, d, e)
evalTuple5 Strategy a
strat1 Strategy b
strat2 Strategy c
strat3 Strategy d
strat4 Strategy e
strat5 (a
x1,b
x2,c
x3,d
x4,e
x5) =
(a -> b -> c -> d -> e -> (a, b, c, d, e))
-> Eval (a -> b -> c -> d -> e -> (a, b, c, d, e))
forall a. a -> Eval a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (,,,,) Eval (a -> b -> c -> d -> e -> (a, b, c, d, e))
-> Eval a -> Eval (b -> c -> d -> e -> (a, b, c, d, e))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy a
strat1 a
x1 Eval (b -> c -> d -> e -> (a, b, c, d, e))
-> Eval b -> Eval (c -> d -> e -> (a, b, c, d, e))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy b
strat2 b
x2 Eval (c -> d -> e -> (a, b, c, d, e))
-> Eval c -> Eval (d -> e -> (a, b, c, d, e))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy c
strat3 c
x3 Eval (d -> e -> (a, b, c, d, e))
-> Eval d -> Eval (e -> (a, b, c, d, e))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy d
strat4 d
x4 Eval (e -> (a, b, c, d, e)) -> Eval e -> Eval (a, b, c, d, e)
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy e
strat5 e
x5
evalTuple6 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy (a,b,c,d,e,f)
evalTuple6 :: forall a b c d e f.
Strategy a
-> Strategy b
-> Strategy c
-> Strategy d
-> Strategy e
-> Strategy f
-> Strategy (a, b, c, d, e, f)
evalTuple6 Strategy a
strat1 Strategy b
strat2 Strategy c
strat3 Strategy d
strat4 Strategy e
strat5 Strategy f
strat6 (a
x1,b
x2,c
x3,d
x4,e
x5,f
x6) =
(a -> b -> c -> d -> e -> f -> (a, b, c, d, e, f))
-> Eval (a -> b -> c -> d -> e -> f -> (a, b, c, d, e, f))
forall a. a -> Eval a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (,,,,,) Eval (a -> b -> c -> d -> e -> f -> (a, b, c, d, e, f))
-> Eval a -> Eval (b -> c -> d -> e -> f -> (a, b, c, d, e, f))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy a
strat1 a
x1 Eval (b -> c -> d -> e -> f -> (a, b, c, d, e, f))
-> Eval b -> Eval (c -> d -> e -> f -> (a, b, c, d, e, f))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy b
strat2 b
x2 Eval (c -> d -> e -> f -> (a, b, c, d, e, f))
-> Eval c -> Eval (d -> e -> f -> (a, b, c, d, e, f))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy c
strat3 c
x3 Eval (d -> e -> f -> (a, b, c, d, e, f))
-> Eval d -> Eval (e -> f -> (a, b, c, d, e, f))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy d
strat4 d
x4 Eval (e -> f -> (a, b, c, d, e, f))
-> Eval e -> Eval (f -> (a, b, c, d, e, f))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy e
strat5 e
x5 Eval (f -> (a, b, c, d, e, f)) -> Eval f -> Eval (a, b, c, d, e, f)
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy f
strat6 f
x6
evalTuple7 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy g -> Strategy (a,b,c,d,e,f,g)
evalTuple7 :: forall a b c d e f g.
Strategy a
-> Strategy b
-> Strategy c
-> Strategy d
-> Strategy e
-> Strategy f
-> Strategy g
-> Strategy (a, b, c, d, e, f, g)
evalTuple7 Strategy a
strat1 Strategy b
strat2 Strategy c
strat3 Strategy d
strat4 Strategy e
strat5 Strategy f
strat6 Strategy g
strat7 (a
x1,b
x2,c
x3,d
x4,e
x5,f
x6,g
x7) =
(a -> b -> c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
-> Eval (a -> b -> c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
forall a. a -> Eval a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (,,,,,,) Eval (a -> b -> c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
-> Eval a
-> Eval (b -> c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy a
strat1 a
x1 Eval (b -> c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
-> Eval b -> Eval (c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy b
strat2 b
x2 Eval (c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
-> Eval c -> Eval (d -> e -> f -> g -> (a, b, c, d, e, f, g))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy c
strat3 c
x3 Eval (d -> e -> f -> g -> (a, b, c, d, e, f, g))
-> Eval d -> Eval (e -> f -> g -> (a, b, c, d, e, f, g))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy d
strat4 d
x4 Eval (e -> f -> g -> (a, b, c, d, e, f, g))
-> Eval e -> Eval (f -> g -> (a, b, c, d, e, f, g))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy e
strat5 e
x5 Eval (f -> g -> (a, b, c, d, e, f, g))
-> Eval f -> Eval (g -> (a, b, c, d, e, f, g))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy f
strat6 f
x6 Eval (g -> (a, b, c, d, e, f, g))
-> Eval g -> Eval (a, b, c, d, e, f, g)
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy g
strat7 g
x7
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)
evalTuple8 :: forall a b c d e f g h.
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)
evalTuple8 Strategy a
strat1 Strategy b
strat2 Strategy c
strat3 Strategy d
strat4 Strategy e
strat5 Strategy f
strat6 Strategy g
strat7 Strategy h
strat8 (a
x1,b
x2,c
x3,d
x4,e
x5,f
x6,g
x7,h
x8) =
(a -> b -> c -> d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
-> Eval
(a -> b -> c -> d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
forall a. a -> Eval a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (,,,,,,,) Eval
(a -> b -> c -> d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
-> Eval a
-> Eval
(b -> c -> d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy a
strat1 a
x1 Eval (b -> c -> d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
-> Eval b
-> Eval (c -> d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy b
strat2 b
x2 Eval (c -> d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
-> Eval c
-> Eval (d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy c
strat3 c
x3 Eval (d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
-> Eval d -> Eval (e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy d
strat4 d
x4 Eval (e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
-> Eval e -> Eval (f -> g -> h -> (a, b, c, d, e, f, g, h))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy e
strat5 e
x5 Eval (f -> g -> h -> (a, b, c, d, e, f, g, h))
-> Eval f -> Eval (g -> h -> (a, b, c, d, e, f, g, h))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy f
strat6 f
x6 Eval (g -> h -> (a, b, c, d, e, f, g, h))
-> Eval g -> Eval (h -> (a, b, c, d, e, f, g, h))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy g
strat7 g
x7 Eval (h -> (a, b, c, d, e, f, g, h))
-> Eval h -> Eval (a, b, c, d, e, f, g, h)
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy h
strat8 h
x8
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)
evalTuple9 :: forall a b c d e f g h i.
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)
evalTuple9 Strategy a
strat1 Strategy b
strat2 Strategy c
strat3 Strategy d
strat4 Strategy e
strat5 Strategy f
strat6 Strategy g
strat7 Strategy h
strat8 Strategy i
strat9 (a
x1,b
x2,c
x3,d
x4,e
x5,f
x6,g
x7,h
x8,i
x9) =
(a
-> b
-> c
-> d
-> e
-> f
-> g
-> h
-> i
-> (a, b, c, d, e, f, g, h, i))
-> Eval
(a
-> b
-> c
-> d
-> e
-> f
-> g
-> h
-> i
-> (a, b, c, d, e, f, g, h, i))
forall a. a -> Eval a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (,,,,,,,,) Eval
(a
-> b
-> c
-> d
-> e
-> f
-> g
-> h
-> i
-> (a, b, c, d, e, f, g, h, i))
-> Eval a
-> Eval
(b
-> c -> d -> e -> f -> g -> h -> i -> (a, b, c, d, e, f, g, h, i))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy a
strat1 a
x1 Eval
(b
-> c -> d -> e -> f -> g -> h -> i -> (a, b, c, d, e, f, g, h, i))
-> Eval b
-> Eval
(c -> d -> e -> f -> g -> h -> i -> (a, b, c, d, e, f, g, h, i))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy b
strat2 b
x2 Eval
(c -> d -> e -> f -> g -> h -> i -> (a, b, c, d, e, f, g, h, i))
-> Eval c
-> Eval (d -> e -> f -> g -> h -> i -> (a, b, c, d, e, f, g, h, i))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy c
strat3 c
x3 Eval (d -> e -> f -> g -> h -> i -> (a, b, c, d, e, f, g, h, i))
-> Eval d
-> Eval (e -> f -> g -> h -> i -> (a, b, c, d, e, f, g, h, i))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy d
strat4 d
x4 Eval (e -> f -> g -> h -> i -> (a, b, c, d, e, f, g, h, i))
-> Eval e -> Eval (f -> g -> h -> i -> (a, b, c, d, e, f, g, h, i))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy e
strat5 e
x5 Eval (f -> g -> h -> i -> (a, b, c, d, e, f, g, h, i))
-> Eval f -> Eval (g -> h -> i -> (a, b, c, d, e, f, g, h, i))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy f
strat6 f
x6 Eval (g -> h -> i -> (a, b, c, d, e, f, g, h, i))
-> Eval g -> Eval (h -> i -> (a, b, c, d, e, f, g, h, i))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy g
strat7 g
x7 Eval (h -> i -> (a, b, c, d, e, f, g, h, i))
-> Eval h -> Eval (i -> (a, b, c, d, e, f, g, h, i))
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy h
strat8 h
x8 Eval (i -> (a, b, c, d, e, f, g, h, i))
-> Eval i -> Eval (a, b, c, d, e, f, g, h, i)
forall a b. Eval (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Strategy i
strat9 i
x9
parTuple2 :: Strategy a -> Strategy b -> Strategy (a,b)
parTuple2 :: forall a b. Strategy a -> Strategy b -> Strategy (a, b)
parTuple2 Strategy a
strat1 Strategy b
strat2 =
Strategy a -> Strategy b -> Strategy (a, b)
forall a b. Strategy a -> Strategy b -> Strategy (a, b)
evalTuple2 (Strategy a -> Strategy a
forall a. Strategy a -> Strategy a
rparWith Strategy a
strat1) (Strategy b -> Strategy b
forall a. Strategy a -> Strategy a
rparWith Strategy b
strat2)
parTuple3 :: Strategy a -> Strategy b -> Strategy c -> Strategy (a,b,c)
parTuple3 :: forall a b c.
Strategy a -> Strategy b -> Strategy c -> Strategy (a, b, c)
parTuple3 Strategy a
strat1 Strategy b
strat2 Strategy c
strat3 =
Strategy a -> Strategy b -> Strategy c -> Strategy (a, b, c)
forall a b c.
Strategy a -> Strategy b -> Strategy c -> Strategy (a, b, c)
evalTuple3 (Strategy a -> Strategy a
forall a. Strategy a -> Strategy a
rparWith Strategy a
strat1) (Strategy b -> Strategy b
forall a. Strategy a -> Strategy a
rparWith Strategy b
strat2) (Strategy c -> Strategy c
forall a. Strategy a -> Strategy a
rparWith Strategy c
strat3)
parTuple4 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy (a,b,c,d)
parTuple4 :: forall a b c d.
Strategy a
-> Strategy b -> Strategy c -> Strategy d -> Strategy (a, b, c, d)
parTuple4 Strategy a
strat1 Strategy b
strat2 Strategy c
strat3 Strategy d
strat4 =
Strategy a
-> Strategy b -> Strategy c -> Strategy d -> Strategy (a, b, c, d)
forall a b c d.
Strategy a
-> Strategy b -> Strategy c -> Strategy d -> Strategy (a, b, c, d)
evalTuple4 (Strategy a -> Strategy a
forall a. Strategy a -> Strategy a
rparWith Strategy a
strat1) (Strategy b -> Strategy b
forall a. Strategy a -> Strategy a
rparWith Strategy b
strat2) (Strategy c -> Strategy c
forall a. Strategy a -> Strategy a
rparWith Strategy c
strat3) (Strategy d -> Strategy d
forall a. Strategy a -> Strategy a
rparWith Strategy d
strat4)
parTuple5 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy (a,b,c,d,e)
parTuple5 :: forall a b c d e.
Strategy a
-> Strategy b
-> Strategy c
-> Strategy d
-> Strategy e
-> Strategy (a, b, c, d, e)
parTuple5 Strategy a
strat1 Strategy b
strat2 Strategy c
strat3 Strategy d
strat4 Strategy e
strat5 =
Strategy a
-> Strategy b
-> Strategy c
-> Strategy d
-> Strategy e
-> Strategy (a, b, c, d, e)
forall a b c d e.
Strategy a
-> Strategy b
-> Strategy c
-> Strategy d
-> Strategy e
-> Strategy (a, b, c, d, e)
evalTuple5 (Strategy a -> Strategy a
forall a. Strategy a -> Strategy a
rparWith Strategy a
strat1) (Strategy b -> Strategy b
forall a. Strategy a -> Strategy a
rparWith Strategy b
strat2) (Strategy c -> Strategy c
forall a. Strategy a -> Strategy a
rparWith Strategy c
strat3) (Strategy d -> Strategy d
forall a. Strategy a -> Strategy a
rparWith Strategy d
strat4) (Strategy e -> Strategy e
forall a. Strategy a -> Strategy a
rparWith Strategy e
strat5)
parTuple6 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy (a,b,c,d,e,f)
parTuple6 :: forall a b c d e f.
Strategy a
-> Strategy b
-> Strategy c
-> Strategy d
-> Strategy e
-> Strategy f
-> Strategy (a, b, c, d, e, f)
parTuple6 Strategy a
strat1 Strategy b
strat2 Strategy c
strat3 Strategy d
strat4 Strategy e
strat5 Strategy f
strat6 =
Strategy a
-> Strategy b
-> Strategy c
-> Strategy d
-> Strategy e
-> Strategy f
-> Strategy (a, b, c, d, e, f)
forall a b c d e f.
Strategy a
-> Strategy b
-> Strategy c
-> Strategy d
-> Strategy e
-> Strategy f
-> Strategy (a, b, c, d, e, f)
evalTuple6 (Strategy a -> Strategy a
forall a. Strategy a -> Strategy a
rparWith Strategy a
strat1) (Strategy b -> Strategy b
forall a. Strategy a -> Strategy a
rparWith Strategy b
strat2) (Strategy c -> Strategy c
forall a. Strategy a -> Strategy a
rparWith Strategy c
strat3) (Strategy d -> Strategy d
forall a. Strategy a -> Strategy a
rparWith Strategy d
strat4) (Strategy e -> Strategy e
forall a. Strategy a -> Strategy a
rparWith Strategy e
strat5) (Strategy f -> Strategy f
forall a. Strategy a -> Strategy a
rparWith Strategy f
strat6)
parTuple7 :: Strategy a -> Strategy b -> Strategy c -> Strategy d -> Strategy e -> Strategy f -> Strategy g -> Strategy (a,b,c,d,e,f,g)
parTuple7 :: forall a b c d e f g.
Strategy a
-> Strategy b
-> Strategy c
-> Strategy d
-> Strategy e
-> Strategy f
-> Strategy g
-> Strategy (a, b, c, d, e, f, g)
parTuple7 Strategy a
strat1 Strategy b
strat2 Strategy c
strat3 Strategy d
strat4 Strategy e
strat5 Strategy f
strat6 Strategy g
strat7 =
Strategy a
-> Strategy b
-> Strategy c
-> Strategy d
-> Strategy e
-> Strategy f
-> Strategy g
-> Strategy (a, b, c, d, e, f, g)
forall a b c d e f g.
Strategy a
-> Strategy b
-> Strategy c
-> Strategy d
-> Strategy e
-> Strategy f
-> Strategy g
-> Strategy (a, b, c, d, e, f, g)
evalTuple7 (Strategy a -> Strategy a
forall a. Strategy a -> Strategy a
rparWith Strategy a
strat1) (Strategy b -> Strategy b
forall a. Strategy a -> Strategy a
rparWith Strategy b
strat2) (Strategy c -> Strategy c
forall a. Strategy a -> Strategy a
rparWith Strategy c
strat3) (Strategy d -> Strategy d
forall a. Strategy a -> Strategy a
rparWith Strategy d
strat4) (Strategy e -> Strategy e
forall a. Strategy a -> Strategy a
rparWith Strategy e
strat5) (Strategy f -> Strategy f
forall a. Strategy a -> Strategy a
rparWith Strategy f
strat6) (Strategy g -> Strategy g
forall a. Strategy a -> Strategy a
rparWith Strategy g
strat7)
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)
parTuple8 :: forall a b c d e f g h.
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)
parTuple8 Strategy a
strat1 Strategy b
strat2 Strategy c
strat3 Strategy d
strat4 Strategy e
strat5 Strategy f
strat6 Strategy g
strat7 Strategy h
strat8 =
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)
forall a b c d e f g h.
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)
evalTuple8 (Strategy a -> Strategy a
forall a. Strategy a -> Strategy a
rparWith Strategy a
strat1) (Strategy b -> Strategy b
forall a. Strategy a -> Strategy a
rparWith Strategy b
strat2) (Strategy c -> Strategy c
forall a. Strategy a -> Strategy a
rparWith Strategy c
strat3) (Strategy d -> Strategy d
forall a. Strategy a -> Strategy a
rparWith Strategy d
strat4) (Strategy e -> Strategy e
forall a. Strategy a -> Strategy a
rparWith Strategy e
strat5) (Strategy f -> Strategy f
forall a. Strategy a -> Strategy a
rparWith Strategy f
strat6) (Strategy g -> Strategy g
forall a. Strategy a -> Strategy a
rparWith Strategy g
strat7) (Strategy h -> Strategy h
forall a. Strategy a -> Strategy a
rparWith Strategy h
strat8)
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)
parTuple9 :: forall a b c d e f g h i.
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)
parTuple9 Strategy a
strat1 Strategy b
strat2 Strategy c
strat3 Strategy d
strat4 Strategy e
strat5 Strategy f
strat6 Strategy g
strat7 Strategy h
strat8 Strategy i
strat9 =
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)
forall a b c d e f g h i.
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)
evalTuple9 (Strategy a -> Strategy a
forall a. Strategy a -> Strategy a
rparWith Strategy a
strat1) (Strategy b -> Strategy b
forall a. Strategy a -> Strategy a
rparWith Strategy b
strat2) (Strategy c -> Strategy c
forall a. Strategy a -> Strategy a
rparWith Strategy c
strat3) (Strategy d -> Strategy d
forall a. Strategy a -> Strategy a
rparWith Strategy d
strat4) (Strategy e -> Strategy e
forall a. Strategy a -> Strategy a
rparWith Strategy e
strat5) (Strategy f -> Strategy f
forall a. Strategy a -> Strategy a
rparWith Strategy f
strat6) (Strategy g -> Strategy g
forall a. Strategy a -> Strategy a
rparWith Strategy g
strat7) (Strategy h -> Strategy h
forall a. Strategy a -> Strategy a
rparWith Strategy h
strat8) (Strategy i -> Strategy i
forall a. Strategy a -> Strategy a
rparWith Strategy i
strat9)
($|) :: (a -> b) -> Strategy a -> a -> b
a -> b
f $| :: forall a b. (a -> b) -> Strategy a -> a -> b
$| Strategy a
s = \a
x -> Eval b -> b
forall a. Eval a -> a
runEval (a -> b
f (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Strategy a
s a
x)
($||) :: (a -> b) -> Strategy a -> a -> b
a -> b
f $|| :: forall a b. (a -> b) -> Strategy a -> a -> b
$|| Strategy a
s = \a
x -> Eval b -> b
forall a. Eval a -> a
runEval (a -> b
f (a -> b) -> Eval a -> Eval b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Strategy a -> Strategy a
forall a. Strategy a -> Strategy a
rparWith Strategy a
s a
x)
(.|) :: (b -> c) -> Strategy b -> (a -> b) -> (a -> c)
.| :: forall b c a. (b -> c) -> Strategy b -> (a -> b) -> a -> c
(.|) b -> c
f Strategy b
s a -> b
g = \a
x -> Eval c -> c
forall a. Eval a -> a
runEval (b -> c
f (b -> c) -> Eval b -> Eval c
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Strategy b
s (a -> b
g a
x))
(.||) :: (b -> c) -> Strategy b -> (a -> b) -> (a -> c)
.|| :: forall b c a. (b -> c) -> Strategy b -> (a -> b) -> a -> c
(.||) b -> c
f Strategy b
s a -> b
g = \a
x -> Eval c -> c
forall a. Eval a -> a
runEval (b -> c
f (b -> c) -> Eval b -> Eval c
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Strategy b -> Strategy b
forall a. Strategy a -> Strategy a
rparWith Strategy b
s (a -> b
g a
x))
(-|) :: (a -> b) -> Strategy b -> (b -> c) -> (a -> c)
-| :: forall a b c. (a -> b) -> Strategy b -> (b -> c) -> a -> c
(-|) a -> b
f Strategy b
s b -> c
g = \a
x -> Eval c -> c
forall a. Eval a -> a
runEval (b -> c
g (b -> c) -> Eval b -> Eval c
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Strategy b
s (a -> b
f a
x))
(-||) :: (a -> b) -> Strategy b -> (b -> c) -> (a -> c)
-|| :: forall a b c. (a -> b) -> Strategy b -> (b -> c) -> a -> c
(-||) a -> b
f Strategy b
s b -> c
g = \a
x -> Eval c -> c
forall a. Eval a -> a
runEval (b -> c
g (b -> c) -> Eval b -> Eval c
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Strategy b -> Strategy b
forall a. Strategy a -> Strategy a
rparWith Strategy b
s (a -> b
f a
x))
{-# DEPRECATED Done "The Strategy type is now a -> Eval a, not a -> Done" #-}
type Done = ()
{-# DEPRECATED demanding "Use 'pseq' or '$|' instead" #-}
demanding :: a -> Done -> a
demanding :: forall a. a -> () -> a
demanding = (() -> a -> a) -> a -> () -> a
forall a b c. (a -> b -> c) -> b -> a -> c
flip () -> a -> a
forall a b. a -> b -> b
pseq
{-# DEPRECATED sparking "Use 'par' or '$||' instead" #-}
sparking :: a -> Done -> a
sparking :: forall a. a -> () -> a
sparking = (() -> a -> a) -> a -> () -> a
forall a b c. (a -> b -> c) -> b -> a -> c
flip () -> a -> a
forall a b. a -> b -> b
par
{-# DEPRECATED (>|) "Use 'pseq' or '$|' instead" #-}
(>|) :: Done -> Done -> Done
>| :: () -> () -> ()
(>|) = () -> () -> ()
forall a b. a -> b -> b
Prelude.seq
{-# DEPRECATED (>||) "Use 'par' or '$||' instead" #-}
(>||) :: Done -> Done -> Done
>|| :: () -> () -> ()
(>||) = () -> () -> ()
forall a b. a -> b -> b
par
{-# DEPRECATED rwhnf "renamed to 'rseq'" #-}
rwhnf :: Strategy a
rwhnf :: forall a. a -> Eval a
rwhnf = Strategy a
forall a. a -> Eval a
rseq
{-# DEPRECATED seqTraverse "renamed to 'evalTraversable'" #-}
seqTraverse :: Traversable t => Strategy a -> Strategy (t a)
seqTraverse :: forall (t :: * -> *) a.
Traversable t =>
Strategy a -> Strategy (t a)
seqTraverse = Strategy a -> Strategy (t a)
forall (t :: * -> *) a.
Traversable t =>
Strategy a -> Strategy (t a)
evalTraversable
{-# DEPRECATED parTraverse "renamed to 'parTraversable'" #-}
parTraverse :: Traversable t => Strategy a -> Strategy (t a)
parTraverse :: forall (t :: * -> *) a.
Traversable t =>
Strategy a -> Strategy (t a)
parTraverse = Strategy a -> Strategy (t a)
forall (t :: * -> *) a.
Traversable t =>
Strategy a -> Strategy (t a)
parTraversable
{-# DEPRECATED seqList "renamed to 'evalList'" #-}
seqList :: Strategy a -> Strategy [a]
seqList :: forall a. Strategy a -> Strategy [a]
seqList = Strategy a -> Strategy [a]
forall a. Strategy a -> Strategy [a]
evalList
{-# DEPRECATED seqPair "renamed to 'evalTuple2'" #-}
seqPair :: Strategy a -> Strategy b -> Strategy (a,b)
seqPair :: forall a b. Strategy a -> Strategy b -> Strategy (a, b)
seqPair = Strategy a -> Strategy b -> Strategy (a, b)
forall a b. Strategy a -> Strategy b -> Strategy (a, b)
evalTuple2
{-# DEPRECATED parPair "renamed to 'parTuple2'" #-}
parPair :: Strategy a -> Strategy b -> Strategy (a,b)
parPair :: forall a b. Strategy a -> Strategy b -> Strategy (a, b)
parPair = Strategy a -> Strategy b -> Strategy (a, b)
forall a b. Strategy a -> Strategy b -> Strategy (a, b)
parTuple2
{-# DEPRECATED seqTriple "renamed to 'evalTuple3'" #-}
seqTriple :: Strategy a -> Strategy b -> Strategy c -> Strategy (a,b,c)
seqTriple :: forall a b c.
Strategy a -> Strategy b -> Strategy c -> Strategy (a, b, c)
seqTriple = Strategy a -> Strategy b -> Strategy c -> Strategy (a, b, c)
forall a b c.
Strategy a -> Strategy b -> Strategy c -> Strategy (a, b, c)
evalTuple3
{-# DEPRECATED parTriple "renamed to 'parTuple3'" #-}
parTriple :: Strategy a -> Strategy b -> Strategy c -> Strategy (a,b,c)
parTriple :: forall a b c.
Strategy a -> Strategy b -> Strategy c -> Strategy (a, b, c)
parTriple = Strategy a -> Strategy b -> Strategy c -> Strategy (a, b, c)
forall a b c.
Strategy a -> Strategy b -> Strategy c -> Strategy (a, b, c)
parTuple3
{-# DEPRECATED unEval "renamed to 'runEval'" #-}
unEval :: Eval a -> a
unEval :: forall a. Eval a -> a
unEval = Eval a -> a
forall a. Eval a -> a
runEval