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

Antoine Latter aslatter at gmail.com
Sat Sep 24 18:14:31 CEST 2011


2011/9/24 Burak Ekici <ekcburak at hotmail.com>:
> 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
>

This isn't an area I'm expert in, but your strategy looks off to me -
since you're not using 'a', 'b', 'c' and 'd' anywhere, it would make
sense that you're not seeing much speedup. Also, the strategy doesn't
seem to be doing anything with it's input, which looks different from
most of the examples I've seen.

In summary, your strategy doesn't appear to have anything relating it
to the computation you're doing with the `using`, if that makes any
sense.



>
> Thanks a lot,
> Burak.
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>



More information about the Haskell-Cafe mailing list