Sunday, September 15, 2019

Parallel summation of a large array without shared data locks


The traditional producer/consumer pattern employs a shared buffer between the producer and the consumer.  Many producer/consumer problems are simply sequential problems with the overhead of multiple tasks and a shared buffer.
Parallel operations, on the other hand, are more naturally concurrent without the locking overhead of a shared buffer. Instead non-overlapping data elements of a collection such as an array are assigned to two or more tasks, and identical tasks process their subsets of the collection without need of locking the collection.

 If the parallel task is to sum all the elements in the array then task 1 in the diagram above will sum the elements in the first half of the array while task 2 sums the elements in the second half of the array. Task 1 and task 2 then simply report their subtotals to the parent task which adds the two values and returns the final total.
The following source code is an Ada package for parallel addition along with a procedure to test the package.

package Parallel_Addition is
   type Data_Array is array(Integer range <>) of Integer;
   type Data_Access is access all Data_Array;
   function Sum(Item : in not null Data_Access) return Integer;
end Parallel_Addition;

The package specification above defines an array type that can be used by the Sum function. The Sum function declares a parameter of the type Data_Accesss so that the function can handle arrays created either on the stack or on the heap.

package body Parallel_Addition is

   ---------
   -- Sum --
   ---------

   function Sum (Item : in not null Data_Access) return Integer is
      task type Adder is
         entry Set (Min : Integer; Max : Integer);
         entry Report (Value : out Integer);
      end Adder;

      task body Adder is
         Total : Integer := 0;
         First : Integer;
         Last  : Integer;
      begin
         accept Set (Min : Integer; Max : Integer) do
            First := Min;
            Last  := Max;
         end Set;
         for I in First .. Last loop
            Total := Total + Item (I);
         end loop;
         accept Report (Value : out Integer) do
            Value := Total;
         end Report;
      end Adder;
      A1  : Adder;
      A2  : Adder;
      R1  : Integer;
      R2  : Integer;
      Mid : constant Integer := (Item'Length / 2) + Item'First;
   begin
      A1.Set (Min => Item'First, Max => Mid);
      A2.Set (Min => Mid + 1, Max => Item'Last);
      A1.Report (R1);
      A2.Report (R2);
      return R1 + R2;
   end Sum;
end Parallel_Addition;

The package body for Parallel_Addition simply implements the Sum function. The Sum function defines a task type named Adder. That task type has two entries. The Set entry receives the minimum and maximum index values to be processed. The Report entry passes the locally calculated subtotal back to the Sum function. Each instance of Adder sums the values in the index range from Min to Max in the array passed as the Sum formal parameter Item, then passes the local sum back through the Report entry.
Two instances of Adder are created as well as two variables to contain results, one result for each Adder task. The variable Mid calculates the middle index value of the array Item.
Adder tasks A1 and A2 suspend at their Set entry until their Set entry is called. The then concurrently process the array slices indicated by their Min and Max values. They then suspend until their Report entry is called.
The Sum function simply calls the two Set entries and then calls the two Report entries. Finally Sum returns the sum of R1 and R2.
The test procedure for the Parallel_Addition package is:

with Parallel_Addition; use Parallel_Addition;
with Ada.Text_IO;       use Ada.Text_IO;
with Ada.Calendar;      use Ada.Calendar;

procedure Parallel_Addition_Test is
   The_Data : Data_Access := new Data_Array (1 .. Integer'Last);
   Start    : Time;
   Stop     : Time;
   The_Sum  : Integer;

begin
   The_Data.all := (others => 1);
   Start        := Clock;
   The_Sum      := Sum (The_Data);
   Stop         := Clock;
   Put_Line ("The sum is: " & Integer'Image (The_Sum));
   Put_Line
     ("Addition elapsed time is " &
      Duration'Image (Stop - Start) &
        " seconds.");
   Put_Line
     ("Time per addition operation is " &
        Float'Image(Float(Stop - Start) / Float(The_Data'Length)) &
        " seconds.");
end Parallel_Addition_Test;

The variable The_Data is an instance of Data_Access which accesses an array containing Integer’Last data elements. The variables Start and Stop are used to capture the time required to calculate the sum of all values in the array.
All the values of the array accessed by the variable The_Data are initialized to 1 to ensure that the resulting sum does not exhibit integer overflow. The variables Start and Stop record the time just before summing the data and just after summing the data. The difference in the two time values is the approximate elapsed time to calculate the sum. The average time per addition operation is simply the elapsed time divided by the number of data elements processed.
An output of this program, run on a Windows 10 computer, is:

The sum is:  2147483647
Addition elapsed time is  5.661118000 seconds.
Time per addition operation is  2.63616E-09 seconds.

The sum is also the number of array elements processed. This large array was used to produce a statistically significant timing sample.

Monday, February 4, 2019

Stack Abstract Data Type using Ada


The stack Abstract Data Type is one of the simplest data types to create and understand. There are fundamentally two kinds of stack types.
·         bounded stacks which have a pre-determined capacity
·         unbounded stacks which can grow to the limits of computer memory.
Every stack implementation has some common subprograms.
  • ·         Is_Empty – This function returns true if the stack is empty and false if it is not empty
  • ·         Size – A function returning number of elements currently contained by the stack
  • ·         Top – A function returning the top element of a stack that is not empty
  • ·         Push – Push a data element onto the stack
  • ·         Pop – A procedure that pops the top element off the stack, passing the popped element out as a parameter
  • ·         Clear – A procedure that empties the stack
  • ·         Display – A procedure that displays the current contents of the stack

A bounded stack may also have the function Is_Full, which returns true if the stack is full and returns false if it is not full. Notice that Is_Empty is not simply the inverse of Is_Full. A bounded stack with a capacity of 10 elements may contain 0 elements, in which case it is empty, or it may contain some number of elements from 1 through 9, in which case it is neither empty nor full, or it may contain 10 elements, in which case it is full.

Unbounded Stack

Unbounded stacks are commonly implemented as specialized linked lists. Every Push operation results in the dynamic allocation of a new item onto the stack. Every Pop operation results in one item from the stack being freed back to the program heap.
The following implementation of an unbounded stack is defined in an Ada generic package, allowing instances of the unbounded stack to be created containing any data type. 
Ada does provide a pre-defined doubly linked list package as part of its standard container library, but this example re-invents a simple singly linked list to give a complete example of how the unbounded stack can be implemented.

The package specification defines the API for the stack abstract data type:

generic
   type Element_Type is private;
  
   with function Image (Item : in Element_Type) return String;
  
package Unbounded_Stack is
   type Stack is tagged private;

   function Is_Empty (S : in Stack) return Boolean;
  
   function Size (S : in Stack) return Natural;
  
   function Top (S : in Stack) return Element_Type with
     Pre => not S.Is_Empty;
  
   procedure Push (S : in out Stack; Value : in Element_Type) with
     Post => S.Size = S'Old.Size + 1;
  
   procedure Pop (S : in out Stack; Value : out Element_Type) with
      Pre  => not S.Is_Empty,
     Post => S.Size = S'Old.Size - 1;
  
   procedure Clear (S : in out Stack) with
     Post => S.Is_Empty;
  
   procedure Display (S : Stack);
  
private
  
   type Cell;
  
   type Cell_Access is access Cell;
  
   type Cell is record
      Value : Element_Type;
      Next  : Cell_Access;
   end record;

   type Stack is tagged record
      Head  : Cell_Access := null;
      Count : Natural     := 0;
   end record;

end Unbounded_Stack;

The package specification defines two generic parameters which must be specified when an instance of the package is created. The first generic parameter is the data type that the stack will contain. The second generic parameter is a function taking an instance of the stack element type and returning a string representation of the value of that data type.
Several of the functions and procedures have preconditions and/or post-conditions associated with them. These pre and post conditions specify the requirements of those functions and procedures.

Function or Procedure Name
Condition
Description
Top
Pre => not S.Is_Empty
This precondition requires the stack to not be empty before calling the Top function.
Push
Post => S.Size = S'Old.Size + 1
Upon completion of this procedure the size of the stack must increase by 1.
Pop
Pre  => not S.Is_Empty,
Post => S.Size = S'Old.Size - 1
This procedure cannot be called when the stack is empty. Upon completion of this procedure the size of the stack must decrease by 1.
Clear
Post => S.Is_Empty
Upon completion of this procedure the stack will be empty.

The private part of the package specification defines the data types needed to implement a linked list.
The package body contains the implementation of all the functions and procedures defined in the package specification.

with Ada.Unchecked_Deallocation;
with Ada.Text_IO; use Ada.Text_IO;

package body Unbounded_Stack is
   procedure free is new Ada.Unchecked_Deallocation (Cell, Cell_Access);

   --------------
   -- Is_Empty --
   --------------

   function Is_Empty (S : in Stack) return Boolean is
   begin
      return S.Count = 0;
   end Is_Empty;

   ----------
   -- Size --
   ----------

   function Size (S : in Stack) return Natural is
   begin
      return S.Count;
   end Size;

   ---------
   -- Top --
   ---------

   function Top (S : in Stack) return Element_Type is
   begin
      return S.Head.Value;
   end Top;

   ----------
   -- Push --
   ----------

   procedure Push (S : in out Stack; Value : in Element_Type) is
      C : Cell_Access := new Cell;
   begin
      C.Value := Value;
      C.Next  := S.Head;
      S.Head  := C;
      S.Count := S.Count + 1;
   end Push;

   ---------
   -- Pop --
   ---------

   procedure Pop (S : in out Stack; Value : out Element_Type) is
      C : Cell_Access := S.Head;
   begin
      Value   := S.Head.Value;
      S.Head  := S.Head.Next;
      S.Count := S.Count - 1;
      free (C);
   end Pop;

   -----------
   -- Clear --
   -----------

   procedure Clear (S : in out Stack) is
      C : Cell_Access := S.Head;
   begin
      while S.Head /= null loop
         C       := S.Head;
         S.Head  := S.Head.Next;
         S.Count := S.Count - 1;
         free (C);
      end loop;
   end Clear;

   -------------
   -- Display --
   -------------

   procedure Display (S : Stack) is
      C : Cell_Access := S.Head;
   begin
      if S.Is_Empty then
         Put_Line ("The stack is empty.");
      end if;

      for I in 1 .. S.Count loop
         Put_Line (Image (C.Value));
         C := C.Next;
      end loop;
   end Display;

end Unbounded_Stack;

Bounded Stack

The bounded stack is also implemented as a generic package. Instead of using a linked list which can be enlarged with each Push operation, the bounded stack uses an array defined when an instance of the bounded stack is declared.
You will also notice that the Is_Full function has been defined for the bounded stack. Additionally, the Push procedure now has a precondition requiring the stack not to be full when Push is called. The names and interfaces for all other functions and procedures are identical between the bounded stack and the unbounded stack.

generic
  
   type Element_Type is private;
  
   with function Image (Item : in Element_Type) return String;
  
package Bounded_Stack is
  
   type Stack (Size : Positive) is tagged private;

   function Is_Empty (S : in Stack) return Boolean;
  
   function Is_Full (S : in Stack) return Boolean;
  
   function Count (S : in Stack) return Natural;
  
   function Top (S : in Stack) return Element_Type with
     Pre => not S.Is_Empty;
  
   procedure Push (S : in out Stack; Value : in Element_Type) with
      Pre  => not S.Is_Full,
     Post => S.Count = S'Old.Count + 1;
  
   procedure Pop (S : in out Stack; Value : out Element_Type) with
      Pre  => not S.Is_Empty,
     Post => S.Count = S'Old.Count - 1;
  
   procedure Clear (S : in out Stack) with
     Post => S.Is_Empty;
  
   procedure Display (S : in Stack);
  
private
  
   type Buff_T is array (Positive range <>) of Element_Type;
  
   type Stack (Size : Positive) is tagged record
      Buff  : Buff_T (1 .. Size);
      Index : Positive := 1;
      Tally : Natural  := 0;
   end record;

end Bounded_Stack;

The implementation of the bounded stack differs from the unbounded stack because stack elements are never dynamically allocated or de-allocated.

with Ada.Text_IO; use Ada.Text_IO;

package body Bounded_Stack is

   --------------
   -- Is_Empty --
   --------------

   function Is_Empty (S : in Stack) return Boolean is
   begin
      return S.Tally = 0;
   end Is_Empty;

   -------------
   -- Is_Full --
   -------------

   function Is_Full (S : in Stack) return Boolean is
   begin
      return S.Tally = S.Size;
   end Is_Full;

   -----------
   -- Count --
   -----------

   function Count (S : in Stack) return Natural is
   begin
      return S.Tally;
   end Count;

   ---------
   -- Top --
   ---------

   function Top (S : in Stack) return Element_Type is
   begin
      return S.Buff(S.Index - 1);
   end Top;

   ----------
   -- Push --
   ----------

   procedure Push (S : in out Stack;  Value : in Element_Type) is
   begin
      S.Buff(S.Index) := Value;
      S.Tally         := S.Tally + 1;
      S.Index         := S.Index + 1;
   end Push;

   ---------
   -- Pop --
   ---------

   procedure Pop (S : in out Stack; Value : out Element_Type) is
   begin
      S.Tally := S.Tally - 1;
      S.Index := S.Index - 1;
      Value   := S.Buff(S.Index);
   end Pop;

   -----------
   -- Clear --
   -----------

   procedure Clear (S : in out Stack) is
   begin
      S.Tally := 0;
      S.Index := 1;
   end Clear;

   -------------
   -- Display --
   -------------

   procedure Display (S : in Stack) is
   begin
      if S.Tally = 0 then
         Put_Line("The stack is empty.");
      else
         for I in reverse 1..S.Index - 1 loop
            Put_Line(Image(S.Buff(I)));
         end loop;
      end if;
   end Display;

end Bounded_Stack;

Since the API for both the bounded and unbounded stack packages are so similar the use of these packages is very similar.

Using the unbounded stack package


with Ada.Text_IO; use Ada.Text_IO;
with Unbounded_Stack;

procedure Main is

   package Int_Stack is new Unbounded_Stack (Integer, Integer'Image);
   use Int_Stack;

   S : Stack;
   V : Integer;

begin
   Put_Line ("Push 5 values on the stack");

   for I in 1 .. 5 loop
      S.Push (I);
   end loop;
   S.Display;

   Put_Line ("Pop 2 values off of stack");

   for I in 1 .. 2 loop
      S.Pop (V);
      Put_Line ("Popped value" & V'Image);
   end loop;

   S.Display;
   Put_Line ("The top of the stack is" & S.Top'Image);
   S.Clear;
   S.Display;
end Main;

Using the bounded stack package


with Ada.Text_IO; use Ada.Text_IO;
with bounded_stack;

procedure Main is

   package Int_Stack is new bounded_stack (integer, integer'image);
   use Int_Stack;

   S : Stack (10);
   V : Integer;

begin

   Put_Line ("Push 5 values on the stack");

   for I in 1 .. 5 loop
      S.Push (I);
   end loop;

   S.Display;

   Put_Line ("Pop 2 values off of stack");

   for I in 1 .. 2 loop
      S.Pop (V);
      Put_Line ("Popped value" & V'Image);
   end loop;

   S.Display;

   Put_Line ("Push 5 values on the stack");

   for I in 1 .. 5 loop
      S.Push (I);
   end loop;

   S.Display;

   Put_Line ("The top of the stack is" & S.Top'Image);
   S.Clear;
   S.Display;
end Main;

In the bounded stack instance the variable S is declared to be a stack with a capacity of 10 elements. This is done in the line

S : Stack (10);

The (10) sets the Size parameter of the Stack record to 10 for this instance.

Comparison of three algorithms for summing an array of integers

This article shares a comparison of the time taken to sum an array of integers. This article tests three algorithms for summing the array. •...