#include "fusion-phases.h"
module Data.Array.Parallel.Unlifted.Sequential.USel
(
USel2(..)
, mkUSel2
, lengthUSel2
, tagsUSel2, indicesUSel2
, elementsUSel2_0, elementsUSel2_1
, tagsToIndices2)
where
import Data.Array.Parallel.Unlifted.Sequential.Vector as V
import qualified Data.Vector.Fusion.Stream as S
import Data.Vector.Fusion.Stream.Monadic ( Stream(..) )
import Data.Array.Parallel.Base (Tag)
data USel2
= USel2
{ usel2_tags :: !(Vector Tag)
, usel2_indices :: !(Vector Int)
, usel2_elements0 :: !Int
, usel2_elements1 :: !Int
}
mkUSel2 :: Vector Tag
-> Vector Int
-> Int
-> Int
-> USel2
mkUSel2 = USel2
lengthUSel2 :: USel2 -> Int
lengthUSel2 = V.length . usel2_tags
tagsUSel2 :: USel2 -> Vector Tag
tagsUSel2 = usel2_tags
indicesUSel2 :: USel2 -> Vector Int
indicesUSel2 = usel2_indices
elementsUSel2_0 :: USel2 -> Int
elementsUSel2_0 = usel2_elements0
elementsUSel2_1 :: USel2 -> Int
elementsUSel2_1 = usel2_elements1
tagsToIndices2 :: Vector Tag -> Vector Int
tagsToIndices2 tags
= unstream (mapAccumS add (0,0) (stream tags))
where
add (i,j) 0 = ((i+1,j),i)
add (i,j) _ = ((i,j+1),j)
mapAccumS :: (acc -> a -> (acc,b)) -> acc -> S.Stream a -> S.Stream b
mapAccumS f acc0 (Stream step s0 n)
= Stream step' (acc0,s0) n
where
step' (acc,s)
= do r <- step s
case r of
S.Yield x s' -> let (acc',y) = f acc x
in return $ S.Yield y (acc',s')
S.Skip s' -> return $ S.Skip (acc,s')
S.Done -> return S.Done