#include "fusion-phases.h"
module Data.Array.Parallel.Unlifted.Parallel.Segmented (
replicateSUP, replicateRSUP, foldlSUP, foldSUP, sumSUP, sumRUP
) where
import Data.Array.Parallel.Unlifted.Sequential
import Data.Array.Parallel.Unlifted.Distributed
import Data.Array.Parallel.Unlifted.Parallel.Combinators (
mapUP, zipWithUP, packUP, combineUP)
import Data.Array.Parallel.Unlifted.Parallel.Sums (
sumUP )
import Data.Array.Parallel.Unlifted.Parallel.Basics (
replicateUP, repeatUP)
import Data.Array.Parallel.Unlifted.Parallel.Enum
import Data.Array.Parallel.Unlifted.Parallel.Permute ( bpermuteUP )
import Data.Array.Parallel.Base (
(:*:)(..), fstS, sndS, uncurryS, unsafe_unpairS)
replicateSUP :: UA a => USegd -> UArr a -> UArr a
replicateSUP segd xs = joinD theGang unbalanced
. mapD theGang (uncurryS replicateSU)
. zipD dsegd
$ splitAsD theGang (lengthUSegdD dsegd) xs
where
dsegd = splitSegdD theGang segd
replicateRSUP :: UA a => Int -> UArr a -> UArr a
replicateRSUP n xs = replicateSUP (lengthsToUSegd (replicateUP (lengthU xs) n)) xs
foldlSUP :: (UA a, UA b) => (b -> a -> b) -> b -> USegd -> UArr a -> UArr b
foldlSUP f z segd xs = joinD theGang unbalanced
(mapD theGang (uncurry (foldlSU f z) . unsafe_unpairS)
(zipD dsegd
(splitSD theGang dsegd xs)))
where
dsegd = splitSegdD theGang segd
foldSUP :: (UA a, UA b) => (b -> a -> b) -> b -> USegd -> UArr a -> UArr b
foldSUP = foldlSUP
sumSUP :: (Num e, UA e) => USegd -> UArr e -> UArr e
sumSUP = foldSUP (+) 0
sumRUP :: (Num e, UA e) => Int -> Int -> UArr e -> UArr e
sumRUP = foldRUP (+) 0
foldRUP :: (UA a, UA b) => (b -> a -> b) -> b -> Int -> Int -> UArr a -> UArr b
foldRUP f z noOfSegs segSize xs =
joinD theGang unbalanced
(zipWithD theGang
(\noS -> \xss -> foldlRU f z noS segSize xss)
(splitLenD theGang noOfSegs)
(splitAsD theGang
(mapD theGang (*segSize) (splitLenD theGang noOfSegs))
xs))