[Haskell-cafe] A Missing Issue on Second Generation Strategies

Daniel Fischer daniel.is.fischer at googlemail.com
Sat Sep 24 18:51:47 CEST 2011


On Saturday 24 September 2011, 18:01:10, Burak Ekici wrote:
> Dear List,
> 
> I am trying to parallelize RSA encryption and decryption by using below
> manner, but when I run executable output file with "+RTS -s -N2"
> command on Windows 7, output stats say 4 sparks are being created
> however none of them converted into real OS threads.
> 
> -- SPARKS :4 (0 converted, 4 pruned) --
> 
> I was thinking that the problem could occur due to lack of forcing
> parallelization but, as far as I know 'rdeepseq' works for that aim.
> 
> Briefly, I could not solve the issue why parallelization was not being
> implemented. I would be appreciated if any of you shed a light on the
> issue that I missed.
> 
> Here is the mentioned part of code:
> 
> split4ToEnc :: RSAPublicKey -> [Integer] -> [Integer]
> split4ToEnc (PUB n e) []     = []
> split4ToEnc (PUB n e) (x:xs) =
>  ((ersa (PUB n e) secondPart2) ++ (ersa (PUB n e) secondPart1) ++ (ersa
> (PUB n e) firstPart2) ++ (ersa (PUB n e) firstPart1)) `using` strategy
> where
>   firstPart1  = fst (Main.splitAt((length (x:xs)) `div` 4)
> (fst(Main.splitAt ((length (x:xs)) `div` 2) (x:xs)))) firstPart2  = snd
> (Main.splitAt((length (x:xs)) `div` 4) (fst(Main.splitAt ((length
> (x:xs)) `div` 2) (x:xs)))) secondPart1  = fst (Main.splitAt((length
> (x:xs)) `div` 4) (snd(Main.splitAt ((length (x:xs)) `div` 2) (x:xs))))
> secondPart2  = snd (Main.splitAt((length (x:xs)) `div` 4)
> (snd(Main.splitAt ((length (x:xs)) `div` 2) (x:xs)))) strategy res = do
>                   a <- rpar (ersa (PUB n e) (firstPart1) `using`
> rdeepseq) b <- rpar (ersa (PUB n e) (firstPart2) `using` rdeepseq) c <-
> rpar (ersa (PUB n e) (secondPart1) `using` rdeepseq) d <- rpar (ersa
> (PUB n e) (secondPart2) `using` rdeepseq) rdeepseq res

First, you are doing a lot of unnecessary recalculation, calculate the 
length once and reuse it, also the parts of input and output lists.
If you don't give a name to the parts of your result, the strategy looks 
completely unrelated to the result to the compiler, hence no gain (if 
you're unlucky, they might be computed twice).

split4ToEnc key [] = []
split4ToEnc key xs = d' ++ c' ++ b' ++ a'
 -- don't need (x:xs), after matching [] failed that's the only possibility
 -- and the first element isn't used
  where
    len = length xs
    (firstHalf,secondHalf) = splitAt (len `quot` 2) xs
    (firstPart1,firstPart2) = splitAt (len `quot` 4) firstHalf
    (secondPart1,secondPart2) = splitAt (len `quot` 4) secondHalf
    a = ersa key firstPart1
    b = ersa key firstPart2
    c = ersa key secondPart1
    d = ersa key secondPart2
    (a',b',c',d') 
      = (a,b,c,d) `using` parTuple4 rdeepseq rdeepseq rdeepseq rdeepseq

should give you some parallelism. People familiar with the topic can 
probably suggest better strategies.



More information about the Haskell-Cafe mailing list