Merging two sorted list in parallel ( dph )

149 views
Skip to first unread message

mukesh tiwari

unread,
Jan 29, 2012, 7:26:16 AM1/29/12
to parallel-haskell
Hello All
I am trying to merge two lists in parallel. I have two sorted list
( [ ( i , j , val ) ] ) . Lists are sorted on j and for same j ,
sorted on i . If the two list contains same ( i , j ) then their
values are added and combined into one . If first contain ( i , j ,
val_1 ) and second contains ( i , j , val_2 ) then combining two will
result ( i , j , val_1 + val_2 ). Merging is highly sequential and
after searching , I found this paper (alecu.ase.ro/articles/
ie_en_2004.pdf ). The idea from this paper is binary search to get
the rank of elements in the final list. Let say we are at Ith position
in the first list so we have ( I - 1 ) elements are lesser than the
current element in first list and perform binary search for this
element's position in second list ( say this position is J ). So the
position of our current element in final list will be I + J - 1 ( I -
1 + J - 1 + 1 ). I wrote a Haskell code using dph-par for this but
there is not documentation (
http://hackage.haskell.org/packages/archive/dph-par/0.5.1.1/doc/html/Data-Array-Parallel.html
) so I am kind of stuck with update. I have two list
l_1 = [ ( 1 , 1 , 1 ) , ( 2 , 1 , 1) , ( 4 , 1 , 1 ) , ( 1 , 4 , 1 ) ,
( 2 , 4 , 1 ) , ( 4 ,4 , 1 ) ]
l_2 = [ ( 1 , 1 , 1 ) , ( 3 , 1 , 1 ) , ( 4 , 1 , 1) , ( 1 , 4 , 1 ) ,
( 3 , 4 , 1 ) , ( 4 , 4 , 1 ) ]

and after updating these two lists , we should have
l_3 = [ ( 1 , 1 , 2 ) , ( 2 , 1 , 1 ) , ( 3 , 1 , 1) , ( 4 , 1 , 2 ) ,
( 1 , 4 , 2 ) , ( 2 , 4 , 2 ) , ( 3 , 4 , 1 ) , ( 4 , 4 , 2) ]

I wrote a this Haskell code for Bsearch.hs
{-# LANGUAGE ParallelArrays #-}
{-# OPTIONS_GHC -fvectorise #-}

module Bsearch ( interfaceSparse ) where
import qualified Data.Array.Parallel as P
import Data.Array.Parallel.PArray
import qualified Data.Array.Parallel.Prelude as Pre
import qualified Data.Array.Parallel.Prelude.Int as I
import qualified Data.Array.Parallel.Prelude.Double as D



bSearch :: ( I.Int , I.Int , D.Double ) -> [: ( I.Int , I.Int ,
D.Double ) :] -> I.Int
bSearch elem@( i , j , val ) xs = ret where
ret = helpBsearch 0 len where
len = P.lengthP xs
helpBsearch :: I.Int -> I.Int -> I.Int
helpBsearch lo hi
| lo I.>= hi = lo
| cond = helpBsearch ( mid I.+ 1 ) hi
| otherwise = helpBsearch lo mid
where mid = I.div ( lo I.+ hi ) 2
( i' , j' , val' ) = xs P.!: mid
cond = case () of
_| j' I.< j Pre.|| ( j I.== j' Pre.&& i' I.<
i ) -> True
| otherwise -> False

bSearchFun :: [: ( I.Int , I.Int , D.Double ) :] -> [: ( I.Int ,
I.Int , D.Double ) :] -> [: I.Int :]
bSearchFun xs ys = P.mapP ( \( x , y ) -> x I.+ y ) ( P.indexedP
( P.mapP ( \x -> bSearch x ys ) xs ) )

bSearchMain :: [: ( I.Int , I.Int , D.Double ) :] -> [: ( I.Int ,
I.Int , D.Double ) :] -> [: ( I.Int , ( I.Int , I.Int ,
D.Double ) ) :]
bSearchMain xs ys = l_1 where --here change l_2 for second list
lst = [: bSearchFun xs ys , bSearchFun ys xs :]
first = lst P.!: 0
second = lst P.!: 1
l_1 = P.zipP first xs
l_2 = P.zipP second ys




interfaceSparse :: PArray ( Int , Int , Double ) -> PArray ( Int ,
Int , Double ) -> PArray ( Int , ( Int , Int , Double ) )
{-# NOINLINE interfaceSparse #-}
interfaceSparse xs ys = P.toPArrayP ( bSearchMain ( P.fromPArrayP
xs ) ( P.fromPArrayP ys ) )

Main.hs

module Main where
import Bsearch
import qualified Data.Array.Parallel.PArray as P
import Data.List


main = do
let
l_1 = P.fromList $ ( [ ( 1 , 1 , 1 ) , ( 2 , 1 , 1) , ( 4 ,
1 , 1 ) , ( 1 , 4 , 1 ) ,( 2 , 4 , 1 ) , ( 4 ,4 , 1 ) ] ::
[ ( Int ,Int , Double ) ] )
l_2 = P.fromList $ ( [ ( 1 , 1 , 1 ) , ( 3 , 1 , 1 ) , ( 4 ,
1 , 1) , ( 1 , 4 , 1 ) , ( 3 , 4 , 1 ) , ( 4 , 4 , 1 ) ] :: [ ( Int ,
Int , Double )] )
e = interfaceSparse l_1 l_2
print e

[ntro@localhost parBsearch]$ ghc -c -Odph -fdph-par -fforce-recomp
Bsearch.hs
[ntro@localhost parBsearch]$ ghc -c -Odph -fdph-par -fforce-recomp
Main.hs
[ntro@localhost parBsearch]$ ghc -o Bsearch -threaded -rtsopts -fdph-
par Main.o Bsearch.o


[ntro@localhost parBsearch]$ ./Bsearch --first list
fromList<PArray> [(0,(1,1,1.0)),(2,(2,1,1.0)),(4,(4,1,1.0)),(6,
(1,4,1.0)),(8,(2,4,1.0)),(10,(4,4,1.0))]
[ntro@localhost parBsearch]$ ./Bsearch -- second list
fromList<PArray> [(0,(1,1,1.0)),(3,(3,1,1.0)),(4,(4,1,1.0)),(6,
(1,4,1.0)),(9,(3,4,1.0)),(10,(4,4,1.0))]

Could some one please tell me how to merge these two list. I need some
thing like this

updateWithFun :: ( a -> a -> a ) -> [: ( Int , a ) :] -> [: a :] ->
[: a :]

This function will take a function which will take one value from [:
( Int , a ) :] and second value from list [: a :] at index Int and
update the list [: a :] at Int index. I tried to do something like
this
l_3 = P.updateP ( P.replicateP 11 ( 0 , 0 , 0) ) l_1
l_4 = P.updateP l_3 l_2
However the contents at given position are over written and not
updated. Sorry for this long post but I want to make myself clear.

Regards
Mukesh Tiwari

P.S. Also There are lot of parallel programmers here so could some
one please suggest me something better to merge lists in parallel. I
think this method involves lot of data movement.
Reply all
Reply to author
Forward
0 new messages