
Dear Everebody. Hepl me please to parallelize (parallel computing of evedidtalk function) the rebus: -- | eve / did = 0.talktalktalk... ten :: Integral a => [a] ten = [0..9] infixr 7 /: (/:) :: (Integral a) => [a] -> [a] -> [a] (/:) [] _ = [0] (/:) _ [] = [] (/:) x y = coldiv (getInteger x) (getInteger y) getInteger :: (Num a) => [a] -> a getInteger = foldl ((+) . (*10)) 0 coldiv :: (Integral a) => a -> a -> [a] coldiv a b = q : if r == 0 then [] else coldiv (r * 10) b where (q, r) = a `quotRem` b evedidtalk = [ ([e, v, e], [d, i, d], [t, a, l, k]) | e <- ten, v <- ten, v /= e, d <- ten, d /= e, d /= v, i <- ten, i /= e, i /= v, i /= d, t <- ten, t /= e, t /= v, t /= d, t /= i, a <- ten, a /= e, a /= v, a /= d, a /= i, a /= t, l <- ten, l /= e, l /= v, l /= d, l /= i, l /= t, l /= a, k <- ten, k /= e, k /= v, k /= d, k /= i, k /= t, k /= a, k /= l, take 9 ([e, v, e] /: [d, i, d]) == [0, t, a, l, k, t, a, l, k] ] Sincerely, Alexander

Excuse me for repetition, but I first time at beginners@haskell.org and very
first time when I sent the message I was not registered, so now I forward it
as rightful member. I must clarify the problem a little. The solution I
represent below is using only 1 processor from 2 of available but I suspect
that using `par` can help to load my computer in full. So :
---------- Forwarded message ----------
From: Alexander.Vladislav.Popov

Am Donnerstag 22 April 2010 19:05:39 schrieb Alexander.Vladislav.Popov:
Excuse me for repetition, but I first time at beginners@haskell.org and very first time when I sent the message I was not registered, so now I forward it as rightful member. I must clarify the problem a little. The solution I represent below is using only 1 processor from 2 of available but I suspect that using `par` can help to load my computer in full. So :
---------- Forwarded message ---------- From: Alexander.Vladislav.Popov
Date: 2010/4/22 Subject: eve / did = 0.talktalktalk... To: beginners@haskell.org Dear Everebody.
Hepl me please to parallelize (parallel computing of evedidtalk function) the rebus:
The only way to exploit parallelism here that I see is to split the work into smaller pieces, say evedidone = [ ([e, v, e], [d, i, d], [t, a, l, k]) | e <- [0 .. 4], v <- ten, v /= e, ... ] evedidtwo = [ ([e, v, e], [d, i, d], [t, a, l, k]) | e <- [5 .. 9], ... ] evedidtalk = evedidone `par` evedidtwo `pseq` (evedidone ++ evedidtwo) However, just a slightly less brutish brute force will make it return the answer in less time than it takes to get two cores working and collect the results.
-- | eve / did = 0.talktalktalk...
Since the quotient is < 1, we must have eve < did, hence e < d. That roughly halves the work.
ten :: Integral a => [a] ten = [0..9]
infixr 7 /:
(/:) :: (Integral a) => [a] -> [a] -> [a] (/:) [] _ = [0] (/:) _ [] = [] (/:) x y = coldiv (getInteger x) (getInteger y)
getInteger :: (Num a) => [a] -> a getInteger = foldl ((+) . (*10)) 0
coldiv :: (Integral a) => a -> a -> [a] coldiv a b = q : if r == 0 then [] else coldiv (r * 10) b where (q, r) = a `quotRem` b
evedidtalk = [ ([e, v, e], [d, i, d], [t, a, l, k]) | e <- ten,
e <- [0 .. 8], -- though we could also exclude 0 a priori
v <- ten, v /= e, d <- ten, d /= e, d /= v,
d <- [e+1 .. 9], d /= v,
i <- ten, i /= e, i /= v, i /= d,
The following is bad:
t <- ten, t /= e, t /= v, t /= d, t /= i, a <- ten, a /= e, a /= v, a /= d, a /= i, a /= t, l <- ten, l /= e, l /= v, l /= d, l /= i, l /= t, l /= a, k <- ten, k /= e, k /= v, k /= d, k /= i, k /= t, k /= a, k /= l,
instead: let [0,t,a,l,k,s,m,o,g] = take 9 ([e,v,e] /: [d,i,d]), t == s, t `notElem` [e,v,d,i], a == m, a `notElem` [e,v,d,i,t], l == o, l `notElem` [e,v,d,i,t,a], k == g, k `notElem` [e,v,d,i,t,a,l]
take 9 ([e, v, e] /: [d, i, d]) == [0, t, a, l, k, t, a, l, k] ]
Not to mention that there are only two possibilities for did, 303 and 909, so you could make it a little faster still using that.
Sincerely, Alexander

Am Donnerstag 22 April 2010 20:35:05 schrieb Daniel Fischer:
Not to mention that there are only two possibilities for did, 303 and 909, so you could make it a little faster still using that.
Rats, forgot that the fraction eve/did need not be reduced, so there's a third possibility, 2*303 = 606.

may not help with the parallelization desire but if you change the check from eve/did=.talktalktalk to eve/did=talk/9999 and then to eve*9999=did*talk it becomes lightning fast. I tried and I can solve it in under a second now. if you want I can share the code of course. On 22 April 2010 18:05, Alexander.Vladislav.Popov < alexander.vladislav.popov@gmail.com> wrote:
Excuse me for repetition, but I first time at beginners@haskell.org and very first time when I sent the message I was not registered, so now I forward it as rightful member. I must clarify the problem a little. The solution I represent below is using only 1 processor from 2 of available but I suspect that using `par` can help to load my computer in full. So :
---------- Forwarded message ---------- From: Alexander.Vladislav.Popov
Date: 2010/4/22 Subject: eve / did = 0.talktalktalk... To: beginners@haskell.org Dear Everebody.
Hepl me please to parallelize (parallel computing of evedidtalk function) the rebus:
-- | eve / did = 0.talktalktalk...
ten :: Integral a => [a] ten = [0..9]
infixr 7 /:
(/:) :: (Integral a) => [a] -> [a] -> [a] (/:) [] _ = [0] (/:) _ [] = [] (/:) x y = coldiv (getInteger x) (getInteger y)
getInteger :: (Num a) => [a] -> a getInteger = foldl ((+) . (*10)) 0
coldiv :: (Integral a) => a -> a -> [a] coldiv a b = q : if r == 0 then [] else coldiv (r * 10) b where (q, r) = a `quotRem` b
evedidtalk = [ ([e, v, e], [d, i, d], [t, a, l, k]) | e <- ten, v <- ten, v /= e, d <- ten, d /= e, d /= v, i <- ten, i /= e, i /= v, i /= d, t <- ten, t /= e, t /= v, t /= d, t /= i, a <- ten, a /= e, a /= v, a /= d, a /= i, a /= t, l <- ten, l /= e, l /= v, l /= d, l /= i, l /= t, l /= a, k <- ten, k /= e, k /= v, k /= d, k /= i, k /= t, k /= a, k /= l, take 9 ([e, v, e] /: [d, i, d]) == [0, t, a, l, k, t, a, l, k] ]
Sincerely, Alexander
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Ozgur Akgun
participants (3)
-
Alexander.Vladislav.Popov
-
Daniel Fischer
-
Ozgur Akgun