comp.lang.ada
 help / color / mirror / Atom feed
* Very confused by Ada tasking, can not explain the execution outcome.
@ 2008-08-30  1:54 climber.cui
  2008-08-30  4:17 ` jimmaureenrogers
  2008-08-30  5:12 ` Jeffrey R. Carter
  0 siblings, 2 replies; 8+ messages in thread
From: climber.cui @ 2008-08-30  1:54 UTC (permalink / raw)


Hi all,
  I am trying to simulate a concurrent resource allocator with Ada's
task and protected type.
  The idea is simple: there are several resource available (total
number is N=8), shared by user_thread. Each user first randomly
generate 4 numbers ranged between 0 and 7, which would represent the
resource needed to access. The resources therefore are implemented by
semaphores, which in turn implemented by protected objects.
  The user_thread is not going to interact with each other by making
entry calls, so no entry is defined in tasks. The task representing
the user_thread simply select a procedure defined in the task body non-
deterministically, until the counter, 'rounds' reached its limit.  I
am now only testing a single task for execution. However, the outcome
is very confusing:
  - the last sentence of the task body, which is a put_line statement
is never executed, but the task terminates.
 - also, the per task counter 'rounds', was never incremented, it
stays the same as the initial value. The only procedure increment
'rounds' is procedure 'use_res', but the procedure was never called
during the execution.  If you notice the entry condition for the while
loop, 'while rounds<2 loop', how could it get out of the loop if
'rounds' was never incremented??  why the program still terminates??
  I am stuck on this issue. Although i am not new to programming, I do
not know Ada very well. Could someone help me out here?

  Thanks a lot.
  The entire program (runnable) would be attached at the end of the
message.

tony

--------------------------------------------------------
--------------------------------------------------
with Ada.Text_IO;
with Ada.Numerics.Discrete_Random;
use  Ada.Text_IO;

procedure multi_res_alloc_a is

N: constant := 8; -- number of resources to share
RD:constant := 2;  -- number of rounds

type BOOL_ARRAY is array(0..N-1) of BOOLEAN;

subtype N_res is Integer range 0..99;
package Random_Int is new Ada.Numerics.Discrete_Random (N_res);
    use Random_Int;
    G : Generator;

-- -------------------------------------
protected type Semaphore is
  entry P;
  entry V;
  private
	value: INTEGER := 1;
end Semaphore;
-- -------------------------------------
protected body Semaphore is
  entry P when value>0 is
  	begin
  	  value:= value-1;
  	end P;

  entry V when value=0 is
  	begin
  	  value:= value+1;
  	end V;
end Semaphore;
-- -------------------------------------
r: array(0..N-1) of Semaphore;

-- -------------------------------------
task type User_thread ;

task body User_thread is

   rounds: INTEGER :=0 ;
   next, i, index : INTEGER;
     state: INTEGER :=-1 ;
     d : INTEGER :=0;
     needs: BOOL_ARRAY := (0..N-1 => FALSE);

     x: INTEGER :=0;
     c: INTEGER :=0;

procedure acquire_no_wait is
  begin
    d:=d+1;
  end acquire_no_wait;

procedure acquire_wait is
  begin
      	  r(d).P;
  	  d:=d+1;
  end acquire_wait;

procedure use_res is
  begin
      	  state:=1;
  	  Put_Line("******* Eating now *******");
  	  while d>0 loop
  	    d:=d-1;
  	    if needs(d) then r(d).V;  end if;
  	  end loop;
  	  state:=-1;
  	  rounds:=rounds+1;
  end use_res;

procedure want_res is
  begin
  	  c:=0;
  	  state:=0;
  	  Reset(G);  -- start the generator in a unique state in each run
  	  while c<4 loop
  	    --random x
  	    x := Random(G);
  	    needs(x mod N):= TRUE;
  	    c:=c+1;
  	  end loop;
  end want_res;

begin

  Put_Line("-->> Enter task body..");
  Reset(G);  -- reset the random number generator
  while rounds<2 loop
    next := Random(G) mod 4;   -- number of actions per task = 4
    Put_Line("  >> next =" & INTEGER'Image(next) & ";  state =" &
INTEGER'Image(state));

    if next=0 and state=0 and d<N and not needs(d) then
       Put_Line("------> acquiring resource,no waiting <------");
       acquire_no_wait;
    end if;

    if next=1 and state=0 and d<N and needs(d) then
       Put_Line("------> acquire and waiting resource <------");
       acquire_wait;
    end if;

    if next=2 and state=0 and d>N-1 then
        Put_Line("------> USING resource <------");
        use_res;
    end if;

    if next=3 and state=-1 then
        Put_Line("------> Want resource(s) <------");
        want_res;
    end if;

    --Put_Line(">> ****** rounds = " & INTEGER'Image(rounds) &
"*******" );
    next:= (next+1) mod 4;
    i:=0;
    Put_Line("    >>> next =" & INTEGER'Image(next) & ";  state =" &
INTEGER'Image(state));
    while (i<3) and (rounds<2) loop

      if next=0 and state=0 and d<N and not needs(d) then
        Put_Line("  >> acquiring resource,no waiting <------");
        acquire_no_wait;
      end if;

      if next=1 and state=0 and d<N and needs(d)  then
        Put_Line("  >> acquire and waiting resource <------");
        acquire_wait;
      end if;

      if next=2 and state=0 and d>N-1 then
        Put_Line("  >> USING resource <------");
        use_res;
      end if;

      if next=3 and state=-1 then
        Put_Line("  >> Want resource(s) <------");
        want_res;
      end if;

      --Put_Line(">> ****** rounds = " & INTEGER'Image(rounds) &
"*******" );
      next:= (next+1) mod 4;
      Put_Line("   >>>> next =" & INTEGER'Image(next) & ";  state =" &
INTEGER'Image(state));
      i:=i+1;
    end loop;
    Put_Line("..... rounds =" & INTEGER'Image(rounds) & "...." );
  end loop;

  Put_Line("TASK EXITS ::  rounds =" & INTEGER'Image(rounds) &
"...." );

end User_thread;
-- -------------------------------------

u1: User_thread;

begin
 null;
end multi_res_alloc_a;



^ permalink raw reply	[flat|nested] 8+ messages in thread

* Re: Very confused by Ada tasking, can not explain the execution outcome.
  2008-08-30  1:54 Very confused by Ada tasking, can not explain the execution outcome climber.cui
@ 2008-08-30  4:17 ` jimmaureenrogers
  2008-08-30  9:34   ` climber.cui
  2008-08-30  5:12 ` Jeffrey R. Carter
  1 sibling, 1 reply; 8+ messages in thread
From: jimmaureenrogers @ 2008-08-30  4:17 UTC (permalink / raw)


On Aug 29, 7:54 pm, climber....@gmail.com wrote:
> Hi all,
>   I am trying to simulate a concurrent resource allocator with Ada's
> task and protected type.
>   The idea is simple: there are several resource available (total
> number is N=8), shared by user_thread. Each user first randomly
> generate 4 numbers ranged between 0 and 7, which would represent the
> resource needed to access. The resources therefore are implemented by
> semaphores, which in turn implemented by protected objects.
>   The user_thread is not going to interact with each other by making
> entry calls, so no entry is defined in tasks. The task representing
> the user_thread simply select a procedure defined in the task body non-
> deterministically, until the counter, 'rounds' reached its limit.  I
> am now only testing a single task for execution. However, the outcome
> is very confusing:
>   - the last sentence of the task body, which is a put_line statement
> is never executed, but the task terminates.
>  - also, the per task counter 'rounds', was never incremented, it
> stays the same as the initial value. The only procedure increment
> 'rounds' is procedure 'use_res', but the procedure was never called
> during the execution.  If you notice the entry condition for the while
> loop, 'while rounds<2 loop', how could it get out of the loop if
> 'rounds' was never incremented??  why the program still terminates??
>   I am stuck on this issue. Although i am not new to programming, I do
> not know Ada very well. Could someone help me out here?

The program runs fine with a few modifications to your conditions.
Note that I changed the index to a modular type. This eliminates any
need to check for out of bounds indexing due to your arithmetic.
Modular arithmetic wraps to values within the type definition.

Your program contains two unused variables: Rd and Index. You should
clean up the unused clutter.

Your original version never incremented Rounds because the conditions
for Use_Res were never satisfied.

with Ada.Text_Io;
with Ada.Numerics.Discrete_Random;
use  Ada.Text_Io;

procedure Multi_Res_Alloc_A is

   N  : constant := 8; -- number of resources to share

   type Res_Index is mod N;

   type Bool_Array is array (Res_Index) of Boolean;

   subtype N_Res is Integer range 0..99;
   package Random_Int is new Ada.Numerics.Discrete_Random (N_Res);
   use Random_Int;
   G : Generator;

   -- -------------------------------------
   protected type Semaphore is
      entry P;
      entry V;
   private
      Value : Boolean := True;
   end Semaphore;
   -- -------------------------------------
   protected body Semaphore is
      entry P when Value is
      begin
         Value:= False;
      end P;

      entry V when not Value is
      begin
         Value:= True;
      end V;
   end Semaphore;
   -- -------------------------------------
   R : array (Res_Index) of Semaphore;

   -- -------------------------------------
   task type User_Thread ;

   task body User_Thread is

      Rounds : Integer    := 0;
      Next,
      I      : Integer;
      State  : Integer    := - 1;
      D      : Res_Index    := 0;
      Needs  : Bool_Array := (Others => False);

      X : Integer := 0;
      C : Integer := 0;

      procedure Acquire_No_Wait is
      begin
         D:=D+1;
      end Acquire_No_Wait;

      procedure Acquire_Wait is
      begin
         R(D).P;
         D:=D+1;
      end Acquire_Wait;

      procedure Use_Res is
      begin
         State:=1;
         Put_Line("******* Eating now *******");
         while D>0 loop
            D:=D-1;
            if Needs(D) then
               R(D).V;
            end if;
         end loop;
         State:=-1;
         Rounds:=Rounds+1;
      end Use_Res;

      procedure Want_Res is
      begin
         C:=0;
         State:=0;
         Reset(G);  -- start the generator in a unique state in each
run
         while C<4 loop
            --random x
            X := Random(G);
            Needs(Res_Index(X mod N)):= True;
            C:=C+1;
         end loop;
      end Want_Res;

   begin

      Put_Line("-->> Enter task body..");
      Reset(G);  -- reset the random number generator
      while Rounds<2 loop
         Next := Random(G) mod 4;   -- number of actions per task = 4
         Put_Line("  >> next =" & Integer'Image(Next) & ";  state =" &
Integer'Image(State));

         if Next=0 and State=0 and not Needs(D) then
            Put_Line("------> acquiring resource,no waiting <------");
            Acquire_No_Wait;
         end if;

         if Next=1 and State=0 and Needs(D) then
            Put_Line("------> acquire and waiting resource <------");
            Acquire_Wait;
         end if;

         if Next=2 and State=0 then
            Put_Line("------> USING resource <------");
            Use_Res;
         end if;

         if Next=3 and State=-1 then
            Put_Line("------> Want resource(s) <------");
            Want_Res;
         end if;

         --Put_Line(">> ****** rounds = " & INTEGER'Image(rounds) &
"*******" );
         Next:= (Next+1) mod 4;
         I:=0;
         Put_Line("    >>> next =" & Integer'Image(Next) & ";  state
=" & Integer'Image(State));
         while (I<3) and (Rounds<2) loop

            if Next=0 and State=0 and not Needs(D) then
               Put_Line("  >> acquiring resource,no waiting <------");
               Acquire_No_Wait;
            end if;

            if Next=1 and State=0 and Needs(D)  then
               Put_Line("  >> acquire and waiting resource <------");
               Acquire_Wait;
            end if;

            if Next=2 and State=0 then
               Put_Line("  >> USING resource <------");
               Use_Res;
            end if;

            if Next=3 and State=-1 then
               Put_Line("  >> Want resource(s) <------");
               Want_Res;
            end if;

            --Put_Line(">> ****** rounds = " & INTEGER'Image(rounds) &
"*******" );
            Next:= (Next+1) mod 4;
            Put_Line("   >>>> next =" & Integer'Image(Next) & ";
state =" & Integer'Image(State));
            I:=I+1;
         end loop;
         Put_Line("..... rounds =" & Integer'Image(Rounds) & "...." );
      end loop;

      Put_Line("TASK EXITS ::  rounds =" & Integer'Image(Rounds) &
"...." );

   end User_Thread;
   -- -------------------------------------

   U1 : User_Thread;

begin
   null;
end Multi_Res_Alloc_A;

Jim Rogers



^ permalink raw reply	[flat|nested] 8+ messages in thread

* Re: Very confused by Ada tasking, can not explain the execution outcome.
  2008-08-30  1:54 Very confused by Ada tasking, can not explain the execution outcome climber.cui
  2008-08-30  4:17 ` jimmaureenrogers
@ 2008-08-30  5:12 ` Jeffrey R. Carter
  2008-08-30  9:42   ` climber.cui
  1 sibling, 1 reply; 8+ messages in thread
From: Jeffrey R. Carter @ 2008-08-30  5:12 UTC (permalink / raw)


climber.cui@gmail.com wrote:
>   - the last sentence of the task body, which is a put_line statement
> is never executed, but the task terminates.
>  - also, the per task counter 'rounds', was never incremented, it
> stays the same as the initial value. The only procedure increment
> 'rounds' is procedure 'use_res', but the procedure was never called
> during the execution.  If you notice the entry condition for the while
> loop, 'while rounds<2 loop', how could it get out of the loop if
> 'rounds' was never incremented??  why the program still terminates??

If an exception occurs in your task, the task will terminate silently. This is a 
way your task and program could terminate although it never increments Rounds 
nor executes its final statement.

-- 
Jeff Carter
"If I could find a sheriff who so offends the citizens of Rock
Ridge that his very appearance would drive them out of town ...
but where would I find such a man? Why am I asking you?"
Blazing Saddles
37



^ permalink raw reply	[flat|nested] 8+ messages in thread

* Re: Very confused by Ada tasking, can not explain the execution outcome.
  2008-08-30  4:17 ` jimmaureenrogers
@ 2008-08-30  9:34   ` climber.cui
  2008-08-30 10:59     ` Damien Carbonne
  0 siblings, 1 reply; 8+ messages in thread
From: climber.cui @ 2008-08-30  9:34 UTC (permalink / raw)


On Aug 30, 12:17 am, "jimmaureenrog...@worldnet.att.net"
<jimmaureenrog...@worldnet.att.net> wrote:
> On Aug 29, 7:54 pm, climber....@gmail.com wrote:
>
>
>
> > Hi all,
> >   I am trying to simulate a concurrent resource allocator with Ada's
> > task and protected type.
> >   The idea is simple: there are several resource available (total
> > number is N=8), shared by user_thread. Each user first randomly
> > generate 4 numbers ranged between 0 and 7, which would represent the
> > resource needed to access. The resources therefore are implemented by
> > semaphores, which in turn implemented by protected objects.
> >   The user_thread is not going to interact with each other by making
> > entry calls, so no entry is defined in tasks. The task representing
> > the user_thread simply select a procedure defined in the task body non-
> > deterministically, until the counter, 'rounds' reached its limit.  I
> > am now only testing a single task for execution. However, the outcome
> > is very confusing:
> >   - the last sentence of the task body, which is a put_line statement
> > is never executed, but the task terminates.
> >  - also, the per task counter 'rounds', was never incremented, it
> > stays the same as the initial value. The only procedure increment
> > 'rounds' is procedure 'use_res', but the procedure was never called
> > during the execution.  If you notice the entry condition for the while
> > loop, 'while rounds<2 loop', how could it get out of the loop if
> > 'rounds' was never incremented??  why the program still terminates??
> >   I am stuck on this issue. Although i am not new to programming, I do
> > not know Ada very well. Could someone help me out here?
>
> The program runs fine with a few modifications to your conditions.
> Note that I changed the index to a modular type. This eliminates any
> need to check for out of bounds indexing due to your arithmetic.
> Modular arithmetic wraps to values within the type definition.
>
> Your program contains two unused variables: Rd and Index. You should
> clean up the unused clutter.
>
> Your original version never incremented Rounds because the conditions
> for Use_Res were never satisfied.
>
> with Ada.Text_Io;
> with Ada.Numerics.Discrete_Random;
> use  Ada.Text_Io;
>
> procedure Multi_Res_Alloc_A is
>
>    N  : constant := 8; -- number of resources to share
>
>    type Res_Index is mod N;
>
>    type Bool_Array is array (Res_Index) of Boolean;
>
>    subtype N_Res is Integer range 0..99;
>    package Random_Int is new Ada.Numerics.Discrete_Random (N_Res);
>    use Random_Int;
>    G : Generator;
>
>    -- -------------------------------------
>    protected type Semaphore is
>       entry P;
>       entry V;
>    private
>       Value : Boolean := True;
>    end Semaphore;
>    -- -------------------------------------
>    protected body Semaphore is
>       entry P when Value is
>       begin
>          Value:= False;
>       end P;
>
>       entry V when not Value is
>       begin
>          Value:= True;
>       end V;
>    end Semaphore;
>    -- -------------------------------------
>    R : array (Res_Index) of Semaphore;
>
>    -- -------------------------------------
>    task type User_Thread ;
>
>    task body User_Thread is
>
>       Rounds : Integer    := 0;
>       Next,
>       I      : Integer;
>       State  : Integer    := - 1;
>       D      : Res_Index    := 0;
>       Needs  : Bool_Array := (Others => False);
>
>       X : Integer := 0;
>       C : Integer := 0;
>
>       procedure Acquire_No_Wait is
>       begin
>          D:=D+1;
>       end Acquire_No_Wait;
>
>       procedure Acquire_Wait is
>       begin
>          R(D).P;
>          D:=D+1;
>       end Acquire_Wait;
>
>       procedure Use_Res is
>       begin
>          State:=1;
>          Put_Line("******* Eating now *******");
>          while D>0 loop
>             D:=D-1;
>             if Needs(D) then
>                R(D).V;
>             end if;
>          end loop;
>          State:=-1;
>          Rounds:=Rounds+1;
>       end Use_Res;
>
>       procedure Want_Res is
>       begin
>          C:=0;
>          State:=0;
>          Reset(G);  -- start the generator in a unique state in each
> run
>          while C<4 loop
>             --random x
>             X := Random(G);
>             Needs(Res_Index(X mod N)):= True;
>             C:=C+1;
>          end loop;
>       end Want_Res;
>
>    begin
>
>       Put_Line("-->> Enter task body..");
>       Reset(G);  -- reset the random number generator
>       while Rounds<2 loop
>          Next := Random(G) mod 4;   -- number of actions per task = 4
>          Put_Line("  >> next =" & Integer'Image(Next) & ";  state =" &
> Integer'Image(State));
>
>          if Next=0 and State=0 and not Needs(D) then
>             Put_Line("------> acquiring resource,no waiting <------");
>             Acquire_No_Wait;
>          end if;
>
>          if Next=1 and State=0 and Needs(D) then
>             Put_Line("------> acquire and waiting resource <------");
>             Acquire_Wait;
>          end if;
>
>          if Next=2 and State=0 then
>             Put_Line("------> USING resource <------");
>             Use_Res;
>          end if;
>
>          if Next=3 and State=-1 then
>             Put_Line("------> Want resource(s) <------");
>             Want_Res;
>          end if;
>
>          --Put_Line(">> ****** rounds = " & INTEGER'Image(rounds) &
> "*******" );
>          Next:= (Next+1) mod 4;
>          I:=0;
>          Put_Line("    >>> next =" & Integer'Image(Next) & ";  state
> =" & Integer'Image(State));
>          while (I<3) and (Rounds<2) loop
>
>             if Next=0 and State=0 and not Needs(D) then
>                Put_Line("  >> acquiring resource,no waiting <------");
>                Acquire_No_Wait;
>             end if;
>
>             if Next=1 and State=0 and Needs(D)  then
>                Put_Line("  >> acquire and waiting resource <------");
>                Acquire_Wait;
>             end if;
>
>             if Next=2 and State=0 then
>                Put_Line("  >> USING resource <------");
>                Use_Res;
>             end if;
>
>             if Next=3 and State=-1 then
>                Put_Line("  >> Want resource(s) <------");
>                Want_Res;
>             end if;
>
>             --Put_Line(">> ****** rounds = " & INTEGER'Image(rounds) &
> "*******" );
>             Next:= (Next+1) mod 4;
>             Put_Line("   >>>> next =" & Integer'Image(Next) & ";
> state =" & Integer'Image(State));
>             I:=I+1;
>          end loop;
>          Put_Line("..... rounds =" & Integer'Image(Rounds) & "...." );
>       end loop;
>
>       Put_Line("TASK EXITS ::  rounds =" & Integer'Image(Rounds) &
> "...." );
>
>    end User_Thread;
>    -- -------------------------------------
>
>    U1 : User_Thread;
>
> begin
>    null;
> end Multi_Res_Alloc_A;
>
> Jim Rogers

Thank you Jim for modifying the program and making it work. I saw how
you modify the guarding conditions for the procedures. In fact, the
conditions are fine by themselves, because i wrote the same program in
Java. However, the modified program is working now. It indeed reminds
me that Ada probably follows the 'strict evaluation' rule when it
comes to the boolean expressions, so in
  if Next=1 and State=0 and D<N and Needs(D)  then ...
  Ada probably would evaluate all the predicates connect by logical
AND, but as soon as D=N is reached, array index for Needs(_) would go
out of bound (because Needs is defined to be  array(0..N-1) of
boolean). I am just guessing here.

This would not cause exceptions in Java, because java follows the non-
strict evaluation rule.

tony



^ permalink raw reply	[flat|nested] 8+ messages in thread

* Re: Very confused by Ada tasking, can not explain the execution outcome.
  2008-08-30  5:12 ` Jeffrey R. Carter
@ 2008-08-30  9:42   ` climber.cui
  2008-08-30 13:40     ` Georg Bauhaus
  0 siblings, 1 reply; 8+ messages in thread
From: climber.cui @ 2008-08-30  9:42 UTC (permalink / raw)


On Aug 30, 1:12 am, "Jeffrey R. Carter"
<spam.jrcarter....@spam.acm.org> wrote:
> climber....@gmail.com wrote:
> >   - the last sentence of the task body, which is a put_line statement
> > is never executed, but the task terminates.
> >  - also, the per task counter 'rounds', was never incremented, it
> > stays the same as the initial value. The only procedure increment
> > 'rounds' is procedure 'use_res', but the procedure was never called
> > during the execution.  If you notice the entry condition for the while
> > loop, 'while rounds<2 loop', how could it get out of the loop if
> > 'rounds' was never incremented??  why the program still terminates??
>
> If an exception occurs in your task, the task will terminate silently. This is a
> way your task and program could terminate although it never increments Rounds
> nor executes its final statement.
>
> --
> Jeff Carter
> "If I could find a sheriff who so offends the citizens of Rock
> Ridge that his very appearance would drive them out of town ...
> but where would I find such a man? Why am I asking you?"
> Blazing Saddles
> 37
.
Thanks Jeff. It seems you are right.  Some exceptions occurs during
the task execution, and Ada is ignoring it. It is very likely to the
'array index out of bound'.  I doubt that Ada follows the strict
evaluation rules when it evaluates the boolean expressions, that is it
will evaluate every term(connected by logical operators),  like in:
  if  D<N and Needs(D)  then..
  Ada would evaluate both D<N and Needs(D). This could cause problem
sometimes if strict-evaluation rules are followed. Many languages
follows the non-strict evaluation rules, so if D<N is false, it will
not bother to evaluate Needs(D).

tony



^ permalink raw reply	[flat|nested] 8+ messages in thread

* Re: Very confused by Ada tasking, can not explain the execution outcome.
  2008-08-30  9:34   ` climber.cui
@ 2008-08-30 10:59     ` Damien Carbonne
  2008-08-31 13:37       ` Stephen Leake
  0 siblings, 1 reply; 8+ messages in thread
From: Damien Carbonne @ 2008-08-30 10:59 UTC (permalink / raw)


climber.cui@gmail.com a �crit :
> Thank you Jim for modifying the program and making it work. I saw how
> you modify the guarding conditions for the procedures. In fact, the
> conditions are fine by themselves, because i wrote the same program in
> Java. However, the modified program is working now. It indeed reminds
> me that Ada probably follows the 'strict evaluation' rule when it
> comes to the boolean expressions, so in
>   if Next=1 and State=0 and D<N and Needs(D)  then ...
>   Ada probably would evaluate all the predicates connect by logical
> AND, but as soon as D=N is reached, array index for Needs(_) would go
> out of bound (because Needs is defined to be  array(0..N-1) of
> boolean). I am just guessing here.

Use "and then" instead of "and" to obtain what Java does with "and" :
--> if Next=1 and then State=0 and then D<N and then Needs(D)  then ...

> 
> This would not cause exceptions in Java, because java follows the non-
> strict evaluation rule.
> 
> tony



^ permalink raw reply	[flat|nested] 8+ messages in thread

* Re: Very confused by Ada tasking, can not explain the execution outcome.
  2008-08-30  9:42   ` climber.cui
@ 2008-08-30 13:40     ` Georg Bauhaus
  0 siblings, 0 replies; 8+ messages in thread
From: Georg Bauhaus @ 2008-08-30 13:40 UTC (permalink / raw)


climber.cui@gmail.com wrote:
> On Aug 30, 1:12 am, "Jeffrey R. Carter"

>> If an exception occurs in your task, the task will terminate silently. This is a
>> way your task and program could terminate although it never increments Rounds
>> nor executes its final statement.

> Thanks Jeff. It seems you are right.  Some exceptions occurs during
> the task execution, and Ada is ignoring it.

Ada is not actually ignoring exceptions in tasks; the program
is following the Ada rules: Add these lines,

      Put_Line("TASK EXITS ::  rounds =" & INTEGER'Image(rounds) &
        "...." );

   exception
      when X: others =>
         Put_Line("TASK failed due to " &
           Ada.Exceptions.Exception_Information(X));
   end User_thread;

and you should see something like
TASK failed due to Exception name: CONSTRAINT_ERROR
Message: multi_res_alloc_a.adb:131 index check failed

So, yes,
> It is very likely to the
> 'array index out of bound'.



>  I doubt that Ada follows the strict
> evaluation rules when it evaluates the boolean expressions,

you would specify short circuit evaluation using "and then"
etc. as explained by Damien Carbonne;  Ada follows the rules
defined in the LRM, section

 "4.5.1 Logical Operators and Short-circuit Control Forms"




^ permalink raw reply	[flat|nested] 8+ messages in thread

* Re: Very confused by Ada tasking, can not explain the execution  outcome.
  2008-08-30 10:59     ` Damien Carbonne
@ 2008-08-31 13:37       ` Stephen Leake
  0 siblings, 0 replies; 8+ messages in thread
From: Stephen Leake @ 2008-08-31 13:37 UTC (permalink / raw)


Damien Carbonne <damien.carbonne@free.fr> writes:

> climber.cui@gmail.com a �crit :
>> Thank you Jim for modifying the program and making it work. I saw how
>> you modify the guarding conditions for the procedures. In fact, the
>> conditions are fine by themselves, because i wrote the same program in
>> Java. However, the modified program is working now. It indeed reminds
>> me that Ada probably follows the 'strict evaluation' rule when it
>> comes to the boolean expressions, so in
>>   if Next=1 and State=0 and D<N and Needs(D)  then ...
>>   Ada probably would evaluate all the predicates connect by logical
>> AND, but as soon as D=N is reached, array index for Needs(_) would go
>> out of bound (because Needs is defined to be  array(0..N-1) of
>> boolean). I am just guessing here.
>
> Use "and then" instead of "and" to obtain what Java does with "and" :
> --> if Next=1 and then State=0 and then D<N and then Needs(D)  then ...

A better style is to use 'and then' only when it is actually necessary
to protect against an exception. In this case, that would be:

    if Next=1 and State=0 and (D<N and then Needs(D))  then ...

since Needs(D) will raise an exception if D<N is false.

That lets the compiler more completely optimize the full expression;
'Next=1' and 'State=0' can be done in parallel register operations. 

It also tells the reader that they should consider exceptions for the
D part of the expression, but they _don't_ have to consider them for
the other part.

Ada is a very expressive language; it helps both the reader and the
compiler if the code is precise.

-- 
-- Stephe



^ permalink raw reply	[flat|nested] 8+ messages in thread

end of thread, other threads:[~2008-08-31 13:37 UTC | newest]

Thread overview: 8+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2008-08-30  1:54 Very confused by Ada tasking, can not explain the execution outcome climber.cui
2008-08-30  4:17 ` jimmaureenrogers
2008-08-30  9:34   ` climber.cui
2008-08-30 10:59     ` Damien Carbonne
2008-08-31 13:37       ` Stephen Leake
2008-08-30  5:12 ` Jeffrey R. Carter
2008-08-30  9:42   ` climber.cui
2008-08-30 13:40     ` Georg Bauhaus

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox