Parallel calculations

From Rosetta Code
Revision as of 23:29, 8 January 2011 by rosettacode>Paddy3118 (→‎{{header|Python}}: Correction - got meaning of task wrong (again).)
Task
Parallel calculations
You are encouraged to solve this task according to the task description, using any language you may know.

Many programming languages allow you to specify computations to be run in parallel. While Concurrent computing is focused on concurrency, the purpose of this task is to distribute time-consuming calculations on as many CPUs as possible.

Assume we have a collection of numbers, and want to find the one with the largest minimal prime factor (that is, the one that contains relatively large factors). To speed up the search, the factorization should be done in parallel using separate threads or processes, to take advantage of multi-core CPUs.

Show how this can be formulated in your language. Parallelize the factorization of those numbers, then search the returned list of numbers and factors for the largest minimal factor, and return that number and its prime factors.

For the prime number decomposition you may use the solution of the Prime decomposition task.

Ada

I took the version from Prime decomposition and adjusted it to use tasks.

prime_numbers.ads: <lang Ada>generic

  type Number is private;
  Zero : Number;
  One  : Number;
  Two  : Number;
  with function Image (X : Number) return String is <>;
  with function "+"   (X, Y : Number) return Number is <>;
  with function "/"   (X, Y : Number) return Number is <>;
  with function "mod" (X, Y : Number) return Number is <>;
  with function ">="  (X, Y : Number) return Boolean is <>;

package Prime_Numbers is

  type Number_List is array (Positive range <>) of Number;
  procedure Put (List : Number_List);
  task type Calculate_Factors is
     entry Start (The_Number : in Number);
     entry Get_Size (Size : out Natural);
     entry Get_Result (List : out Number_List);
  end Calculate_Factors;

end Prime_Numbers;</lang>

prime_numbers.adb: <lang Ada>with Ada.Text_IO; package body Prime_Numbers is

  procedure Put (List : Number_List) is
  begin
     for Index in List'Range loop
        Ada.Text_IO.Put (Image (List (Index)));
     end loop;
  end Put;
  task body Calculate_Factors is
     Size : Natural := 0;
     N    : Number;
     M    : Number;
     K    : Number  := Two;
  begin
     accept Start (The_Number : in Number) do
        N := The_Number;
        M := N;
     end Start;
     -- Estimation of the result length from above
     while M >= Two loop
        M    := (M + One) / Two;
        Size := Size + 1;
     end loop;
     M := N;
     -- Filling the result with prime numbers
     declare
        Result : Number_List (1 .. Size);
        Index  : Positive := 1;
     begin
        while N >= K loop -- Divisors loop
           while Zero = (M mod K) loop -- While divides
              Result (Index) := K;
              Index          := Index + 1;
              M              := M / K;
           end loop;
           K := K + One;
        end loop;
        Index := Index - 1;
        accept Get_Size (Size : out Natural) do
           Size := Index;
        end Get_Size;
        accept Get_Result (List : out Number_List) do
           List (1 .. Index) := Result (1 .. Index);
        end Get_Result;
     end;
  end Calculate_Factors;

end Prime_Numbers;</lang>

Example usage:

parallel.adb: <lang Ada>with Ada.Text_IO; with Prime_Numbers; procedure Parallel is

  package Integer_Primes is new Prime_Numbers (
     Number => Integer, -- use Large_Integer for longer numbers
     Zero   => 0,
     One    => 1,
     Two    => 2,
     Image  => Integer'Image);
  My_List : Integer_Primes.Number_List :=
    ( 12757923,
      12878611,
      12757923,
      15808973,
      15780709,
     197622519);
  Decomposers : array (My_List'Range) of Integer_Primes.Calculate_Factors;
  Lengths     : array (My_List'Range) of Natural;
  Max_Length  : Natural := 0;

begin

  for I in My_List'Range loop
     -- starts the tasks
     Decomposers (I).Start (My_List (I));
  end loop;
  for I in My_List'Range loop
     -- wait until task has reached Get_Size entry
     Decomposers (I).Get_Size (Lengths (I));
     if Lengths (I) > Max_Length then
        Max_Length := Lengths (I);
     end if;
  end loop;
  declare
     Results                :
       array (My_List'Range) of Integer_Primes.Number_List (1 .. Max_Length);
     Largest_Minimal_Factor : Integer := 0;
     Winning_Index          : Positive;
  begin
     for I in My_List'Range loop
        -- after Get_Result, the tasks terminate
        Decomposers (I).Get_Result (Results (I));
        if Results (I) (1) > Largest_Minimal_Factor then
           Largest_Minimal_Factor := Results (I) (1);
           Winning_Index          := I;
        end if;
     end loop;
     Ada.Text_IO.Put_Line
       ("Number" & Integer'Image (My_List (Winning_Index)) &
        " has largest minimal factor:");
     Integer_Primes.Put (Results (Winning_Index) (1 .. Lengths (Winning_Index)));
     Ada.Text_IO.New_Line;
  end;

end Parallel;</lang>

Output:

Number 12878611 has largest minimal factor:
 47 101 2713

D

<lang d>import std.stdio, std.math, std.algorithm, std.typecons; import core.thread, core.stdc.time;

final class MinFactor: Thread {

   private ulong   num ;
   private ulong[] fac;
   private ulong   minFac ;
   this(ulong n) nothrow {
       super(&run);
       num = n;
       fac = new ulong[](0) ;
   }
   ulong   number() @property { return num ; }
   ulong[] factors() @property { return fac.dup ; }
   ulong   minFactor() @property { return minFac ; }
   private void run() {
       immutable clock_t begin = clock();
       switch(num) {
           case 0: fac = []  ; break ;
           case 1: fac = [1] ; break ;
           default:
               uint limit = cast(uint) (1 + sqrt(num)) ;
               ulong n = num ;
               for (ulong div = 3; div < limit; div += 2) {
                   if(n == 1) break ;
                   if((n % div) == 0) {
                       while((n > 1) && ((n % div) == 0)) {
                           fac ~= div ;
                           n /= div ;
                       }
                       limit = cast(uint) (1 + sqrt(n)) ;
                   }
               }
               if(n > 1)
                   fac ~= n ;
       }
       minFac = reduce!min(fac) ;
       immutable clock_t end = clock();
       writefln("num: %20d --> min. factor: %20d  ticks(%7d -> %7d)",
                num, minFac, begin, end);
   }

}

void main() {

   auto numbers = [2UL^^59-1, 2UL^^59-1, 2UL^^59-1, 112272537195293UL, 
                   115284584522153, 115280098190773, 115797840077099,
                   112582718962171, 112272537095293, 1099726829285419];
   auto tgroup = new ThreadGroup;
   foreach (n; numbers)
       tgroup.add(new MinFactor(n));
   writeln("Minimum factors for respective numbers are:");
   foreach (t; tgroup)
       t.start();
   tgroup.joinAll();
   Tuple!(ulong, ulong[], ulong) maxmin ;
   maxmin = tuple(0UL, [0UL], 0UL) ;
   foreach (t; tgroup) {
       auto s = cast(MinFactor)t;
       if (s !is null && maxmin[2] < s.minFactor)
               maxmin = tuple(s.number, s.factors, s.minFactor) ;
   }
   writefln("Number with largest min. factor is %16d, with factors:\n\t%s",
            maxmin[0], maxmin[1]);

}</lang> Output (1 core CPU, edited to fit page width):

Minimum factors for respective numbers are:
num:   576460752303423487 --> min. factor: 179951  ticks(  16 ->  78)
num:   576460752303423487 --> min. factor: 179951  ticks(  78 -> 125)
num:   576460752303423487 --> min. factor: 179951  ticks( 141 -> 203)
num:      112272537195293 --> min. factor:    173  ticks( 203 -> 203)
num:      115284584522153 --> min. factor: 513937  ticks( 203 -> 219)
num:      115280098190773 --> min. factor: 513917  ticks( 219 -> 250)
num:      115797840077099 --> min. factor: 544651  ticks( 250 -> 266)
num:      112582718962171 --> min. factor:   3121  ticks( 266 -> 266)
num:      112272537095293 --> min. factor:    131  ticks( 266 -> 266)
num:     1099726829285419 --> min. factor:    271  ticks( 266 -> 266)
Number with largest min. factor is  115797840077099, with factors:
        [544651, 212609249]

PicoLisp

The 'later' function is used in PicoLisp to start parallel computations. The following solution calls 'later' on the 'factor' function from Prime decomposition#PicoLisp, and then 'wait's until all results are available: <lang PicoLisp>(let Lst

  (mapcan
     '((N)
        (later (cons)               # When done,
           (cons N (factor N)) ) )  # return the number and its factors
     (quote
        188573867500151328137405845301  # Process a collection of 12 numbers
        3326500147448018653351160281
        979950537738920439376739947
        2297143294659738998811251
        136725986940237175592672413
        3922278474227311428906119
        839038954347805828784081
        42834604813424961061749793
        2651919914968647665159621
        967022047408233232418982157
        2532817738450130259664889
        122811709478644363796375689 ) )
  (wait NIL (full Lst))  # Wait until all computations are done
  (maxi '((L) (apply min L)) Lst) )  # Result: Number in CAR, factors in CDR</lang>

Output:

-> (2532817738450130259664889 6531761 146889539 2639871491)

Prolog

Works with: swipl

This piece needs prime_decomp definition from the Prime decomposition#Prolog example, it worked on my swipl, but I don't know how other Dialects thread.

<lang Prolog>threaded_decomp(Number,ID):- thread_create( (prime_decomp(Number,Y), thread_exit((Number,Y))) ,ID,[]).

threaded_decomp_list(List,Erg):- maplist(threaded_decomp,List,IDs), maplist(thread_join,IDs,Results), maplist(pack_exit_out,Results,Smallest_Factors_List), largest_min_factor(Smallest_Factors_List,Erg).

pack_exit_out(exited(X),X). %Note that here some error handling should happen.

largest_min_factor([(N,Facs)|A],(N2,Fs2)):- min_list(Facs,MF), largest_min_factor(A,(N,MF,Facs),(N2,_,Fs2)).

largest_min_factor([],Acc,Acc). largest_min_factor([(N1,Facs1)|Rest],(N2,MF2,Facs2),Goal):- min_list(Facs1, MF1), (MF1 > MF2-> largest_min_factor(Rest,(N1,MF1,Facs1),Goal); largest_min_factor(Rest,(N2,MF2,Facs2),Goal)).


format_it(List):- threaded_decomp_list(List,(Number,Factors)), format('Number with largest minimal Factor is ~w\nFactors are ~w\n', [Number,Factors]). </lang>

Example (Numbers Same as in Ada Example):

?- ['prime_decomp.prolog', parallel].
% prime_decomp.prolog compiled 0.00 sec, 3,392 bytes
% parallel compiled 0.00 sec, 4,672 bytes
true.
format_it([12757923,
       12878611, 
       12757923, 
       15808973, 
       15780709, 
      197622519]).
Number with largest minimal factor is 12878611
Factors are [2713, 101, 47]
true.

PureBasic

<lang PureBasic>Structure IO_block

 ThreadID.i
 StartSeamaphore.i
 Value.q
 MinimumFactor.i
 List Factors.i()

EndStructure

\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\

Declare Factorize(*IO.IO_block) Declare main()

\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\

Main() End

\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\

Procedure Main()

 Protected AvailableCpu, MainSemaphore
 Protected i, j, qData.q, Title$, Message$
 NewList T.IO_block()
 ;
 AvailableCpu = Val(GetEnvironmentVariable("NUMBER_OF_PROCESSORS"))
 If AvailableCpu<1: AvailableCpu=1: EndIf
 MainSemaphore = CreateSemaphore(AvailableCpu)
 ;
 Restore Start_of_data
 For i=1 To (?end_of_data-?Start_of_data) / SizeOf(Quad)
   ; Start all threads at ones, they will then be let to
   ; self-oganize according to the availiable Cores.
   AddElement(T())
   Read.q  qData
   T()\Value = qData
   T()\StartSeamaphore = MainSemaphore
   T()\ThreadID = CreateThread(@Factorize(), @T())
 Next
 ;
 ForEach T()
   ; Wait for all threads to complete their work and
   ; find the smallest factor from eact task.
   WaitThread(T()\ThreadID)
 Next
 ;
 i = OffsetOf(IO_block\MinimumFactor)
 SortStructuredList(T(), #PB_Sort_Integer, i, #PB_Sort_Descending)
 FirstElement(T())
 Title$="Info"
 Message$="Number "+Str(T()\Value)+" has largest minimal factor:"+#CRLF$
 ForEach T()\Factors()
   Message$ + Str(T()\Factors())+" "
 Next
 MessageRequester(Title$, Message$)

EndProcedure

ProcedureDLL Factorize(*IO.IO_block) ; Fill list Factors() with the factor parts of Number

 ;Based on http://rosettacode.org/wiki/Prime_decomposition#PureBasic
 With *IO
   Protected Value.q=\Value
   WaitSemaphore(\StartSeamaphore)
   Protected I = 3
   ClearList(\Factors())
   While Value % 2 = 0
     AddElement(\Factors())
     \Factors() = 2
     Value / 2
   Wend
   Protected Max = Value
   While I <= Max And Value > 1
     While Value % I = 0
       AddElement(\Factors())
       \Factors() = I
       Value / I
     Wend
     I + 2
   Wend
   SortList(\Factors(), #PB_Sort_Ascending)
   FirstElement(\Factors())
   \MinimumFactor=\Factors()
   SignalSemaphore(\StartSeamaphore)
 EndWith ;*IO

EndProcedure

DataSection

 Start_of_data: ; Same numbers as Ada
 Data.q  12757923, 12878611, 12757923, 15808973, 15780709, 197622519
 end_of_data:

EndDataSection </lang>

Python

Python 3.2 has a new concurrent.futures module that allows for the easy specification of thread-parallel or process-parallel processes. The following is modified from their example and will run, by default, with as many processes as as there are available cores on your machine.

Note that there is no need to calculate all prime factors of all NUMBERS when only the prime factors of the number with the lowest overall prime factor is needed. <lang python>from concurrent import futures from math import floor, sqrt

NUMBERS = [

   112272537195293,
   112582718962171,
   112272537095293,
   115280098190773,
   115797840077099,
   1099726829285419]
  1. NUMBERS = [33, 44, 55, 275]

def lowest_factor(n, _start=3):

   if n % 2 == 0:
       return 2
   search_max = int(floor(sqrt(n))) + 1
   for i in range(_start, search_max, 2):
       if n % i == 0:
           return i
   return n

def prime_factors(n, lowest):

   pf = []
   while n > 1:
       pf.append(lowest)
       n //= lowest
       lowest = lowest_factor(n, max(lowest, 3))
   return pf

def prime_factors_of_number_with_lowest_prime_factor(NUMBERS):

   with futures.ProcessPoolExecutor() as executor:
       low_factor, number = max( (l, f) for l, f in zip(executor.map(lowest_factor, NUMBERS), NUMBERS) )
       all_factors = prime_factors(number, low_factor)
       return number, all_factors


def main():

   print( 'For these numbers:\n  ' + '\n  '.join(str(p) for p in NUMBERS) )
   number, all_factors = prime_factors_of_number_with_lowest_prime_factor(NUMBERS)
   print('    The one with the largest minimum prime factor is %i:' % number)
   print('      All its prime factors in order are: %s' % all_factors)
       

if __name__ == '__main__':

   main()</lang>

Sample Output

For these numbers:
  112272537195293
  112582718962171
  112272537095293
  115280098190773
  115797840077099
  1099726829285419
    The one with the largest minimum prime factor is 115797840077099:
      All its prime factors in order are: [544651, 212609249]

Tcl

With Tcl, it is necessary to explicitly perform computations in other threads because each thread is strongly isolated from the others (except for inter-thread messaging). However, it is entirely practical to wrap up the communications so that only a small part of the code needs to know very much about it, and in fact most of the complexity is managed by a thread pool; each value to process becomes a work item to be handled. It is easier to transfer the results by direct messaging instead of collecting the thread pool results, since we can leverage Tcl's vwait command nicely.

Works with: Tcl version 8.6

<lang tcl>package require Tcl 8.6 package require Thread

  1. Pooled computation engine; runs event loop internally

namespace eval pooled {

   variable poolSize 3; # Needs to be tuned to system size
   proc computation {computationDefinition entryPoint values} {

variable result variable poolSize # Add communication shim append computationDefinition [subst -nocommands { proc poolcompute {value target} { set outcome [$entryPoint \$value] set msg [list set ::pooled::result(\$value) \$outcome] thread::send -async \$target \$msg } }]

# Set up the pool set pool [tpool::create -initcmd $computationDefinition \ -maxworkers $poolSize]

# Prepare to receive results unset -nocomplain result array set result {}

# Dispatch the computations foreach value $values { tpool::post $pool [list poolcompute $value [thread::id]] }

# Wait for results while {[array size result] < [llength $values]} {vwait pooled::result}

# Dispose of the pool tpool::release $pool

# Return the results return [array get result]

   }

}</lang> This is the definition of the prime factorization engine (a somewhat stripped-down version of the Tcl Prime decomposition solution: <lang tcl># Code for computing the prime factors of a number set computationCode {

   namespace eval prime {

variable primes [list 2 3 5 7 11] proc restart {} { variable index -1 variable primes variable current [lindex $primes end] }

proc get_next_prime {} { variable primes variable index if {$index < [llength $primes]-1} { return [lindex $primes [incr index]] } variable current while 1 { incr current 2 set p 1 foreach prime $primes { if {$current % $prime} {} else { set p 0 break } } if {$p} { return [lindex [lappend primes $current] [incr index]] } } }

proc factors {num} { restart set factors [dict create] for {set i [get_next_prime]} {$i <= $num} {} { if {$num % $i == 0} { dict incr factors $i set num [expr {$num / $i}] continue } elseif {$i*$i > $num} { dict incr factors $num break } else { set i [get_next_prime] } } return $factors }

   }

}

  1. The values to be factored

set values {

   188573867500151328137405845301
   3326500147448018653351160281
   979950537738920439376739947
   2297143294659738998811251
   136725986940237175592672413
   3922278474227311428906119
   839038954347805828784081
   42834604813424961061749793
   2651919914968647665159621
   967022047408233232418982157
   2532817738450130259664889
   122811709478644363796375689

}</lang> Putting everything together: <lang tcl># Do the computation, getting back a dictionary that maps

  1. values to its results (itself an ordered dictionary)

set results [pooled::computation $computationCode prime::factors $values]

  1. Find the maximum minimum factor with sorting magic

set best [lindex [lsort -integer -stride 2 -index {1 0} $results] end-1]

  1. Print in human-readable form

proc renderFactors {factorDict} {

   dict for {factor times} $factorDict {

lappend v {*}[lrepeat $times $factor]

   }
   return [join $v "*"]

} puts "$best = [renderFactors [dict get $results $best]]"</lang>