[Haskell-cafe] Karatsuba Multiplication Parallel

Burak Ekici ekcburak at hotmail.com
Fri Sep 16 13:22:34 CEST 2011


Excuse me, in the last post I forgot to send the last version of the code
and some some needed functions.

So sorry for spamming.

Here is the code:

import Control.Parallel
import Control.Parallel.Strategies
import Control.DeepSeq
------

type Strategy a = a -> Main.Eval a

data Eval a = Done a

instance Monad Main.Eval where
    return x = Main.Done x
    Main.Done x >>= k = k x

runEval :: Main.Eval a -> a
runEval (Main.Done a) = a

using :: a -> Main.Strategy a -> a
x `using` strat = Main.runEval (strat x)

rseq :: Main.Strategy a
rseq x = x `pseq` Main.Done x
-- runEval(rseq 100) = 100
--  :t rseq 100 :: Num a => Eval a

rdeepseq :: NFData a => Main.Strategy a
rdeepseq x = rnf x `pseq` return x

rpar :: Main.Strategy a
rpar x = x `par` Main.Done x
-- runEval(rpar 100) = 100
-- :t rpar 100 :: Num a => Eval a

dot :: Main.Strategy a -> Main.Strategy a -> Main.Strategy a
strat2 `dot` strat1 = strat2 . Main.runEval . strat1

------

normalize [] = []
normalize (False : xs) = 
  let ns = normalize xs
  in if ns == [] then [] else (False : ns)
normalize (True : xs) = True : (normalize xs)

mul [] _ = []
mul (False : xs) ys = False : (mul xs ys)
mul (True : xs) ys = mul (False : xs) ys `add` ys

addc [] ys ci = add ys (normalize [ci])
addc xs [] ci = add xs (normalize [ci])
addc (x : xs) (y : ys) ci = 
  let s = xor (xor x y) ci
      co = (x && y) || ((x || y) && ci) 
      a = (addc xs ys co)
  in if s == False && a == [] then [] else s : a

add [] ys = ys
add xs [] = xs
add xs ys = addc xs ys False

subc xs [] ci = sub xs (normalize [ci])
subc (x : xs) (y : ys) ci = 
  let d = xor (xor x (not y)) (not ci)
      co = ((not x) && y) || (((not x) || y) && ci)
      s = (subc xs ys co) 
  in if d == False && s == [] then [] else d : s

sub xs [] = xs
sub xs ys = subc xs ys False

xor x y = x /= y

normalize [] = []
normalize (False : xs) = 
  let ns = normalize xs
  in if ns == [] then [] else (False : ns)
normalize (True : xs) = True : (normalize xs)

mul [] _ = []
mul (False : xs) ys = False : (mul xs ys)
mul (True : xs) ys = mul (False : xs) ys `add` ys

mulk3 [] _ = []
mulk3 _ [] = []
mulk3 xs ys =
 (normalize (mulk3 xs0 ys0)) `add` (replicate l False ++ (((mulk3 (add xs0 xs1) (add ys0 ys1)) `sub` (normalize (mulk3 xs0 ys0)) `sub` (normalize (mulk3 xs1 ys1))) `add` (replicate l False ++ (normalize (mulk3 xs1 ys1))))) using` strategy
 where
  l = (min (length xs) (length ys)) `div` 2
  (xs0, xs1) = splitAt l xs
  (ys0, ys1) = splitAt l ys
  if l > 32 then
   strategy res = do
    rpar (normalize (mulk3 xs0 ys0))
    rpar (normalize (mulk3 xs1 ys1)) 
    rpar ((mulk3 (add xs0 xs1) (add ys0 ys1)) `sub` (normalize (mulk3 xs0 ys0)) `sub` (normalize (mulk3 xs1 ys1)))
    rdeepseq res
  else
   mul xs ys

From: ekcburak at hotmail.com
To: haskell-cafe at haskell.org
Subject: Karatsuba Multiplication Parallel
Date: Fri, 16 Sep 2011 10:52:14 +0000








Dear All,

I am trying to parallelize the below Karatsuba multiplication code. However, 
at each trial of mine the error message speaking of "incorrect indentation"
is returned. I could not come up with ideas to solve the problem.

I will be more than glad and appreciated, if any of you sheds light on the
issue and point out the problem with its solution.

Many thanks in advance,

 Cheers,
Burak.

import Control.Parallel
import Control.Parallel.Strategies

normalize [] = []
normalize (False : xs) = 
  let ns = normalize xs
  in if ns == [] then [] else (False : ns)
normalize (True : xs) = True : (normalize xs)

mul [] _ = []
mul (False : xs) ys = False : (mul xs ys)
mul (True : xs) ys = mul (False : xs) ys `add` ys

mulk3 [] _ = []
mulk3 _ [] = []
mulk3 xs ys =
 (normalize (mulk3 xs0 ys0)) `add` (replicate l False ++ (((mulk3 (add xs0 xs1) (add ys0 ys1)) `sub` (normalize (mulk3 xs0 ys0)) `sub` (normalize (mulk3 xs1 ys1))) `add` (replicate l False ++ (normalize (mulk3 xs1 ys1)))))
 where
  l = (min (length xs) (length ys)) `div` 2
  (xs0, xs1) = splitAt l xs
  (ys0, ys1) = splitAt l ys
  if l > 32 then
   (normalize (mulk3 xs0 ys0)) `par`
   (normalize (mulk3 xs1 ys1)) `par`
   ((mulk3 (add xs0 xs1) (add ys0 ys1)) `sub` (normalize (mulk3 xs0 ys0)) `sub` (normalize (mulk3 xs1 ys1)))
  else
   mul xs ys


 		 	   		   		 	   		  
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110916/94d60e27/attachment.htm>


More information about the Haskell-Cafe mailing list