module Parrows.Skeletons.Topology where
import Control.Arrow
import Parrows.Definition
import Parrows.Future
import Parrows.Util
(|>>>|) :: (ArrowLoop arr, ArrowChoice arr,
ArrowLoopParallel arr (fut (([a], [b]), [c])) (fut (([a], [b]), [c])) (),
Future fut (([a], [b]), [c]) ()) =>
arr a b -> arr b c -> arr a c
(|>>>|) = pipe2 ()
pipe2 :: (ArrowLoop arr, ArrowChoice arr,
ArrowLoopParallel arr (fut (([a], [b]), [c])) (fut (([a], [b]), [c])) conf,
Future fut (([a], [b]), [c]) conf) =>
conf -> arr a b -> arr b c -> arr a c
pipe2 conf f g =
(arr return &&& arr (const [])) &&& arr (const []) >>>
pipe conf (replicate 2 (unify f g)) >>>
arr snd >>>
arr head
where
unify :: (ArrowChoice arr) => arr a b -> arr b c -> arr (([a], [b]), [c]) (([a], [b]), [c])
unify f' g' = (mapArr f' *** mapArr g') *** arr (const []) >>> arr (\((b, c), a) -> ((a, b), c))
pipe :: (ArrowLoop arr, ArrowLoopParallel arr (fut a) (fut a) conf, Future fut a conf) => conf -> [arr a a] -> arr a a
pipe conf fs = unliftFut conf (pipeSimple conf (map (liftFut conf) fs))
pipeSimple :: (ArrowLoop arr, ArrowLoopParallel arr a a conf) => conf -> [arr a a] -> arr a a
pipeSimple conf fs =
loop (arr snd &&&
(arr (uncurry (:) >>> lazy) >>> loopParEvalN conf fs)) >>>
arr last
ring :: (Future fut r conf,
ArrowLoop arr,
ArrowLoopParallel arr (i, fut r) (o, fut r) conf,
ArrowLoopParallel arr o o conf) =>
conf -> arr (i, r) (o, r) -> arr [i] [o]
ring conf f =
loop (second (rightRotate >>> lazy) >>>
arr (uncurry zip) >>>
loopParEvalN conf (repeat (second (get conf) >>> f >>> second (put conf))) >>>
arr unzip) >>>
postLoopParEvalN conf (repeat (arr id))
torus :: (Future fut a conf, Future fut b conf,
ArrowLoop arr, ArrowChoice arr,
ArrowLoopParallel arr (c, fut a, fut b) (d, fut a, fut b) conf,
ArrowLoopParallel arr [d] [d] conf) =>
conf -> arr (c, a, b) (d, a, b) -> arr [[c]] [[d]]
torus conf f =
loop (second ((mapArr rightRotate >>> lazy) *** (arr rightRotate >>> lazy)) >>>
arr (uncurry3 (zipWith3 lazyzip3)) >>>
arr length &&& (shuffle >>> loopParEvalN conf (repeat (ptorus conf f))) >>>
arr (uncurry unshuffle) >>>
arr (map unzip3) >>> arr unzip3 >>> threetotwo) >>>
postLoopParEvalN conf (repeat (arr id))
uncurry3 :: (a -> b -> c -> d) -> (a, (b, c)) -> d
uncurry3 f (a, (b, c)) = f a b c
lazyzip3 :: [a] -> [b] -> [c] -> [(a, b, c)]
lazyzip3 as bs cs = zip3 as (lazy bs) (lazy cs)
ptorus :: (Arrow arr, Future fut a conf, Future fut b conf) =>
conf ->
arr (c, a, b) (d, a, b) ->
arr (c, fut a, fut b) (d, fut a, fut b)
ptorus conf f = arr (\ ~(c, a, b) -> (c, get conf a, get conf b)) >>> f >>> arr (\ ~(d, a, b) -> (d, put conf a, put conf b))
threetotwo :: (Arrow arr) => arr (a, b, c) (a, (b, c))
threetotwo = arr $ \ ~(a, b, c) -> (a, (b, c))
twotothree :: (Arrow arr) => arr (a, (b, c)) (a, b, c)
twotothree = arr $ \ ~(a, (b, c)) -> (a, b, c)