[Haskell-cafe] A Missing Issue on Second Generation Strategies
Burak Ekici
ekcburak at hotmail.com
Sat Sep 24 18:46:39 CEST 2011
Thanks a lot for the quick answer.
Accordingly, I have just changed the code into below one, however
sparks are still being pruned.
Do you have any other ideas?
Bests,
Burak.
------
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
(rpar `dot` rdeepseq) (ersa (PUB n e) firstPart1)
(rpar `dot` rdeepseq) (ersa (PUB n e) firstPart2)
(rpar `dot` rdeepseq) (ersa (PUB n e) secondPart1)
(rpar `dot` rdeepseq) (ersa (PUB n e) secondPart2)
rdeepseq res
-----
> From: aslatter at gmail.com
> Date: Sat, 24 Sep 2011 11:19:49 -0500
> Subject: Re: [Haskell-cafe] A Missing Issue on Second Generation Strategies
> To: ekcburak at hotmail.com
> CC: haskell-cafe at haskell.org
>
> On Sat, Sep 24, 2011 at 11:14 AM, Antoine Latter <aslatter at gmail.com> wrote:
> > 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.
> >
>
> May a better way to phrase things is that your strategy never does
> anything to its input (like force any parts of it to evaluate), it
> merely sparks of computations that no one ever looks at. Which is why
> they get pruned.
>
> >
> >
> >>
> >> Thanks a lot,
> >> Burak.
> >>
> >>
> >>
> >> _______________________________________________
> >> Haskell-Cafe mailing list
> >> Haskell-Cafe at haskell.org
> >> http://www.haskell.org/mailman/listinfo/haskell-cafe
> >>
> >>
> >
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110924/b197fa72/attachment.htm>
More information about the Haskell-Cafe
mailing list