Google Groupes n'accepte plus les nouveaux posts ni abonnements Usenet. Les contenus de l'historique resteront visibles.

Private or public task ?

8 vues
Accéder directement au premier message non lu

Hibou57 (Yannick Duchêne)

non lue,
5 févr. 2010, 15:54:4205/02/2010
à
Hello Ada novel writers,

I'm starting to experiment with Ada tasking, which as I suggest, I've
never used so far (I will need at least it for a Windows API binding
and for a later VST binding... a VST is a kind of software synthesizer
for electronic music).

Let me explain the context before I introduce my though. I was playing
with a source from a tutorial.
This source : http://www.infres.enst.fr/~pautet/Ada95/e_c26_p2.ada
From this tutorial : http://www.infres.enst.fr/~pautet/Ada95/chap26.htm

Basically, three task running concurrently, display text to the
standard output stream. I've tried this one, and noticed that as the
output from each task was not atomic, output from all these tasks
ended to interlaced output on the console (notice the message each
task is displaying, made of three statement).

So I wanted to solve this, and added a protected object providing an
Put procedure which was displaying the same message, all three
statement in an atomic procedure.

It was fine and output was no more interlaced.

Later, I wanted to play a bit more and do the same with a task instead
of a protected object.

It was a task with a single entry and accept statement, Put, doing the
same, and a Terminate statement triggered when there was no more
request queued.

Later, I advised the task may terminates while some potential clients
may still be alive, or even the task may terminates before any client
had time to make any first request.

So I've decided to add a Aquire and Release entry, whose purpose was
to increase and decrease a counter, telling the output task server
that some potential clients were still alive or not. As a special
case, the initial zero value of the counter was not construed as a
terminating condition, for the same reason as explained above (some
clients may not had time to make an initial request) and it was only
interpreted as such when it was going from a non-zero value to the
zero value.

Ok, it was working fine.

Later, I wanted to make it more secure and though it would be nice to
manage these Acquire/Release invocations transparently, using a
Limited_Controller type. All clients were then required to own an
instance of this type and to pass it to the Put entry, as a proof the
client was indeed owning one. This type was named Ticket_Type.

I've created a separate package for the output task and its associated
Ticket_Type, Well, I wanted the Acquire/Release entry of the output
task to not be public any more and the Ticket_Type to be private.
Trouble : there was no way to declare the task in the public part with
a public Put entry and to give it Acquire/Release entries which would
be visible only in the private part and implementation.

The output server task only had a public Put entry, and the Acquire/
Release method were moved to a protected counter object in the
implementation. The Ticket_Type were invoking Acquire/Release on this
protected object, and the output task were requesting the counter
status on this same protected counter object.

All this story to tell to finally understand that making the output
task public, ended into more complex tricks that what I would have get
with a simple publicly declared Put procedure, implemented on top of a
task in the implementation only (the task would have had an Acquire
and Release entry, which the Ticket_Type implementation would have
accessed directly, as it would have been made private in the
implementation).

Here is my though (talking about design principle) : are tasks mostly
to be treated as things to be exposed in public part of to be treated
as implementation details ? After this experiment, I'm filling like
task are just like record components, that is, better to make these
private.

Any way, a request made to a task is blocking as long as the task is
not ready to fulfill the request (the rendezvous, which is the Ada
primitive for synchronization). So, from the client point of view, a
method implemented on top of a task is not a different thing than a
method implemented on top of a procedure.

Any experienced comments about it ?

For inquisitive peoples, here is the source (see next post) designed
with a public task, which make me think a private task is perhaps in
most of case better than a public task.

Notice there was another trouble with this source : when some
accessory stuff were removed, the output task was blocking forever,
never triggering the Terminate statement. I was circumspect about it
until I've understood this was because the select statement was not
evaluated as long as no more queued request were pending. I've solved
this in another version (not this one), using a kind of pooling with
delay..... but I do not like pooling, so I'm still working on the
subject.

Hibou57 (Yannick Duchêne)

non lue,
5 févr. 2010, 15:56:1305/02/2010
à
The source I'm referring to in the previous post :

with Ada.Text_IO;
-- For the service provided by the
-- Output_Server package.
with Ada.Finalization;
-- For the Ticket_Type implementation.

procedure Test is

package Text_IO renames Ada.Text_IO;

package Output_Server is
-- Provides a server which outputs text on
-- the standard output stream, in an atomic
-- maner. Ths purpose of this package is
-- to experiment and the better implementation
-- for such a requirement, would have been to
-- simply use a protected type. This is an
-- experiment to do the same with a task
-- instead.

type Ticket_Type is limited private;
-- Any request to Instance.Put must be
-- made providing a ticket. The Instance task
-- will live at least as long as a ticket
-- is alive in scope and as long as there is
-- no more ticket alive.

task Instance is
entry Put
(Ticket : in Ticket_Type;
Text : in String;
Number : in Natural);
-- Print Text follow by the image of Number
-- on a new line on the standard output. Keep
-- in mind this is just an experiment example.
--
-- The normal way to complete a task in Ada
-- (not to be confused with task termination),
-- is to either have executed all of its task
-- body [ARM 9.3(5)] or to be blocked on select
-- statement with an opened terminate alternative
-- [ARM 9.3(6/1)], that is, if there is no other
-- opened accept statement matching a queued
-- request [ARM 9.7.1(16)] (providing the task
-- body is built around a Select Accept block).
--
-- The "trouble" with this, is that this will
-- be completed as soon there will be no more
-- queued request pending. Indeed, the task
-- semantic refer to actual state and in some
-- way to the previous state, but cannot refer
-- to any futur or potentially futur state.
--
-- We want to complete the task, only when we
-- will know no futur request could come.
-- A specification may be to tell we are in
-- such a case when no more client task are
-- alive (when they are either all completed
-- or terminated).
--
-- So we need a way to know which tasks are
-- clients of this server task. This is the
-- purpose of the ticket of Ticket_Type which
-- comes as a required parameter of the Put
-- entry.
end Instance;

private

-- There use to be an implementation where
-- the server task exposed an Acquire and
-- Release entry, which client were to invok
-- to declare they are client and later no
-- more client of the server task. To
-- be more secure, it was later decided to
-- manage it automatically via the
-- Initialize/Finalize capabilities of a
-- Limited_Controlled type.
--
-- Clients do not invok any more Acquire
-- and then later Release, they just have
-- to own a ticket, which automatically
-- do the stuff as its initialization
-- and later finalization part. This
-- is more safe and less error prone
-- on the client side.

type Ticket_Type is
limited
new Ada.Finalization.Limited_Controlled
with null record;

overriding procedure Initialize
(Ticket : in out Ticket_Type);
-- Initialization of a ticket register
-- a client.

overriding procedure Finalize
(Ticket : in out Ticket_Type);
-- Finalization of a ticket unregister
-- a client.

end Output_Server;

package body Output_Server is

-- Ticket_Type is a private type of the
-- Output_Server package. It needs to
-- inform the Instance task (the server
-- task) when a ticket is entering into
-- existance and when it is later no
-- more alive.
--
-- Unfortunately, we cannot provide Acquire
-- and Release entries which will be only
-- accessible to the implementation of
-- Ticket_Type.
--
-- So, we need another way the Ticket_Type
-- and the Instance to be able to communicate
-- privately. This is done via the following
-- Clients_Counter protected object.

protected Clients_Counter is
procedure Acquire;
procedure Release;
function Count return Natural;
function Has_Started return Boolean;
private
-- These two members use the postffix _Value
-- to avoid a name clash with the two
-- corresponding functions.
Count_Value : Natural := 0;
Has_Started_Value : Boolean := False;
-- The number of registered clients is first
-- zero. The Instance task completes as soon
-- as there is no queued request and the number
-- of living registered clients is zero.
--
-- But the start time is a special case : we
-- are waiting for client to register. So
-- we will not consider the first zero value,
-- and will only take care of a zero value
-- when it will go down to zero.
--
-- This is the purpose of Has_Started_Value.
--
-- Thus, the Instance task can request to
-- both Count and Has_Started status.
end Clients_Counter;

protected body Clients_Counter is

procedure Acquire is
begin
Has_Started_Value := True;
Count_Value := Count_Value + 1;
Text_IO.Put_Line
("Acquire: Count is now " &
Natural'Image (Count_Value) &
"and Has_Started is now " &
Boolean'Image (Has_Started_Value));
-- Log Clients_Counter activities for
-- debuging purpose.
end Acquire;

procedure Release is
begin
Count_Value := Count_Value - 1;
Text_IO.Put_Line
("Release: Count is now " &
Natural'Image (Count_Value));
-- Log Clients_Counter activities for
-- debuging purpose.
end Release;

function Has_Started return Boolean is
begin
-- {Location #1}: if this log
-- statement is removed, then
-- the Instance task blocked
-- indefinitely at location #2.
Text_IO.Put_Line
("Has_Started: returned " &
Boolean'Image (Has_Started_Value));
-- Log Clients_Counter activities for
-- debuging purpose.
return Has_Started_Value;
end Has_Started;

function Count return Natural is
begin
Text_IO.Put_Line
("Count: returned " &
Natural'Image (Count_Value));
-- Log Clients_Counter activities for
-- debuging purpose.
return Count_Value;
end Count;

end Clients_Counter;

overriding procedure Initialize
(Ticket : in out Ticket_Type)
-- Initialization of a ticket register
-- a client.
is
begin
Clients_Counter.Acquire;
end Initialize;

overriding procedure Finalize
(Ticket : in out Ticket_Type)
-- Finalization of a ticket unregister
-- a client.
is
begin
Clients_Counter.Release;
end Finalize;

task body Instance
is
begin
while True loop
select
accept Put
(Ticket : in Ticket_Type;
Text : in String;
Number : in Natural)
do
pragma Unreferenced (Ticket);
-- The sole use of the ticket is
-- to require the client to actually
-- own a ticket.
Text_IO.Put_Line
(Text &
" " &
Natural'Image (Number));
end Put;
or
-- {Location #2}: this work find
-- as long a there is a log statement
-- at location #1. If this statement
-- is removed, then the task never
-- reach its terminate alternative.
when
(Clients_Counter.Has_Started) and
(Clients_Counter.Count = 0)
=>
terminate;
end select;
end loop;
end Instance;

end Output_Server;

-- Shortcuts for better readability.

subtype Ticket_Type is
Output_Server.Ticket_Type;

procedure Put
(Ticket : in Ticket_Type;
Text : in String;
Number : in Natural)
renames
Output_Server.Instance.Put;
-- Keep in mind it's a task entry.

-- Now comes three simple task.
-- Al have the same layout. The
-- first one is the sole commented
-- one.

task First_Task;
task body First_Task
is
Ticket : Ticket_Type;
-- Automatically register this
-- task as client when we enter the
-- scope and unregister this task
-- when the task is terminated.
begin
for Index in 1..4 loop
Put
(Ticket,
"This is First_Task, passing number ",
Index);
-- Remember Put is a request to the
-- Output_Server.Instance.Put entry.
end loop;
end First_Task;

-- Second task : same thing.

task Second_Task;
task body Second_Task
is
Ticket : Ticket_Type;
begin
for Index in 1..7 loop
Put
(Ticket,
"This is Second_Task, passing number",
Index);
end loop;
end Second_Task;

-- Third task : same story.

task Third_Task;
task body Third_Task
is
Ticket : Ticket_Type;
begin
for Index in 1..5 loop
Put
(Ticket,
"This is Third_Task, passing number ",
Index);
end loop;
end Third_Task;

begin
null;
-- Nothing there, all is done in tasks.
-- The application terminates when the last
-- task terminates.
--
-- The tasks which will be started by the environment
-- task are : Output_Server.Instance, First_Task,
-- Second_Task and Third_Task.
end Test;

Jeffrey R. Carter

non lue,
5 févr. 2010, 16:38:0805/02/2010
à
Hibou57 (Yannick Duch�ne) wrote:
>
> So I wanted to solve this, and added a protected object providing an
> Put procedure which was displaying the same message, all three
> statement in an atomic procedure.

Technically this is a bounded error: Ada.Text_IO.Put* operations are potentially
blocking, and should not be called from a protected operation.

> Later, I advised the task may terminates while some potential clients
> may still be alive, or even the task may terminates before any client
> had time to make any first request.

This should not happen. Did you actually experience this?

--
Jeff Carter
"He didn't get that nose from playing ping-pong."
Never Give a Sucker an Even Break
110

Dmitry A. Kazakov

non lue,
5 févr. 2010, 16:40:3805/02/2010
à
On Fri, 5 Feb 2010 12:54:42 -0800 (PST), Hibou57 (Yannick Duch�ne) wrote:

> So I wanted to solve this, and added a protected object providing an
> Put procedure which was displaying the same message, all three
> statement in an atomic procedure.

This is illegal, because protected procedure shall not perform potentially
blocking actions (like I/O.



> Later, I advised the task may terminates while some potential clients
> may still be alive, or even the task may terminates before any client
> had time to make any first request.

You do not need to worry about that. Unless you are using pointers, the
task object's scope encloses any calls to its entries. Therefore it simply
cannot terminate due to its finalization before any entry call. If it
terminates for any other reason, you get Tasking_Error in the entry calls.



> Later, I wanted to make it more secure and though it would be nice to
> manage these Acquire/Release invocations transparently, using a
> Limited_Controller type. All clients were then required to own an
> instance of this type and to pass it to the Put entry, as a proof the
> client was indeed owning one. This type was named Ticket_Type.

If you want garbage collection because of pointers involved then just do
it. Don't break the task interface, make a handle type pointing to the task
object. When the last handle vanishes, deallocate the task. That is.

> Here is my though (talking about design principle) : are tasks mostly
> to be treated as things to be exposed in public part of to be treated
> as implementation details ? After this experiment, I'm filling like
> task are just like record components,

Task component does not work in most real-life cases.

> that is, better to make these private.
> Any way, a request made to a task is blocking as long as the task is
> not ready to fulfill the request (the rendezvous, which is the Ada
> primitive for synchronization). So, from the client point of view, a
> method implemented on top of a task is not a different thing than a
> method implemented on top of a procedure.

Yes, an entry call can be syntactically and semantically different than a
call to a procedure.

Here is how I would do this:

with Ada.Text_IO;

procedure Test is

task Monitor is -- "Monitor" is the customary name of this pattern
entry Put (Text : in String; Number : in Natural);
end Monitor;

task body Monitor is
begin
loop
select
accept Put (Text : in String; Number : in Natural) do
Ada.Text_IO.Put_Line (Text & " " & Natural'Image (Number));
end Put;
or terminate;
end select;
end loop;
exception
when others =>
Text_IO.Put_Line ("Oops, there is something bad here");
end Monitor;

task First_Task;
task body First_Task is

begin
for Index in 1..4 loop

Monitor.Put ("This is First_Task, passing number ", Index);
end loop;
end First_Task;

task Second_Task;
task body Second_Task is

begin
for Index in 1..7 loop

Monitor.Put ("This is Second_Task, passing number", Index);
end loop;
end Second_Task;

task Third_Task;
task body Third_Task is


begin
for Index in 1..5 loop

Monitor.Put ("This is Third_Task, passing number ", Index);
end loop;
end Third_Task;

begin
null;
end Test;

You can print from the rendezvous. That is not a problem. Some tight
implementations would prefer buffering in the rendezvous in order to
release the caller as soon as possible (minimizing the effect of priority
inversion). I.e. Text is first copied into the task's buffer during the
rendezvous and printed later outside the rendezvous before accepting the
new one. Assuming that the callers run at a higher priority and do not
print very often leaving the processor free most of the time, this would
give better response times in the callers (at the cost of some overall
performance hit).

--
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de

Hibou57 (Yannick Duchêne)

non lue,
5 févr. 2010, 16:53:5005/02/2010
à
Hi Jeffrey, nice to meet you again,

On 5 fév, 22:38, "Jeffrey R. Carter" <spam.jrcarter....@spam.acm.org>
wrote:


> Technically this is a bounded error: Ada.Text_IO.Put* operations are potentially
> blocking, and should not be called from a protected operation.

I did not ever suspected such a requirement. Transitive blocking is
not allowed ?

So, if blocking operation are not allowed from a protected type,
clients of a given operation have to know it weither or not it's
potentially blocking, and so, this fact must be stated in public part
of specifications, so then, the protected and tasked aspect of a
method must be stated in specifications and I suppose it's not a good
idea to make it private.

Wrong or right assumptions ?

> This should not happen. Did you actually experience this?

No, I did not experience it, this was just my imagination : I knew a
task may completes at its own discretion. Thus if may possibly
completes too much soon if its completion condition is not well
designed.

I will have to check the RM, but I'm pretty sure a completed task
cannot handle any request any more (at least, this seems to be a
reasonable assumption to me, but I will still have to check...).

Hibou57 (Yannick Duchêne)

non lue,
5 févr. 2010, 17:09:3305/02/2010
à
On 5 fév, 22:40, "Dmitry A. Kazakov" <mail...@dmitry-kazakov.de>
wrote:

> This is illegal, because protected procedure shall not perform potentially
> blocking actions (like I/O.
As Jeffrey pointed out as well. I will check the RM about it (I have
to establish I've missed it).

> You do not need to worry about that. Unless you are using pointers, the
> task object's scope encloses any calls to its entries. Therefore it simply
> cannot terminate due to its finalization before any entry call.

**it simply cannot terminate due to its finalization before any entry
call**

That's clever to notice ! OK, I see. Now I understand Jeffrey's
doubts.

> If you want garbage collection because of pointers involved then just do
> it. Don't break the task interface, make a handle type pointing to the task
> object. When the last handle vanishes, deallocate the task. That is.

“ Deallocate the task ” ? If I want to deallocate, I have to request
it to completes, and for the latter, I need it to have a corresponding
request entry... which would need to be public (as private entry
accessible from implementation is not possible).

> Task component does not work in most real-life cases.

My words was wrong : I was not to talk about using task as record
components, I was to say task may be implementation details, just like
record components are.

> Yes, an entry call can be syntactically and semantically different than a
> call to a procedure.

Syntactically : can be wrapped in a procedure call.
Semantically : sure if protected objects are required to not invoke
blocking operations, this is semantically different.

> You can print from the rendezvous. That is not a problem. Some tight
> implementations would prefer buffering in the rendezvous in order to
> release the caller as soon as possible (minimizing the effect of priority
> inversion). I.e. Text is first copied into the task's buffer during the
> rendezvous and printed later outside the rendezvous before accepting the
> new one. Assuming that the callers run at a higher priority and do not
> print very often leaving the processor free most of the time, this would
> give better response times in the callers (at the cost of some overall
> performance hit).

I like this hint (have a taste of real-time design by the way).

sjw

non lue,
5 févr. 2010, 17:57:2805/02/2010
à
On Feb 5, 10:09 pm, Hibou57 (Yannick Duchêne)

<yannick_duch...@yahoo.fr> wrote:
> On 5 fév, 22:40, "Dmitry A. Kazakov" <mail...@dmitry-kazakov.de>

> > If you want garbage collection because of pointers involved then just do


> > it. Don't break the task interface, make a handle type pointing to the task
> > object. When the last handle vanishes, deallocate the task. That is.
>
> “ Deallocate the task ” ? If I want to deallocate, I have to request
> it to completes, and for the latter, I need it to have a corresponding
> request entry... which would need to be public (as private entry
> accessible from implementation is not possible).

You could just abort the task before freeing it.

With GNAT (maybe just with older versions, maybe not on all
platforms), if you free a task before it has terminated it will
silently not do the deallocation. The trick is to loop until
'Terminated is True.

I had to create a scavenger task; tasks that had been aborted were
placed on a queue for the scavenger task to free when the task had
terminated. Fairly gruesome generics involved.

Hibou57 (Yannick Duchêne)

non lue,
5 févr. 2010, 21:20:5805/02/2010
à
On 5 fév, 22:38, "Jeffrey R. Carter" <spam.jrcarter....@spam.acm.org>
wrote:
> Technically this is a bounded error: Ada.Text_IO.Put* operations are potentially
> blocking, and should not be called from a protected operation.

On 5 fév, 22:40, "Dmitry A. Kazakov" <mail...@dmitry-kazakov.de>
wrote:


> This is illegal, because protected procedure shall not perform potentially
> blocking actions (like I/O.

Here is the reference (for any other peoples who read this thread) :
First occurrence of this requirement appears as an example in [ARM
9.5(4.e)] :

procedure Op2 is
begin
Op1; -- An internal call.
Pt.Op1; -- Another internal call.
PO.Op1; -- An external call. It the current instance is PO, then
-- this is a bounded error (see 9.5.1).
Other_Object.Some_Op; -- An external call.
end Op2;

Then formally stated at [ARM 9.5.1(8)] :
“ During a protected action, it is a bounded error to invoke an
operation that is potentially blocking. ” (follows a list of
operations defined to be potentially blocking)
And later in [ARM 9.5.1(17)] :
“ If the bounded error is detected, Program_Error is raised. If not
detected, the bounded error might result in deadlock or a (nested)
protected action on the same target object. ”

So it is not guaranteed to be a bounded error, as nested protected
action may succeed.

By as soon as it is said it is a potential error, ... all is said.

Hibou57 (Yannick Duchêne)

non lue,
5 févr. 2010, 21:23:0205/02/2010
à
On 6 fév, 03:20, Hibou57 (Yannick Duchêne) <yannick_duch...@yahoo.fr>
wrote:

> By as soon as it is said it is a potential error, ... all is said.
Tipo mistake : “ But as soon ” instead of “ By as soon ”

Jeffrey R. Carter

non lue,
5 févr. 2010, 22:29:1605/02/2010
à
Hibou57 (Yannick Duch�ne) wrote:
>
> � If the bounded error is detected, Program_Error is raised. If not

> detected, the bounded error might result in deadlock or a (nested)
> protected action on the same target object. �

>
> So it is not guaranteed to be a bounded error, as nested protected
> action may succeed.

No, it is a bounded error. A bounded error has a finite set of possible effects.
One of the possible effects of this particular bounded error is that the
operation will complete normally.

See also pragma Detect_Blocking (ARM H.5); without it an implementation may
choose to never detect potentially blocking operations and never raise
Program_Error. This seems to be the way GNAT handles these.

Alex R. Mosteo

non lue,
8 févr. 2010, 04:55:1508/02/2010
à
Hibou57 (Yannick Duchêne) wrote:

> Hi Jeffrey, nice to meet you again,
>
> On 5 fév, 22:38, "Jeffrey R. Carter" <spam.jrcarter....@spam.acm.org>
> wrote:
>> Technically this is a bounded error: Ada.Text_IO.Put* operations are
>> potentially blocking, and should not be called from a protected
>> operation.
> I did not ever suspected such a requirement. Transitive blocking is
> not allowed ?
>
> So, if blocking operation are not allowed from a protected type,
> clients of a given operation have to know it weither or not it's
> potentially blocking, and so, this fact must be stated in public part
> of specifications, so then, the protected and tasked aspect of a
> method must be stated in specifications and I suppose it's not a good
> idea to make it private.

I have had some headaches not long along because of potentially blocking
operations. The short conclusion is that as long as you don't try anything
strange, you'll do well. By strange I mean things that may seem "clever" at
some point like calling a task from a protected or so.

Past versions of gnat where indulging about this, there's now a pragma that
won't allow it and that I recommend to use; you'll save further problems
with deadlocks. I think is pragma Detect_Blocking.

So, if your type is encapsulating a hidden call to a task entry, it would be
advisable to document it in the call, because this indeed can raise an
exception at runtime if called from a protected op. I think this is a
recommendation, but a bounded error in any case. The above pragma enforces
its detection.

However, I don't think it's recommended design to call from protected ops to
foreign, implementation-unknown, subprograms. Protected calls should
encapsulate something as well defined and narrow as possible.

I make extensive use of protected and task types generally without issue; my
problem was that I had to quickly hack a solution for a convoluted tasking
subsystem and I was frankly abusing the design. In general, sticking to the
client-server model for tasks/protected objects covers 99% of use cases and
it's totally safe.

> Wrong or right assumptions ?
>
>> This should not happen. Did you actually experience this?
> No, I did not experience it, this was just my imagination : I knew a
> task may completes at its own discretion. Thus if may possibly
> completes too much soon if its completion condition is not well
> designed.
>
> I will have to check the RM, but I'm pretty sure a completed task
> cannot handle any request any more (at least, this seems to be a
> reasonable assumption to me, but I will still have to check...).

At first I also was reticent of terminate parts, but this is really one of
these nice aspects of Ada where something apparently complex is done for you
by the language :)

Jean-Pierre Rosen

non lue,
8 févr. 2010, 05:02:1808/02/2010
à
Hibou57 (Yannick Duch�ne) a �crit :

> So, if blocking operation are not allowed from a protected type,
> clients of a given operation have to know it weither or not it's
> potentially blocking, and so, this fact must be stated in public part
> of specifications, so then, the protected and tasked aspect of a
> method must be stated in specifications and I suppose it's not a good
> idea to make it private.
>
> Wrong or right assumptions ?
>

Right. Thats why there is a rule in AdaControl to check potentially
blocking operations called from protected actions.

The check is of course pessimistic (if it were really statically
checkable, it would be forbidden by langage rules). So it checks for
potentially potentially blocking operations ;-)

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

Maciej Sobczak

non lue,
8 févr. 2010, 12:28:4408/02/2010
à
On 5 Lut, 22:53, Hibou57 (Yannick Duchêne) <yannick_duch...@yahoo.fr>
wrote:

> I did not ever suspected such a requirement. Transitive blocking is
> not allowed ?

As far as I understand, there is a careful wording around this subject
so that formally speaking protected operations (except for entries)
are not themselves "blocking". So, for example, you can call protected
operations from other protected operations.

The operations that are considered to be blocking in this context are
delay statements, entry calls, select statements and... I/O
operations. These cannot be called from protected operations.

(I'm sure somebody will correct me if I'm off tracks)

> So, if blocking operation are not allowed from a protected type,
> clients of a given operation have to know it weither or not it's
> potentially blocking,

That would be nice, yes. But be careful, this approach might blow up
the language. What about exception specifications? And so on.

But: see RavenSPARK.

The problem with blocking in particular is that there is no way to
verify whether imported subprograms (from C libraries, for example)
are blocking. You can import I/O operations from C libraries and there
is no way to verify what they do.

--
Maciej Sobczak * www.msobczak.com * www.inspirel.com

Database Access Library for Ada: www.inspirel.com/soci-ada

Dmitry A. Kazakov

non lue,
9 févr. 2010, 03:43:3309/02/2010
à
On Mon, 8 Feb 2010 09:28:44 -0800 (PST), Maciej Sobczak wrote:

> The problem with blocking in particular is that there is no way to
> verify whether imported subprograms (from C libraries, for example)
> are blocking. You can import I/O operations from C libraries and there
> is no way to verify what they do.

You do not need that. The default must be "blocking". The programmer
overrides the default if he is sure that the imported subprogram is not
blocking. This is no different to the parameter profile of an imported
procedure. There is no way to verify it. So the programmer just gives his
word, and the compiler rely on it.

Hibou57 (Yannick Duchêne)

non lue,
9 févr. 2010, 07:07:1409/02/2010
à
On 8 fév, 18:28, Maciej Sobczak <see.my.homep...@gmail.com> wrote:
> As far as I understand, there is a careful wording around this subject
> so that formally speaking protected operations (except for entries)
> are not themselves "blocking". So, for example, you can call protected
> operations from other protected operations.
>
> The operations that are considered to be blocking in this context are
> delay statements, entry calls, select statements and... I/O
> operations. These cannot be called from protected operations.
>
> (I'm sure somebody will correct me if I'm off tracks)
Protected types was most the subject of another thread, but as you
talked about it here : I don't understand why you've protected
operation (I suppose you were talking about procedures, not entries)
are not themselves blocking. They grant exclusive read-write access
and ensure there is no race. So if another task is currently running
the procedure of a protected type, another task cannot enter this
procedure if it was to do so and a task switch occurs at the same
time.

Or is it guaranteed that no task switch can occurs when a task is
actually in a procedure of a protected type ? Is the task switch
delayed in such a circumstance ?

Let temporarily suppose so. But remains another wolf in the wood :
what if the application is running in a multiprocessors environment
and its thread are not executed on the same CPU ? If one task on CPU#1
was to enter a procedure of a protected object while a task on CPU#2
is actually running a procedure on the same protected object, then,
the task running on CPU#1 must be delayed, and thus, the procedure is
blocking.

Sure a procedure of a protected type or object should be short and
quick to execute, but it seems to still remains potentially blocking.

Alex R. Mosteo

non lue,
9 févr. 2010, 09:44:1709/02/2010
à
Maciej Sobczak wrote:

> On 5 Lut, 22:53, Hibou57 (Yannick Duchêne) <yannick_duch...@yahoo.fr>
> wrote:
>
>> I did not ever suspected such a requirement. Transitive blocking is
>> not allowed ?
>
> As far as I understand, there is a careful wording around this subject
> so that formally speaking protected operations (except for entries)
> are not themselves "blocking". So, for example, you can call protected
> operations from other protected operations.

And this makes sense: if you don't allow anything blocking inside a
protected procedure, it follows that the procedure is itself non-blocking :)

Entries, on the other hand, are blocking... because you don't know if you'll
be blocked on the entry conditional. This is true even for non-conditional
entries, I think, because of possible requeues.

Alex.

Jean-Pierre Rosen

non lue,
9 févr. 2010, 09:26:3009/02/2010
à
Hibou57 (Yannick Duch�ne) a �crit :
> [...]

> Sure a procedure of a protected type or object should be short and
> quick to execute, but it seems to still remains potentially blocking.

There are two kinds of blockings: bounded and unbounded. The idea is
that when computing a time budget, you can account for bounded
blockings, but not unbounded ones.

protected procedures are bounded, because if you know the processing
time and the maximum number of tasks waiting, you know the WCET of the
procedure. Entries are unbounded, because they depend on a guard whose
condition can be anything.

The "potentially blocking" phrase should be understood as really meaning
unbounded. This all boils down to: "an operation with a bounded
execution time is not allowed to call an operation with an unbounded
execution time".

Makes more sense?

Robert A Duff

non lue,
9 févr. 2010, 10:20:0309/02/2010
à
"Hibou57 (Yannick Duch�ne)" <yannick...@yahoo.fr> writes:

> Let temporarily suppose so. But remains another wolf in the wood :
> what if the application is running in a multiprocessors environment
> and its thread are not executed on the same CPU ? If one task on CPU#1
> was to enter a procedure of a protected object while a task on CPU#2
> is actually running a procedure on the same protected object, then,
> the task running on CPU#1 must be delayed, and thus, the procedure is
> blocking.
>
> Sure a procedure of a protected type or object should be short and
> quick to execute, but it seems to still remains potentially blocking.

You should read all the stuff in the Real Time annex about priorities
and ceilings and policies and whatnot.

No, protected procedures and functions are not potentially blocking.

In your multiprocessor example, task#1 cannot procede
into the protected procedure until task#2 lets go
of it, but that's not blocking. No lower-or-equal priority
task can preempt task#1. One possible implementation is
that task#1 spins on the lock, which is OK because you
made sure your protected procedure executes in a short
bounded time.

This all depends on using the right real-time policy. Other policies
are possible -- and likely, when running on top of a desktop OS.

Protected entries, on the other hand, are potentially blocking,
because they put the task to sleep for an arbitrarily long time
(until the barrier becomes True).

- Bob

Hibou57 (Yannick Duchêne)

non lue,
9 févr. 2010, 13:17:5509/02/2010
à
On 9 fév, 15:26, Jean-Pierre Rosen <ro...@adalog.fr> wrote:
> protected procedures are bounded, because if you know the processing
> time and the maximum number of tasks waiting, you know the WCET of the
> procedure. Entries are unbounded, because they depend on a guard whose
> condition can be anything.
>
> The "potentially blocking" phrase should be understood as really meaning
> unbounded.  This all boils down to: "an operation with a bounded
> execution time is not allowed to call an operation with an unbounded
> execution time".
>
> Makes more sense?
Yes, more sense. Bounded/Unbounded execution-time is better
expressive.


Side note. For peoples who like me didn't knew what is WCET : its
"Worst Case Execution Time" (dixit Wikipedia).

Hibou57 (Yannick Duchêne)

non lue,
9 févr. 2010, 13:26:3709/02/2010
à
On 9 fév, 16:20, Robert A Duff <bobd...@shell01.TheWorld.com> wrote:
> You should read all the stuff in the Real Time annex about priorities
> and ceilings and policies and whatnot.
>
> No, protected procedures and functions are not potentially blocking.
The misunderstanding was because I was misled on the meaning of
"blocking".
Jean-Pierre's words changed the situation (see his post).

> In your multiprocessor example, task#1 cannot procede
> into the protected procedure until task#2 lets go
> of it, but that's not blocking.  No lower-or-equal priority
> task can preempt task#1.  One possible implementation is
> that task#1 spins on the lock, which is OK because you
> made sure your protected procedure executes in a short
> bounded time.

I've later learned today about spin, but I still have to learn more
about it (that's an other area).

> Protected entries, on the other hand, are potentially blocking,
> because they put the task to sleep for an arbitrarily long time
> (until the barrier becomes True).

Unbounded

mka...@gmail.com

non lue,
9 févr. 2010, 18:38:0109/02/2010
à
On Feb 5, 4:38 pm, "Jeffrey R. Carter"

Why do people insist that Ada.Text_IO.Put routines are potentially
blocking.

From the ARM

Discussion: {AI95-00178-01} Any subprogram in a language-defined input-
output package that has a file parameter or result or operates on a
default file is considered to manipulate a file. An instance of a
language-defined input-output generic package provides subprograms
that are covered by this rule. The only subprograms in language-
defined input-output packages not covered by this rule (and thus not
potentially blocking) are the Get and Put routines that take string
parameters defined in the packages nested in Text_IO.

Robert A Duff

non lue,
9 févr. 2010, 18:51:2309/02/2010
à
"mka...@gmail.com" <mka...@gmail.com> writes:

> Why do people insist that Ada.Text_IO.Put routines are potentially
> blocking.

Because they're talking about the ones that operate on files,
which are the commonly-used ones. If you say:

Ada.Text_IO.Put_Line("Hello, world.");

in a protected procedure, that's wrong. GNAT will often let you
get away with it, but it's still wrong, because Put_Line is
potentially blocking.

Yes, as you quote below, the Get/Put that do parsing/formatting
on strings are not blocking, as you would expect. But these
are rarely used, so people forget about them.

> From the ARM
>
> Discussion: {AI95-00178-01} Any subprogram in a language-defined input-
> output package that has a file parameter or result or operates on a
> default file is considered to manipulate a file. An instance of a
> language-defined input-output generic package provides subprograms
> that are covered by this rule. The only subprograms in language-
> defined input-output packages not covered by this rule (and thus not
> potentially blocking) are the Get and Put routines that take string
> parameters defined in the packages nested in Text_IO.

- Bob

Jeffrey R. Carter

non lue,
9 févr. 2010, 19:01:3409/02/2010
à
mka...@gmail.com wrote:
>
> Why do people insist that Ada.Text_IO.Put routines are potentially
> blocking.
>
> From the ARM
>
> Discussion: {AI95-00178-01} Any subprogram in a language-defined input-
> output package that has a file parameter or result or operates on a
> default file is considered to manipulate a file. An instance of a
> language-defined input-output generic package provides subprograms
> that are covered by this rule. The only subprograms in language-
> defined input-output packages not covered by this rule (and thus not
> potentially blocking) are the Get and Put routines that take string
> parameters defined in the packages nested in Text_IO.

Probably because of ARM 9.5.1:

"the subprograms of the language-defined input-output packages that manipulate
files (implicitly or explicitly) are potentially blocking."

--
Jeff Carter
"My mind is aglow with whirling, transient nodes of
thought, careening through a cosmic vapor of invention."
Blazing Saddles
85

Maciej Sobczak

non lue,
10 févr. 2010, 03:17:5510/02/2010
à
On 9 Lut, 15:26, Jean-Pierre Rosen <ro...@adalog.fr> wrote:

> There are two kinds of blockings: bounded and unbounded. The idea is
> that when computing a time budget, you can account for bounded
> blockings, but not unbounded ones.

> The "potentially blocking" phrase should be understood as really meaning
> unbounded.

Well, I know what you try to convey, but there are traps:

delay Some_Static_Constant;

Is it bounded or unbounded?

As far as WCET (or any other time-based analysis) goes, the above can
be accounted for statically. Still, it is a no-no within any protected
operation.

Hibou57 (Yannick Duchêne)

non lue,
10 févr. 2010, 03:29:5310/02/2010
à
On 10 fév, 09:17, Maciej Sobczak <see.my.homep...@gmail.com> wrote:
> > There are two kinds of blockings: bounded and unbounded. The idea is
> > that when computing a time budget, you can account for bounded
> > blockings, but not unbounded ones.
> > The "potentially blocking" phrase should be understood as really meaning
> > unbounded.
>
> Well, I know what you try to convey, but there are traps:
>
>    delay Some_Static_Constant;
>
> Is it bounded or unbounded?
>
> As far as WCET (or any other time-based analysis) goes, the above can
> be accounted for statically. Still, it is a no-no within any protected
> operation.
Interesting enigma

I would say Bounded, as it is predictable.
... as long as the delay is short, otherwise it will break the other
rule stating that a protected operation should be fast to execute.

If I try to have a delay X.Y in a protected operation, GNAT just warns
me “ potentially blocking operation in protected operation ”, while
the program is still compiled.

You've said “ it is a no-no within any protected ” : do you get a
compilation error when you do the same ?

I've not seen anything in the Rationale nor in the ARM which
explicitly disallow it anyway (but as these are long pages I should
later read again, I may have miss it).

Martin

non lue,
10 févr. 2010, 03:40:2210/02/2010
à
On Feb 10, 8:29 am, Hibou57 (Yannick Duchêne)

It's isn't predicatable - it will delay for /at least/
Some_Static_Constant. It's up to the task scheduling algorithm (plus
the rest of the program! ;-) as to what happen next...and when!

Cheers
-- Martin

Jean-Pierre Rosen

non lue,
10 févr. 2010, 06:38:5610/02/2010
à
Maciej Sobczak a �crit :

> On 9 Lut, 15:26, Jean-Pierre Rosen <ro...@adalog.fr> wrote:
>
>> There are two kinds of blockings: bounded and unbounded. The idea is
>> that when computing a time budget, you can account for bounded
>> blockings, but not unbounded ones.
>
>> The "potentially blocking" phrase should be understood as really meaning
>> unbounded.
>
> Well, I know what you try to convey, but there are traps:
>
> delay Some_Static_Constant;
>
> Is it bounded or unbounded?
>
For the rules of potentially blocking operations, delay is potentially
blocking because it /can/ be unbounded. Many unbounded things can be
proved bounded with sufficient analysis and provided some elements are
static; that's not the point here.

Jean-Pierre Rosen

non lue,
10 févr. 2010, 06:44:3910/02/2010
à
Martin a �crit :

> It's isn't predicatable - it will delay for /at least/
> Some_Static_Constant. It's up to the task scheduling algorithm (plus
> the rest of the program! ;-) as to what happen next...and when!
>

If your compiler supports annex D, the possible extra delay time has to
be documented - see D.9.

Martin

non lue,
10 févr. 2010, 07:51:1610/02/2010
à
On Feb 10, 11:44 am, Jean-Pierre Rosen <ro...@adalog.fr> wrote:
> Martin a écrit :


D.9 (12) in this case?

I guess if you're that interested then you do need an Annex D
conforming compiler...just looking and yup, GNAT GLP 2009 for WinXP
doesn't list that - so non-deterministic for this OS.

Cheers
-- Martin

Robert A Duff

non lue,
10 févr. 2010, 11:17:1610/02/2010
à
Martin <martin...@btopenworld.com> writes:

> It's isn't predicatable - it will delay for /at least/
> Some_Static_Constant.

Well, implementations are supposed to wake the task up
as soon as possible after the delay expires.
We don't really have a way to say that in RM terms,
but an implementation that delays for an extra
second, for example, should probably be considered
broken.

>..It's up to the task scheduling algorithm (plus


> the rest of the program! ;-) as to what happen next...and when!

Yeah, the rest of the program is key. But that's the case even
without delays. For example, suppose a protected procedure
says, "X := X + 1;". Looks pretty bounded. But it can
get preempted by a higher priority task, which can
go off and do stuff for a long and unbounded time.

You have to take care to get your priorities right.

- Bob

Dmitry A. Kazakov

non lue,
13 févr. 2010, 06:09:4813/02/2010
à
On Tue, 09 Feb 2010 15:26:30 +0100, Jean-Pierre Rosen wrote:

> Hibou57 (Yannick Duch�ne) a �crit :
>> [...]
>> Sure a procedure of a protected type or object should be short and
>> quick to execute, but it seems to still remains potentially blocking.
>
> There are two kinds of blockings: bounded and unbounded. The idea is
> that when computing a time budget, you can account for bounded
> blockings, but not unbounded ones.

I use another idiom: "instant" and "delayed". "Delayed" can be bounded, so
"delay D" being not unbounded is still not instant. "Instant" means that
whatever delay is caused by the call that does not change the program
semantics, as defined and to be respected by the programmer. Which is a
more or less formal definition for "short and quick".

On the caller's side protected procedures and functions are instant =
non-blocking. Protected entries are delayed = potentially blocking.

0 nouveau message