comp.lang.ada
 help / color / mirror / Atom feed
* Combining entry_call, accept_statment and terminate_statment
@ 2004-03-29 19:41 Lutz Donnerhacke
  2004-03-29 22:04 ` Randy Brukardt
  2004-03-30  0:33 ` James Rogers
  0 siblings, 2 replies; 15+ messages in thread
From: Lutz Donnerhacke @ 2004-03-29 19:41 UTC (permalink / raw)


Sorry, but I do not get it:

I have a protected type with an entry:

  protected type PT is
     entry X;
  end PT;
  p : PT;

Now I have to construct a task dealing with new data from the protected
type, an call from other tasks or the termination of the parent task.
  task type TT is
     entry Config;
  end TT;
  
  task body TT is
  begin
     loop
        select
	   p.X;
	   -- dealing with new data
	or accept Config;
	   -- modify the task
	or terminate;
	end select;
     end loop;
  end TT;

Unfortunly this is not allowed. Either accept and terminate or an entry_call
and a delay can be combinded. I wonder how to solve such as deadlock. It
should be a common idiom, but I had no luck in choosing searching keywords.

Any hint?



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

* Re: Combining entry_call, accept_statment and terminate_statment
  2004-03-29 19:41 Combining entry_call, accept_statment and terminate_statment Lutz Donnerhacke
@ 2004-03-29 22:04 ` Randy Brukardt
  2004-03-29 23:19   ` Mark Lorenzen
                     ` (2 more replies)
  2004-03-30  0:33 ` James Rogers
  1 sibling, 3 replies; 15+ messages in thread
From: Randy Brukardt @ 2004-03-29 22:04 UTC (permalink / raw)


"Lutz Donnerhacke" <lutz@iks-jena.de> wrote in message
news:slrnc6guve.g7p.lutz@belenus.iks-jena.de...
> Unfortunly this is not allowed. Either accept and terminate or an
entry_call
> and a delay can be combinded. I wonder how to solve such as deadlock. It
> should be a common idiom, but I had no luck in choosing searching
keywords.

I can't tell you how to work around it, but I can tell you why it's not
allowed - the implementation would be very slow.

During the Ada 9X process, there was a proposal for a multi-way entry call.
(A more limited version of what you're asking for here.) The three
User-Implementer teams were asked to analyze the implementation effort. (The
reports are somewhere in the AdaIC archives, if you're interested.) All
three teams decided that the run-time cost of the feature would be high (it
would be close to polling). Since the real-time users that were requesting
the feature need high performance, it was eventually dropped as impractical.

I recently ran into a similar problem. All I wanted was an entry call with
terminate. The (ugly) solution I used was to add an explicit Quit entry to
the task, and I changed the select into a polling loop:

    loop
         select
             accept Quit;
             exit;
         else null;
         end select;
         select
             PO.Get_New_Operation (...);
             Do_Operation (...);
         or
             delay 0.06;
         end select;
    end loop;

That's effectively what the implementation of such a select would have to do
anyway, so there's not much extra cost.

But I'd say that you probably have a design problem if you have a task that
is both calling and accepting at the same time. That's pretty weird (unless
the accepts are purely for task control, as above). It's preferable that
each task be either a server (accepting entries) or a client (calling
entries), but not both. Analysis is complicated if you have both.

                      Randy.






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

* Re: Combining entry_call, accept_statment and terminate_statment
  2004-03-29 23:19   ` Mark Lorenzen
@ 2004-03-29 23:14     ` Robert I. Eachus
  0 siblings, 0 replies; 15+ messages in thread
From: Robert I. Eachus @ 2004-03-29 23:14 UTC (permalink / raw)


Mark Lorenzen wrote:
> "Randy Brukardt" <randy@rrsoftware.com> writes:
> 
> [cut]
> 
> 
>>But I'd say that you probably have a design problem if you have a task that
>>is both calling and accepting at the same time. That's pretty weird (unless
>>the accepts are purely for task control, as above). It's preferable that
>>each task be either a server (accepting entries) or a client (calling
>>entries), but not both. Analysis is complicated if you have both.
>>
>>                      Randy.
> 
> 
> To me, this seems to be a severe design limitation. Isn't it normal to
> have a task acting as a filter, i.e. reading data from a PO,
> manipulating the data and the writing the manipulated data to a PO?
> This could f.x. be a task implementing a (de)multiplexer.
> 
> - Mark Lorenzen

I was going to say that the special case of a "transformer" that accepts 
a call and then immediately makes a call, usually in a loop is an 
exception to this rule.  But you beat me to it.

If you create a call graph for tasks and protected objects each node 
should either make calls or be the target of calls, with this one 
exception where the net number of calls is always negative.  If you want 
to think of these special cases as arcs instead of nodes, that works too.

Oh, and there is a different exception which is seldom used.  You may 
requeue a call to you as a call to a different entry (common) or to an 
entry of another task.  I have no idea of how to represent or analyze 
that last case.

-- 

                                           Robert I. Eachus

"The terrorist enemy holds no territory, defends no population, is 
unconstrained by rules of warfare, and respects no law of morality. Such 
an enemy cannot be deterred, contained, appeased or negotiated with. It 
can only be destroyed--and that, ladies and gentlemen, is the business 
at hand."  -- Dick Cheney




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

* Re: Combining entry_call, accept_statment and terminate_statment
  2004-03-29 22:04 ` Randy Brukardt
@ 2004-03-29 23:19   ` Mark Lorenzen
  2004-03-29 23:14     ` Robert I. Eachus
  2004-03-30  7:26   ` Lutz Donnerhacke
  2004-03-30  7:29   ` Lutz Donnerhacke
  2 siblings, 1 reply; 15+ messages in thread
From: Mark Lorenzen @ 2004-03-29 23:19 UTC (permalink / raw)


"Randy Brukardt" <randy@rrsoftware.com> writes:

[cut]

>
> But I'd say that you probably have a design problem if you have a task that
> is both calling and accepting at the same time. That's pretty weird (unless
> the accepts are purely for task control, as above). It's preferable that
> each task be either a server (accepting entries) or a client (calling
> entries), but not both. Analysis is complicated if you have both.
>
>                       Randy.

To me, this seems to be a severe design limitation. Isn't it normal to
have a task acting as a filter, i.e. reading data from a PO,
manipulating the data and the writing the manipulated data to a PO?
This could f.x. be a task implementing a (de)multiplexer.

- Mark Lorenzen



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

* Re: Combining entry_call, accept_statment and terminate_statment
  2004-03-29 19:41 Combining entry_call, accept_statment and terminate_statment Lutz Donnerhacke
  2004-03-29 22:04 ` Randy Brukardt
@ 2004-03-30  0:33 ` James Rogers
  1 sibling, 0 replies; 15+ messages in thread
From: James Rogers @ 2004-03-30  0:33 UTC (permalink / raw)


Lutz Donnerhacke <lutz@iks-jena.de> wrote in
news:slrnc6guve.g7p.lutz@belenus.iks-jena.de: 

> Sorry, but I do not get it:
> 
> I have a protected type with an entry:
> 
>   protected type PT is
>      entry X;
>   end PT;
>   p : PT;
> 
> Now I have to construct a task dealing with new data from the
> protected type, an call from other tasks or the termination of the
> parent task. 

I ran into this problem when illustrating a producer/consumer
example that emulates a just in time production line. I wanted the
producing tasks to be able to write to a protected object at a
specified rate, but also be able to be shut down through a
rendezvous. 

Following is my solution:

--------------------------------------------------------------------------
-- Production Lines
--------------------------------------------------------------------------
   with Con_Bon_Pads;

   package Production_Lines is
   
      package Tuner_Bufs renames Con_Bon_Pads.Tuner_Buffers;
      package Ps_Bufs renames Con_Bon_pads.Ps_Buffers;
   
      task type Tuners is
         entry Start(Destination : in Tuner_Bufs.Parts_Buf_Ptr);
         entry Stop;
      end Tuners;
   
      task type Power_Supplies is
         entry Start(Destination : in Ps_Bufs.Parts_Buf_Ptr);
         entry Stop;
      end Power_Supplies;
   
      task type Radios is
         entry Start(Tuner_Src : in Tuner_Bufs.Parts_Buf_Ptr;
                     PS_Src    : in Ps_Bufs.Parts_Buf_Ptr);
         entry Stop;
      end Radios;
   end Production_Lines;

   with Assemblies; use Assemblies;
   with Ada.Text_Io;

   package body Production_Lines is
   
   
   --------------------
   -- Power_Supplies --
   --------------------
   
      task body Power_Supplies is
         Con_Bon : Ps_Bufs.Parts_Buf_Ptr;
         Unit    : Assemblies.Power_Supply;
         Blocked : Boolean := False;
      begin
         accept Start(Destination : in Ps_Bufs.Parts_Buf_Ptr)
         do
            Con_Bon := Destination;
         end Start;
      Build:
         loop       
            select
               accept Stop;
               Ada.Text_Io.Put_Line("Power Supply Production Stopped.");
               exit Build;
            else
               delay 1.0;
               if not Blocked then
                  Set_Serial_Number(Unit);
               end if;
               select
                  Con_Bon.Put(Unit);
                  Blocked := False;
               or
                  delay 0.2;
                  Blocked := True;
               end select;
               if not Blocked then
                  Print(Unit);
               end if;
            end select;
         end loop Build;
      
      end Power_Supplies;
   
   ------------
   -- Radios --
   ------------
   
      task body Radios is
         Power_Supply_Unit : Assemblies.Power_Supply;
         Tuner_Unit        : Assemblies.Tuner;
         Unit              : Assemblies.Radio;
         Ps_Buf            : Ps_Bufs.Parts_Buf_Ptr;
         Tuner_Buf         : Tuner_Bufs.Parts_Buf_Ptr;
         Got_T, Got_P      : Boolean := False;
      
      begin
         accept Start(Tuner_Src : in Tuner_Bufs.Parts_Buf_Ptr;
                      Ps_Src    : in Ps_Bufs.Parts_Buf_Ptr) do
            Ps_Buf := Ps_Src;
            Tuner_Buf := Tuner_Src;
         end Start;
      Build:
         loop
            select
               accept Stop;
               Ada.Text_Io.Put_Line("Radio Production Stopped.");
               exit Build;
            else
               if not Got_p then
                  select
                     Ps_Buf.Get(Power_Supply_Unit);
                     Got_P := True;
                  or 
                     delay 1.5;
                  end select;
               end if;
               if not Got_T then
                  select
                     Tuner_Buf.Get(Tuner_Unit);
                     got_T := True;
                  or 
                     delay 1.5;
                  end select;
               end if;
            end select;
            if Got_t and Got_P then
               delay 1.25;
               Unit := Radio_Constructor.Assemble_Radio(Tuner_Unit,
                                                        Power_Supply_Unit);
               Set_Serial_Number(Unit);
               Print(Unit);
               Got_T := False;
               Got_P := False;
            end if;
         end loop Build;
      end Radios;
   
   ------------
   -- Tuners --
   ------------
   
      task body Tuners is
         Con_Bon : Tuner_Bufs.Parts_Buf_Ptr;
         Unit    : Assemblies.Tuner;
         Blocked : Boolean := False;
      begin
         accept Start(Destination : in Tuner_Bufs.Parts_Buf_Ptr)
         do
            Con_Bon := Destination;
         end Start;
      Build:
         loop
            select
               accept Stop;
               Ada.Text_Io.Put_Line("Tuner Production Stopped.");
               exit Build;
            else
               delay 1.5;
               if not Blocked then
                  Set_Serial_Number(Unit);
               end if;
               select
                  Con_Bon.Put(Unit);
                  Blocked := False;
               or
                  delay 0.2;
                  Blocked := True;
               end select;
               if not Blocked then
                  Print(Unit);
               end if;
            end select;
         end loop Build;
      
      end Tuners;
   end Production_Lines;

Jim Rogers



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

* Re: Combining entry_call, accept_statment and terminate_statment
  2004-03-29 22:04 ` Randy Brukardt
  2004-03-29 23:19   ` Mark Lorenzen
@ 2004-03-30  7:26   ` Lutz Donnerhacke
  2004-03-30 20:04     ` Randy Brukardt
  2004-03-30  7:29   ` Lutz Donnerhacke
  2 siblings, 1 reply; 15+ messages in thread
From: Lutz Donnerhacke @ 2004-03-30  7:26 UTC (permalink / raw)


* Randy Brukardt wrote:
> "Lutz Donnerhacke" <lutz@iks-jena.de> wrote in message
>> Unfortunly this is not allowed. Either accept and terminate or an
>> entry_call and a delay can be combinded. I wonder how to solve such as
>> deadlock. It should be a common idiom, but I had no luck in choosing
>> searching keywords.
>
> I can't tell you how to work around it, but I can tell you why it's not
> allowed - the implementation would be very slow.

IBTD. accept_statements and entry_call_statements as well as the
terminate_statement deal with queuing (wait queues). AFAIK the linux kernel
does implement all such "select" constructs by such wait queues and does not
have much trouble with it.

Of course accept and terminate queues are the other way around than entry
calls.

> During the Ada 9X process, there was a proposal for a multi-way entry
> call. (A more limited version of what you're asking for here.) The three
> User-Implementer teams were asked to analyze the implementation effort.
> (The reports are somewhere in the AdaIC archives, if you're interested.)
> All three teams decided that the run-time cost of the feature would be
> high (it would be close to polling). Since the real-time users that were
> requesting the feature need high performance, it was eventually dropped
> as impractical.

I do see the problem now: entry_barriers on entry_calls to protected types
or guarded task accepts are evaluated by the calling task. Therefore wait
queues are not possible. Polling is required.

This explains an other problem, I came across:

>     loop
>          select
>              accept Quit;
>              exit;
>          else null;
>          end select;
>          select
>              PO.Get_New_Operation (...);
>              Do_Operation (...);
>          or
>              delay 0.06;
>          end select;
>     end loop;

That's exactly my current implementation. But I increased the delay and
noticed, that the entry_barrier of the delayed entry_call is evaluated only
once on startup of the timed entry call. If the barrier becomes true while
the delay is running, the delay is not aborted.

A reason for this strange behavior might be a call to a protected function
in the entry_barrier itself.

> But I'd say that you probably have a design problem if you have a task that
> is both calling and accepting at the same time. That's pretty weird (unless
> the accepts are purely for task control, as above). It's preferable that
> each task be either a server (accepting entries) or a client (calling
> entries), but not both. Analysis is complicated if you have both.

I have a buffer, filled by a single task an read by an unknown number of
tasks. It's a stream multiplier implemented using a ringbuffer structure.

The writer task fills a proteced type (ringbuffer) using an protected
procedure, while the reader tasks call the protected procedure to get there
data.

In order to prevent polling, I implemented a second protected type
(constraint with an anonymous access to the ringbuffer) to encapsulate the
reader position variable and use it for an entry barrier on this second type.

If I had to stick to polling anyway, I can drop the second proteced type and
poll the protected ringbuffer directly.



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

* Re: Combining entry_call, accept_statment and terminate_statment
  2004-03-29 22:04 ` Randy Brukardt
  2004-03-29 23:19   ` Mark Lorenzen
  2004-03-30  7:26   ` Lutz Donnerhacke
@ 2004-03-30  7:29   ` Lutz Donnerhacke
  2004-03-30  8:11     ` tmoran
  2004-03-30 11:45     ` Lutz Donnerhacke
  2 siblings, 2 replies; 15+ messages in thread
From: Lutz Donnerhacke @ 2004-03-30  7:29 UTC (permalink / raw)


* Randy Brukardt wrote:
> "Lutz Donnerhacke" <lutz@iks-jena.de> wrote in message
>> Unfortunly this is not allowed. Either accept and terminate or an
>> entry_call and a delay can be combinded. I wonder how to solve such as
>> deadlock. It should be a common idiom, but I had no luck in choosing
>> searching keywords.
>
> I can't tell you how to work around it, but I can tell you why it's not
> allowed - the implementation would be very slow.

IBTD. accept_statements and entry_call_statements as well as the
terminate_statement deal with queuing (wait queues). AFAIK the linux kernel
does implement all such "select" constructs by such wait queues and does not
have much trouble with it.

Of course accept and terminate queues are the other way around than entry
calls.

> During the Ada 9X process, there was a proposal for a multi-way entry
> call. (A more limited version of what you're asking for here.) The three
> User-Implementer teams were asked to analyze the implementation effort.
> (The reports are somewhere in the AdaIC archives, if you're interested.)
> All three teams decided that the run-time cost of the feature would be
> high (it would be close to polling). Since the real-time users that were
> requesting the feature need high performance, it was eventually dropped
> as impractical.

I do see the problem now: entry_barriers on entry_calls to protected types
or guarded task accepts are evaluated by the calling task. Therefore wait
queues are not possible. Polling is required.

This explains an other problem, I came across:

>     loop
>          select
>              accept Quit;
>              exit;
>          else null;
>          end select;
>          select
>              PO.Get_New_Operation (...);
>              Do_Operation (...);
>          or
>              delay 0.06;
>          end select;
>     end loop;

That's exactly my current implementation. But I increased the delay and
noticed, that the entry_barrier of the delayed entry_call is evaluated only
once on startup of the timed entry call. If the barrier becomes true while
the delay is running, the delay is not aborted.

A reason for this strange behavior might be a call to a protected function
in the entry_barrier itself.

> But I'd say that you probably have a design problem if you have a task that
> is both calling and accepting at the same time. That's pretty weird (unless
> the accepts are purely for task control, as above). It's preferable that
> each task be either a server (accepting entries) or a client (calling
> entries), but not both. Analysis is complicated if you have both.

I have a buffer, filled by a single task and read by an unknown number of
tasks. It's a stream multiplier implemented using a ringbuffer structure.

The writer task fills a proteced type (ringbuffer) using an protected
procedure, while the reader tasks call the protected procedure to get their
data.

In order to prevent polling, I implemented a second protected type
(constrainted with an anonymous access to the ringbuffer) to encapsulate the
reader position variable and use it for an entry barrier on this second type.

If I had to stick to polling anyway, I can drop the second proteced type and
poll the protected ringbuffer directly.



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

* Re: Combining entry_call, accept_statment and terminate_statment
  2004-03-30  7:29   ` Lutz Donnerhacke
@ 2004-03-30  8:11     ` tmoran
  2004-03-30 11:45     ` Lutz Donnerhacke
  1 sibling, 0 replies; 15+ messages in thread
From: tmoran @ 2004-03-30  8:11 UTC (permalink / raw)


> task body TT is
> begin
>    loop
>       select
>          p.X;
>          -- dealing with new data
>       or accept Config;
>          -- modify the task
>       or terminate;
>       end select;
>    end loop;
> end TT;
   It seems to me there are three kinds of inputs TT has to deal with:
regular data, please-reconfig, and please-terminate.  From that point of
view, TT could just deal with one supplier of input, rather than the three
different suppliers in the current code:
  task body TT is
  begin
     loop
       p.X(What_To_Do, Possible_Data);
       case What_To_Do is
         when Regular_Data => ... -- dealing with new data
         when Reconfigure  => ... -- modify the task
         when Please_Terminate => exit;
       end case;
     end loop;
  end TT;

The protected object p then has to convey more heterogeneous information,
and may need to use Task_IDs if it needs to deliver different info to
different callers, but it will be a queueing, rather than polling, solution.



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

* Re: Combining entry_call, accept_statment and terminate_statment
  2004-03-30  7:29   ` Lutz Donnerhacke
  2004-03-30  8:11     ` tmoran
@ 2004-03-30 11:45     ` Lutz Donnerhacke
  1 sibling, 0 replies; 15+ messages in thread
From: Lutz Donnerhacke @ 2004-03-30 11:45 UTC (permalink / raw)


* Lutz Donnerhacke wrote:
> In order to prevent polling, I implemented a second protected type
> (constrainted with an anonymous access to the ringbuffer) to encapsulate
> the reader position variable and use it for an entry barrier on this
> second type.

Polling is not necessary. It's important to transfer caller information into
the entry_barrier, and this can be done using an entry family:

package PT is
   subtype Index is Integer range 1 .. 5;

   protected type T is
      procedure Set(x : Integer);
      entry Get(Index)(x : out Integer);
   private
      p : Integer := 0;
   end T;
end PT;
      
package body PT is
   protected body T is
      procedure Set(x : Integer) is
      begin
         p := x;
      end Set;
      
      entry Get(for i in Index)(x : out Integer) when p >= i is
      begin
         x := p;
      end Get;
   end T;
end PT;

with Ada.Text_IO; use Ada.Text_IO;
with PT;

procedure test_pt is
   test : PT.T;
   
   task type TT is
      entry Name(c : Character);
   end TT;

   task body TT is
      n : Character;
      i : Integer;
      d : PT.Index;
   begin
      accept Name(c : Character) do
         n := c;
      end Name;

      d := Character'Pos(n) - Character'Pos('a');
      Put_Line(n & ": Uses index" & d'Img);

      loop
         delay 0.1;
         Put_Line(n & ": Reading");
         test.Get(d)(i);
         Put_Line(n & ": Got" & i'Img);
         exit when i > d;
      end loop;
      Put_Line(n & ": Exit");
   end TT;

   t : array(Character'('a') .. 'f') of TT;
begin
   for i in t'Range loop
      Put_Line("Naming " & i);
      t(i).Name(i);
   end loop;

   for i in Integer range 0 .. 10 loop
      delay 0.25;
      Put_Line("Setting" & i'Img);
      test.Set(i);
   end loop;
end test_pt;

Please do not blame me for calling Ada.Text_IO.Put_Line without
synchronisation.



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

* Re: Combining entry_call, accept_statment and terminate_statment
  2004-03-30  7:26   ` Lutz Donnerhacke
@ 2004-03-30 20:04     ` Randy Brukardt
  2004-03-30 22:47       ` Lutz Donnerhacke
  2004-03-31  6:39       ` Jean-Pierre Rosen
  0 siblings, 2 replies; 15+ messages in thread
From: Randy Brukardt @ 2004-03-30 20:04 UTC (permalink / raw)


"Lutz Donnerhacke" <lutz@iks-jena.de> wrote in message
news:slrnc6i89d.o5.lutz@taranis.iks-jena.de...
...
> That's exactly my current implementation. But I increased the delay and
> noticed, that the entry_barrier of the delayed entry_call is evaluated
only
> once on startup of the timed entry call. If the barrier becomes true while
> the delay is running, the delay is not aborted.
>
> A reason for this strange behavior might be a call to a protected function
> in the entry_barrier itself.

Barriers of a PO are re-evaluated whenever a protected action ends, and when
an entry is called. A barrier which can change state without a protected
action ending is incorrect and may not work properly.

If there is a protected action ending (completion of a protected entry or
procedure call - a protected function cannot change the state of a protected
object) that is changing the state of the barrier, then the delay should end
and the entry call proceed. If that doesn't happen, that's a bug in the
compiler you're using.

                        Randy.






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

* Re: Combining entry_call, accept_statment and terminate_statment
  2004-03-30 20:04     ` Randy Brukardt
@ 2004-03-30 22:47       ` Lutz Donnerhacke
  2004-03-31  9:03         ` Dmitry A. Kazakov
  2004-03-31  6:39       ` Jean-Pierre Rosen
  1 sibling, 1 reply; 15+ messages in thread
From: Lutz Donnerhacke @ 2004-03-30 22:47 UTC (permalink / raw)


* Randy Brukardt wrote:
> "Lutz Donnerhacke" <lutz@iks-jena.de> wrote in message
>> That's exactly my current implementation. But I increased the delay and
>> noticed, that the entry_barrier of the delayed entry_call is evaluated
>> only once on startup of the timed entry call. If the barrier becomes
>> true while the delay is running, the delay is not aborted.
>>
>> A reason for this strange behavior might be a call to a protected function
>> in the entry_barrier itself.
>
> Barriers of a PO are re-evaluated whenever a protected action ends, and when
> an entry is called. A barrier which can change state without a protected
> action ending is incorrect and may not work properly.

So cascading of protected types will not work.

My incorrect version was:

   protected type Ringbuffer is
      procedure Put(data : in String);
      procedure Get(data : out Buffer; last : out Extended_Buffer_Offset;
        missed : out Absolute_Position; pos : in out Absolute_Position);
      function Is_New(pos : Absolute_Position) return Boolean;
   private
      buf : Buffer;
      start, stop : Absolute_Position := Absolute_Position'First;
   end Ringbuffer;
   
   protected type Read_Context(ringbuf : access Ringbuffer) is
      entry Get(data : out Buffer; last : out Extended_Buffer_Offset;
        missed : out Absolute_Position);
   private
      pos : Absolute_Position := Absolute_Position'First;
   end Read_Context;

   protected body Read_Context is
      entry Get(
        data : out Buffer; last : out Extended_Buffer_Offset;
        missed : out Absolute_Position
      ) when ringbuf.Is_New(pos) is
      begin
         ringbuf.Get(data, last, missed, pos);
      end Get;
   end Read_Context;



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

* Re: Combining entry_call, accept_statment and terminate_statment
  2004-03-30 20:04     ` Randy Brukardt
  2004-03-30 22:47       ` Lutz Donnerhacke
@ 2004-03-31  6:39       ` Jean-Pierre Rosen
  1 sibling, 0 replies; 15+ messages in thread
From: Jean-Pierre Rosen @ 2004-03-31  6:39 UTC (permalink / raw)


[-- Warning: decoded text below may be mangled, UTF-8 assumed --]
[-- Attachment #1: Type: text/plain, Size: 757 bytes --]


"Randy Brukardt" <randy@rrsoftware.com> a �crit dans le message de news:106jkmlj2g6ik57@corp.supernews.com...
> Barriers of a PO are re-evaluated whenever a protected action ends, and when
> an entry is called. A barrier which can change state without a protected
> action ending is incorrect and may not work properly.
>
I would not describe this as "incorrect", but certainly you need to know what you are doing.
I do have one PO where a barrier state is external to the PO and can change without protected action. But the PO has a "begin null;
end" procedure whose name is "Reevaluate_Guards"...

-- 
---------------------------------------------------------
           J-P. Rosen (rosen@adalog.fr)
Visit Adalog's web site at http://www.adalog.fr





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

* Re: Combining entry_call, accept_statment and terminate_statment
  2004-03-30 22:47       ` Lutz Donnerhacke
@ 2004-03-31  9:03         ` Dmitry A. Kazakov
  2004-03-31  9:14           ` Lutz Donnerhacke
  0 siblings, 1 reply; 15+ messages in thread
From: Dmitry A. Kazakov @ 2004-03-31  9:03 UTC (permalink / raw)


On Tue, 30 Mar 2004 22:47:27 +0000 (UTC), Lutz Donnerhacke
<lutz@iks-jena.de> wrote:

>* Randy Brukardt wrote:
>> "Lutz Donnerhacke" <lutz@iks-jena.de> wrote in message
>>> That's exactly my current implementation. But I increased the delay and
>>> noticed, that the entry_barrier of the delayed entry_call is evaluated
>>> only once on startup of the timed entry call. If the barrier becomes
>>> true while the delay is running, the delay is not aborted.
>>>
>>> A reason for this strange behavior might be a call to a protected function
>>> in the entry_barrier itself.
>>
>> Barriers of a PO are re-evaluated whenever a protected action ends, and when
>> an entry is called. A barrier which can change state without a protected
>> action ending is incorrect and may not work properly.
>
>So cascading of protected types will not work.

They should, AFAIK.

>My incorrect version was:
>
>   protected type Ringbuffer is
>      procedure Put(data : in String);
>      procedure Get(data : out Buffer; last : out Extended_Buffer_Offset;
>        missed : out Absolute_Position; pos : in out Absolute_Position);
>      function Is_New(pos : Absolute_Position) return Boolean;
>   private
>      buf : Buffer;
>      start, stop : Absolute_Position := Absolute_Position'First;
>   end Ringbuffer;
>   
>   protected type Read_Context(ringbuf : access Ringbuffer) is
>      entry Get(data : out Buffer; last : out Extended_Buffer_Offset;
>        missed : out Absolute_Position);
>   private
>      pos : Absolute_Position := Absolute_Position'First;
>   end Read_Context;
>
>   protected body Read_Context is
>      entry Get(
>        data : out Buffer; last : out Extended_Buffer_Offset;
>        missed : out Absolute_Position
>      ) when ringbuf.Is_New(pos) is
>      begin
>         ringbuf.Get(data, last, missed, pos);
>      end Get;
>   end Read_Context;

Ringbuffer.Get(...); in Read_Context is an external call, so it should
start a new protected action, which would lead to re-evaluating the
barriers of ringbuf.all. So Read_Context.Get would result in
re-evaluation of the barriers of both objects. However, I cannot say
if ringbuf.Is_New will be called during a re-evaluation of the
barriers of Read_Context. But surely it won't, if ringbuff is touched
from outside.

[ tagged protected object could be very useful in cases like this.
Mix-in works poorly here. ]

--
Regards,
Dmitry Kazakov
www.dmitry-kazakov.de



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

* Re: Combining entry_call, accept_statment and terminate_statment
  2004-03-31  9:03         ` Dmitry A. Kazakov
@ 2004-03-31  9:14           ` Lutz Donnerhacke
  2004-03-31 12:22             ` Dmitry A. Kazakov
  0 siblings, 1 reply; 15+ messages in thread
From: Lutz Donnerhacke @ 2004-03-31  9:14 UTC (permalink / raw)


* Dmitry A Kazakov wrote:
> On Tue, 30 Mar 2004 22:47:27 +0000 (UTC), Lutz Donnerhacke
>>My incorrect version was:
>>
>>   protected type Ringbuffer is
>>      procedure Put(data : in String);
>>      procedure Get(data : out Buffer; last : out Extended_Buffer_Offset;
>>        missed : out Absolute_Position; pos : in out Absolute_Position);
>>      function Is_New(pos : Absolute_Position) return Boolean;
>>   private
>>      buf : Buffer;
>>      start, stop : Absolute_Position := Absolute_Position'First;
>>   end Ringbuffer;
>>   
>>   protected type Read_Context(ringbuf : access Ringbuffer) is
>>      entry Get(data : out Buffer; last : out Extended_Buffer_Offset;
>>        missed : out Absolute_Position);
>>   private
>>      pos : Absolute_Position := Absolute_Position'First;
>>   end Read_Context;
>>
>>   protected body Read_Context is
>>      entry Get(
>>        data : out Buffer; last : out Extended_Buffer_Offset;
>>        missed : out Absolute_Position
>>      ) when ringbuf.Is_New(pos) is
>>      begin
>>         ringbuf.Get(data, last, missed, pos);
>>      end Get;
>>   end Read_Context;
>
> Ringbuffer.Get(...); in Read_Context is an external call, so it should
> start a new protected action, which would lead to re-evaluating the
> barriers of ringbuf.all.

There are no barriers on Ringbuffer. The only barrier is on Read_Context.
And the barrier is neither reevaluated on a call to Ringbuffer.Put nor polled.

> So Read_Context.Get would result in re-evaluation of the barriers of both
> objects.

Read_Context.Get is never called after the first evaluation of the barrier.
The barrier is never reevaluated. So the system blocked forever.

> However, I cannot say if ringbuf.Is_New will be called during a
> re-evaluation of the barriers of Read_Context.

It will, but there is no reevaluated at all.

> But surely it won't, if ringbuff is touched from outside.

Ack.

> [ tagged protected object could be very useful in cases like this.
> Mix-in works poorly here. ]

Tagging doesn't provide anything useful in this context.
Please do not mix orthogonal concepts.

Entry families does provide the required behavior:
  An entry family call has two formal argument lists.
  The first one is evaluated before the barrier and therefor usable in the
  barrier itself. (That's the real issue on entry families.)
  The second one is evaluated after the barrier is evaluated to True.



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

* Re: Combining entry_call, accept_statment and terminate_statment
  2004-03-31  9:14           ` Lutz Donnerhacke
@ 2004-03-31 12:22             ` Dmitry A. Kazakov
  0 siblings, 0 replies; 15+ messages in thread
From: Dmitry A. Kazakov @ 2004-03-31 12:22 UTC (permalink / raw)


On Wed, 31 Mar 2004 09:14:12 +0000 (UTC), Lutz Donnerhacke
<lutz@iks-jena.de> wrote:

>* Dmitry A Kazakov wrote:
>> On Tue, 30 Mar 2004 22:47:27 +0000 (UTC), Lutz Donnerhacke
>>>My incorrect version was:
>>>
>>>   protected type Ringbuffer is
>>>      procedure Put(data : in String);
>>>      procedure Get(data : out Buffer; last : out Extended_Buffer_Offset;
>>>        missed : out Absolute_Position; pos : in out Absolute_Position);
>>>      function Is_New(pos : Absolute_Position) return Boolean;
>>>   private
>>>      buf : Buffer;
>>>      start, stop : Absolute_Position := Absolute_Position'First;
>>>   end Ringbuffer;
>>>   
>>>   protected type Read_Context(ringbuf : access Ringbuffer) is
>>>      entry Get(data : out Buffer; last : out Extended_Buffer_Offset;
>>>        missed : out Absolute_Position);
>>>   private
>>>      pos : Absolute_Position := Absolute_Position'First;
>>>   end Read_Context;
>>>
>>>   protected body Read_Context is
>>>      entry Get(
>>>        data : out Buffer; last : out Extended_Buffer_Offset;
>>>        missed : out Absolute_Position
>>>      ) when ringbuf.Is_New(pos) is
>>>      begin
>>>         ringbuf.Get(data, last, missed, pos);
>>>      end Get;
>>>   end Read_Context;
>>
>> Ringbuffer.Get(...); in Read_Context is an external call, so it should
>> start a new protected action, which would lead to re-evaluating the
>> barriers of ringbuf.all.
>
>There are no barriers on Ringbuffer. The only barrier is on Read_Context.
>And the barrier is neither reevaluated on a call to Ringbuffer.Put nor polled.

Of course, because Read_Context's barriers are re-evaluated on the
events related to the Read_Context, which is unreated to Ringbuffer.
Mix-in is not inheritance.

>> So Read_Context.Get would result in re-evaluation of the barriers of both
>> objects.
>
>Read_Context.Get is never called after the first evaluation of the barrier.
>The barrier is never reevaluated. So the system blocked forever.

It could, if you made a proxy in Read_Context for Put of Ringbuffer
and would use it instead.

>> However, I cannot say if ringbuf.Is_New will be called during a
>> re-evaluation of the barriers of Read_Context.
>
>It will, but there is no reevaluated at all.
>
>> But surely it won't, if ringbuff is touched from outside.
>
>Ack.
>
>> [ tagged protected object could be very useful in cases like this.
>> Mix-in works poorly here. ]
>
>Tagging doesn't provide anything useful in this context.
>Please do not mix orthogonal concepts.

It looks like Read_Context extending Ringbuffer or at least using the
events (a protected action end) of the Ringbuffer for its barriers.
The only possible way to do it without surprises is to inherit from
Ringbuffer.

>Entry families does provide the required behavior:
>  An entry family call has two formal argument lists.
>  The first one is evaluated before the barrier and therefor usable in the
>  barrier itself. (That's the real issue on entry families.)
>  The second one is evaluated after the barrier is evaluated to True.

If you want to use actual parameters in barriers, there is another way
- the requeue statement. But I do not see how it might help if a
barrier depends on some external event, as in your example.

--
Regards,
Dmitry Kazakov
www.dmitry-kazakov.de



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

end of thread, other threads:[~2004-03-31 12:22 UTC | newest]

Thread overview: 15+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2004-03-29 19:41 Combining entry_call, accept_statment and terminate_statment Lutz Donnerhacke
2004-03-29 22:04 ` Randy Brukardt
2004-03-29 23:19   ` Mark Lorenzen
2004-03-29 23:14     ` Robert I. Eachus
2004-03-30  7:26   ` Lutz Donnerhacke
2004-03-30 20:04     ` Randy Brukardt
2004-03-30 22:47       ` Lutz Donnerhacke
2004-03-31  9:03         ` Dmitry A. Kazakov
2004-03-31  9:14           ` Lutz Donnerhacke
2004-03-31 12:22             ` Dmitry A. Kazakov
2004-03-31  6:39       ` Jean-Pierre Rosen
2004-03-30  7:29   ` Lutz Donnerhacke
2004-03-30  8:11     ` tmoran
2004-03-30 11:45     ` Lutz Donnerhacke
2004-03-30  0:33 ` James Rogers

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