Version 1.11 of ais/ai-00348.txt

Unformatted version of ais/ai-00348.txt version 1.11
Other versions for file ais/ai-00348.txt

!standard 6.07(00)          04-05-27 AI95-00348/07
!standard 3.01(09)
!standard 6.01(04)
!standard 7.06(06)
!standard 7.06(08)
!standard 7.06(09)
!standard 12.06(03)
!standard 12.06(04)
!standard 12.06(10)
!standard 12.06(16)
!class amendment 03-09-02
!status Amendment 200Y 04-04-16
!status ARG Approved 10-0-0 03-10-04
!status work item 03-09-02
!status received 03-09-02
!priority Medium
!difficulty Easy
!subject Null procedures
!summary
A new form of procedure declaration, a null procedure, is added to the language. Its effect is that of a procedure whose body comprises just a null statement. Null procedures are important for abstract interfaces (see AI-251). They are also useful for generic defaults and in simplifying Ada.Finalization.
!problem
It currently is impossible to change an abstract tagged type to an abstract interface (see AI-251) if the abstract tagged type has any concrete subprograms. Many such subprograms exist only to give a default (empty) implementation so that the standard "pass-the-buck" implementation is always possible. (This means that the implementation of an overriding operation always calls the overridden operation of the parent type.) This is especially an issue in generic units, where the overriding routine must "pass-the-buck", since it can assume nothing about the implementation.
!proposal
A "null procedure" is a procedure declaration of the (newly introduced) form
procedure P (...) is null;
whose dynamic semantics are similar to a procedure with the body
procedure P (...) is begin null; end;
The use of "null" as a default for generic formal procedures is also supported.
!wording
Add to 3.1(3):
basic_declaration ::= ... | null_procedure_declaration
Replace 6.1(4):
procedure_specification ::= procedure defining_program_unit_name parameter_profile function_specification ::= function defining_designator parameter_and_result_profile subprogram_specification ::= procedure_specification | function_specification
Add a new clause 6.7:
6.7 Null Procedures
A null_procedure_declaration provides a shorthand to declare a procedure with an empty body.
Syntax
null_procedure_declaration ::= procedure_specification is null;
Static Semantics
A null_procedure_declaration declares a null procedure. [A completion is not allowed for a null_procedure_declaration.]
AARM Proof: A null_procedure_declaration is not a subprogram_declaration, thus it does not require or allow completion.
Dynamic Semantics
The execution of a null procedure is invoked by a subprogram call. For the execution of a subprogram call on a null procedure, the execution of the subprogram_body has no effect.
AARM Note: A null procedure has no subprogram_body; but we need to explain what the subprogram_body mentioned in 6.4's Dynamic Semantics does.
Replace 7.6(6) with
procedure Initialize (Object : in out Controlled) is null; procedure Adjust (Object : in out Controlled) is null; procedure Finalize (Object : in out Controlled) is null;
Replace 7.6(8) with
procedure Initialize (Object : in out Limited_Controlled) is null; procedure Finalize (Object : in out Limited_Controlled) is null;
Delete the second sentence of 7.6(9):
The (default) implementations of Initialize, Adjust, and Finalize have no effect.
Add to 12.6(3)
subprogram_default ::= ... | null
Add after 12.6(4)
A subprogram_default of null shall not be specified for a formal function.
Add after 12.6(10)
If a generic unit has a subprogram_default specified by the reserved word null, and the corresponding actual parameter is omitted, then it is equivalent to an explicit actual parameter that is a null procedure having the profile given in the formal_subprogram_declaration.
Add after 12.6(16)
A null procedure as a subprogram default has convention Intrinsic (see 6.3.1).
AARM Proof: This follows from 6.3.1(7).
!discussion
Null procedures make interface types (AI-251) much more useful. The ability to declare a primitive of an interface as a null procedure enables existing abstract types that have null (non-abstract) default implementations of some of their primitives to be transitioned to being interface types. An example of such a type is Ada.Finalization.Controlled. There are other considerations which argue for leaving Controlled as a "normal" tagged type (especially the fact that many implementations use data components for linking in all controlled objects, but such data is not allowed for interfaces), but the capability of switching other existing abstract tagged types to be interfaces remains potentially quite useful.
Although the primary motivation for null procedures is for use with interface types, they are also useful in other contexts. For code in a generic which always "passes the buck" to the corresponding parent primitive (as is done for Finalize, for example), the compiler can eliminate such a call when the parent's operation is known to be null at instantiation time. There are obvious documentation advantages for someone extending a type to know that the default implementation of an operation is null.
The ability to have non-dispatching calls on the primitive of a generic formal interface type to be made inside the generic can be necessary to enable a pass-the-buck-to-the-parent paradigm when overriding the operation. This is the paradigm used for finalization, for example, and is quite common in type hierarchies in general.
For example:
type T is interface; procedure Prim1(X : T) is null; procedure Prim2(X : T) is abstract;
generic type NT is abstract new T with private; -- NT guaranteed to have non-abstract implementation of Prim1 package P is type NN is new NT with private; procedure Prim1(X : NN); -- May "pass-the-buck" to Prim1 of NT as part -- of implementation of Prim1 of NN procedure Prim2(X : NN); -- Prim2 must be overridden; -- cannot call Prim2 of NT since it might be abstract end P;
Consider the following:
package Pkg1 is procedure P is null; end Pkg1;
package Pkg2 is procedure P is null; end Pkg2;
with Pkg1, Pkg2; package Pkg3 is type Ref is access procedure; Ptr1 : Ref := Pkg1.P'access; Ptr2 : Ref := Pkg2.P'access; Eq : constant Boolean := Ptr1 = Ptr2; end Pkg3;
Null procedures are distinct subprograms in the sense of 4.5.2(13), so as a consequence the Boolean Eq must be False.
A null procedure is also allowed as a generic default. For example:
generic with procedure Proc is null; package G is ... end G;
package I is new G;
In instance package I, calling Proc has no effect.
The convention of a formal procedure whose default is null and whose actual is omitted is Intrinsic. This follows from 6.3.1(7). Thus we don't have to worry about access issues for such formal subprograms.
Like an instantiation, a null procedure is not allowed as a completion. Allowing this would double the amount of RM text needed for no real gain. Also like an instantiation, a null procedure does not "require completion".
A null procedure may have OUT-mode parameters, just as a regular procedure may. Since
procedure Piglet(X: out T) is begin null; end Piglet;
is legal,
procedure Piglet(X: out T) is null;
is also allowed. Note that copyback is performed in this case, just as for a regular procedure. The phrase "The execution of the subprogram_body" in the dynamic semantics section refers to "The subprogram_body is then executed" from clause 6.4(10), which is just one of the steps in the execution of a subprogram call. The call as a whole may have a user-visible side-effect (e.g. copying junk into the actual of a scalar out parameter); it is only the "execution of the subprogram_body" step of the call which has no effect.
The changes to Ada.Finalization are not an essential part of this AI, but using syntax is clearer than using text to describe the semantics of these routines.
!example
package Pkg is procedure Proc is null; end Pkg;
!corrigendum 3.01(03)
Replace the paragraph:
basic_declaration ::= type_declaration | subtype_declaration | object_declaration | number_declaration | subprogram_declaration | abstract_subprogram_declaration | package_declaration | renaming_declaration | exception_declaration | generic_declaration | generic_instantiation
by:
basic_declaration ::= type_declaration | subtype_declaration | object_declaration | number_declaration | subprogram_declaration | abstract_subprogram_declaration | null_procedure_declaration | package_declaration | renaming_declaration | exception_declaration | generic_declaration | generic_instantiation
!corrigendum 6.1(4)
Replace the paragraph:
subprogram_specification ::= procedure defining_program_unit_name parameter_profile | function defining_designator parameter_and_result_profile
by:
procedure_specification ::= procedure defining_program_unit_name parameter_profile
function_specification ::= function defining_designator parameter_and_result_profile
subprogram_specification ::= procedure_specification | function_specification
!corrigendum 6.7(1)
Insert new clause:
A null_procedure_declaration provides a shorthand to declare a procedure with an empty body.
Syntax
null_procedure_declaration ::= procedure_specification is null;
Static Semantics
A null_procedure_declaration declares a null procedure. A completion is not allowed for a null_procedure_declaration.
Dynamic Semantics
The execution of a null procedure is invoked by a subprogram call. For the execution of a subprogram call on a null procedure, the execution of the subprogram_body has no effect.
!corrigendum 7.6(6)
Replace the paragraph:
procedure Initialize (Object : in out Controlled); procedure Adjust (Object : in out Controlled); procedure Finalize (Object : in out Controlled);
by:
procedure Initialize (Object : in out Controlled) is null; procedure Adjust (Object : in out Controlled) is null; procedure Finalize (Object : in out Controlled) is null;
!corrigendum 7.6(8)
Replace the paragraph:
procedure Initialize (Object : in out Limited_Controlled); procedure Finalize (Object : in out Limited_Controlled); private ... -- not specified by the language end Ada.Finalization;
by:
procedure Initialize (Object : in out Limited_Controlled) is null; procedure Finalize (Object : in out Limited_Controlled) is null; private ... -- not specified by the language end Ada.Finalization;
!corrigendum 7.6(9)
Replace the paragraph:
A controlled type is a descendant of Controlled or Limited_Controlled. The (default) implementations of Initialize, Adjust, and Finalize have no effect. The predefined "=" operator of type Controlled always returns True, since this operator is incorporated into the implementation of the predefined equality operator of types derived from Controlled, as explained in 4.5.2. The type Limited_Controlled is like Controlled, except that it is limited and it lacks the primitive subprogram Adjust.
by:
A controlled type is a descendant of Controlled or Limited_Controlled. The predefined "=" operator of type Controlled always returns True, since this operator is incorporated into the implementation of the predefined equality operator of types derived from Controlled, as explained in 4.5.2. The type Limited_Controlled is like Controlled, except that it is limited and it lacks the primitive subprogram Adjust.
!corrigendum 12.6(3)
Replace the paragraph:
subprogram_default ::= default_name | <>
by:
subprogram_default ::= default_name | <> | null
!corrigendum 12.6(4)
Insert after the paragraph:
default_name ::= name
the new paragraph:
A subprogram_default of null shall not be specified for a formal function.
!corrigendum 12.6(10)
Insert after the paragraph:
If a generic unit has a subprogram_default specified by a box, and the corresponding actual parameter is omitted, then it is equivalent to an explicit actual parameter that is a usage name identical to the defining name of the formal.
the new paragraph:
If a generic unit has a subprogram_default specified by the reserved word null, and the corresponding actual parameter is omitted, then it is equivalent to an explicit actual parameter that is a null procedure having the profile given in the formal_subprogram_declaration.
!corrigendum 12.6(16)
Insert after the paragraph:
18 The actual subprogram cannot be abstract (see 3.9.3).
the new paragraph:
19 A null procedure as a subprogram default has convention Intrinsic (see 6.3.1).
!ACATS test
Test(s) need to be constructed.
!appendix

From: Thomas Wolf
Sent: Monday, June 30, 2003  5:36 AM

AI-251 proposes new null procedures ("procedure ... is null")
for the new interfaces.

Wouldn't it make sense to allow "is null" as a subprogram default
for generic formal procedures, too? Semantics as the box default
("is <>") but if no actual parameter is given and no match exists,
defaults to a null procedure.

generic
   type Item (<>) is private;
   with procedure Clean_Up (X : in out Item) is null;
package Some_Containers is
   type Container is limited private;
   ...
   procedure Clear (C : in out Container);
   -- Removes all items currently in 'C'. Calls 'Clean_Up' for any item
   -- just before it is removed from 'C'.

private
   type Item_Ptr is access Item;

   type Container is limited
     record
        The_Item : Item_Ptr;
     end record;
   --  Assume some complex dynamic container, such as an AVL tree.
end Some_Containers;

and an implementation like

procedure Clear (C : in out Container)
is
  procedure Free is new Unchecked_Dealloctaion (Item, Item_Pr);
begin
  for I in "all items in C" loop
    Clean_Up (I.all);
    Free (I);
  end loop;
end Clear;

Now, instantiating this with a type where we don't care about clean-up
is easy:

  package Int_Containers is new Some_Containers (Integer);

Instantiating with a controlled type also is simple, for we don't need
a clean-up routine, "built-in" finalization is supposed to do that job:

  type XYZ is new Ada.Finalization.Controlled with ...

  package XYZ_Containers is new Some_Containers (XYZ);

So far, package Some_Containers could've been written without the
'Clean_Up' formal procedure.

But now suppose we want to instantiate Some_Containers with an access
type:

  type Int_Ptr is access Integer;

  package Int_Ptr_Containers is new Some_Containers (Int_Ptr);

Now, if the values added to such a container had been allocated
dynamically, we'd like to have them automatically deallocated
when the container is cleared. Hence, we could do instead

  procedure Free is new Unchecked_Deallocation (Integer, Int_Ptr);

  package Int_Ptr_Containers is new Some_Containers (Int_Ptr, Free);

Without a "is null" generic formal procedure, one would either have to
provide explicit null implementations of Clean_Up for Int_Containers
and XYZ_Containers, or write the 'Some_Containers' generic package
without the 'Clean_Up' formal parameter in the first place and insist
that the Int_Ptr_Container be written using a wrapping of the Int_Ptr
in a controlled type, so that its Finalize operation be called when
the container is cleared.

Both variants cause additional, basically useless work for users of
Some_Containers, and the instantiations are needlessly complicated.

Since AI-251 proposes "null procedures" anyway, it seems a small step
to allow them not only as primitive operations of abstract interfaces,
but also in other contexts where they might make sense.

Note: to get a similar effect as the "is null", one would currently
have to use two nested generics, which still complicates the
instantiation further:

generic
   type Item  (<>) is private;
package Some_Container_Wrapper is

   procedure Null_Clean_Up (X : in out Item);
   -- Has a null body

   generic
      with Clean_Up (X : in out Item) is Null_Clean_Up;
   package Some_Containers is
      ...
   end Some_Containers;
end Some_Container_Wrapper;

and an instantiation like

   package Wrapper is new Some_Container_Wrapper (A_Type);
   package A_Type_Containers is new Wrapper.Some_Containers;

or something like

generic
   type Item (<>) is private;
   with procedure Clean_Up (X : in out Item) is null;
package Some_Containers is
   ...
end Some_Containers;

generic
   type Item (<>) is private;
procedure Null_Clean_Up (X : in out Item);

and an instantiation like

   procedure No_Clean_up is new Null_Clean_Up (A_Type);
   package A_Type_Containers is
      new Some_Containers (A_Type, No_Clean_up);

Both variants are substantially more complex than the one with the
"is null" formal procedure.

A minor disadvantage of "is null" for generic formal procedures is
that this would not make sense for generic formal functions.

****************************************************************

From: Tucker Taft
Sent: Monday, June 30, 2003  7:46 AM

The ARG discussed this at our recent meeting and we also concluded
this was a useful and natural generalization of the proposal.
It was noted that it is fairly common when defining a generic
with a formal subprogram to explicitly define a "Do_Nothing"
procedure as a default.  "is null" would provide a natural and
more uniform way to accomplish the same thing.

****************************************************************

From: Stephen W Baird
Sent: Tuesday, September 2, 2003  4:01 PM

It was suggested at the Toulouse meeting that null procedures should be
defined in a separate AI, rather than as a part of AI-251 (interface
types). This is an initial version of that AI.

[This is version /01 of the AI. - ED]

****************************************************************

From: Jean-Pierre Rosen
Sent: Wednesday, September 3, 2003  2:02 AM

This version does not address null procedures as default for generic formal
procedures
i.e.
generic
   with procedure P (...) is null;
package Gen ....

Is it an omission or a separate AI?

****************************************************************

From: Stephen W Baird
Sent: Wednesday, September 3, 2003 12:49 PM

I was trying to keep the proposal as simple as possible.

I didn't want to deal with, for example, the interactions between this new
kind of subprogram_default and equality operators for access-to-subprogram
types.

Defaults for formal subprogram parameters can currently only be used to
refer to already-existing subprograms. The change you mention would mean
that instantiating a generic would have the side effect of generating a
new subprogram for use as an actual parameter. It would violate the
correspondence between generic actual parameters and renames.

I'm not claiming that one should therefore conclude that this change is a
bad idea or that it could not be properly defined. I'm just saying that
it is more complicated than one might think at first glance and that I
chose to steer clear of that complexity.

If there is a general consensus in favor of this feature, I think it would
belong in this AI. In any case, it probably ought to be mentioned in the
discussion section.

****************************************************************

From: Tucker Taft
Sent: Wednesday, September 3, 2003  3:20 PM

It seems like a natural and quite useful generalization to allow
"is null" for formal procedures.  It certainly doesn't
require generating a "real" procedure for macro-expanded
generics, and for shared generics, the implementation
is presumably pretty used to generating "thunks"
for cases where the actual is a predefined operator,
attribute, etc.

So I would argue for its inclusion, sooner rather than later,
though I understand your desire to get the simpler version
out the door.

****************************************************************

From: Randy Brukardt
Sent: Wednesday, September 3, 2003  4:00 PM

And we agreed to include it at the last meeting. So, I think it should be
included in the AI unless there is a pretty significant problem with it (in
which case, the problem ought to be discussed in the Discussion section).

****************************************************************

From: Stephen W Baird
Sent: Thursday, September 4, 2003  7:49 PM

Oops - I forgot that we had approved it. Thanks for keeping me honest.

Here's an attempt at wording for "with procedure P (...) is null;".

[This is version /02 of the AI. - ED]

****************************************************************

From: Tucker Taft
Sent: Thursday, September 4, 2003  9:18 PM

> Legality Rules
>
>   Add after 12.6(8)
>
>     A subprogram_default of null shall not be specified for a formal
> function.

This probably belongs in the Syntactic rules rather than
in the Legality rules, since it requires no semantic
information.

>
> Static Semantics
>
>   Add after 12.6(10)
>
>     If a generic unit has a subprogram_default specified by a null, and the

    "... specified by the reserved word null, ..."

>     corresponding actual parameter is omitted, then it is equivalent to
>     an explicit actual parameter that is an anonymous null procedure having
>     the profile given in the formal_subprogram_declaration. The anonymous null

Why do you bother calling it "anonymous"?  Is there something
significant about that?

>     procedure is implicitly declared immediately before the instantiation.
>     The anonymous null procedure is not a primitive subprogram of any type.

This seems overly complicated.  Why do we care where the actual
is declared, or what is its name?  All we need to say is that
it is a procedure whose body has no effect when invoked.

****************************************************************

From: Stephen W Baird
Sent: Friday, September 5, 2003  2:02 PM

Steve said:
>>     A subprogram_default of null shall not be specified
>>     for a formal function.

Tuck said:
> This probably belongs in the Syntactic rules rather than
> in the Legality rules, since it requires no semantic
> information.

Out-mode parameters for functions are disallowed via a legality rule
(6.1(18)). This could have been done as a syntax rule, but the solution
that was chosen seems cleaner. I think the situation with null defaults
for formal subprograms is similar.

Steve said:
>>     If a generic unit has a subprogram_default specified by a null, ...

Tuck said:
>    "... specified by the reserved word null, ..."

Agreed.

Steve said:
>>     ... and the corresponding actual parameter is omitted, then it is
>>     equivalent to
>>     an explicit actual parameter that is an anonymous null procedure
>>     having the profile given in the formal_subprogram_declaration. The
>>     anonymous null procedure is not a primitive subprogram ...

Tuck said:
> This seems overly complicated.  Why do we care where the actual
> is declared, or what is its name?  All we need to say is that
> it is a procedure whose body has no effect when invoked.

I think you are right, and these null subprograms should be treated more like
subprogram-valued attributes (which don't really have a declaration point).

I was concerned about something like

    generic
      with procedure Proc is null;
    package G is
      procedure Proc_Rename renames Proc;
    end G;

    type Ref is access procedure;

    package I is new G;

    Ptr : Ref := I.Proc_Rename'Access;

where we would need to know the accessibility level of the
procedure, but this is solved by noting that these null
procedures have a convention of Intrinsic (see 6.3.1(7)).

Below is a revised attempt. Is the note necessary? [This is version /03 - ED.]

****************************************************************

From: Tucker Taft
Sent: Friday, September 5, 2003  3:24 PM

> Out-mode parameters for functions are disallowed via a legality rule
> (6.1(18)). This could have been done as a syntax rule, but the solution
> that was chosen seems cleaner. I think the situation with null defaults
> for formal subprograms is similar.

It is not a big deal, but I didn't mean that you would write a BNF
rule for it, but rather just put the exact same wording in a paragraph
in the Syntax part of 12.6.  You may not be aware of this, but
we do have narrative syntax rules.  Take a look at record aggregates,
4.6.1.  You will see a couple of paragraphs after the BNF that
are considered syntax rules.  In array aggregates (4.6.2), there
is a similar syntax-rule paragraph.  Generally it was considered
preferable to group such paragraphs under Syntax rules if they
were truly independent of name resolution or other semantic
considerations.


>   Add after 12.6(10)
>
>     If a generic unit has a subprogram_default specified by the reserved word
>     null, and the corresponding actual parameter is omitted, then it is
>     equivalent to an explicit actual parameter that is a null procedure
>     having the profile given in the formal_subprogram_declaration.

I presume you have defined "null procedure" somewhere.


> Notes
>   Add after 12.6(16)
>
>     If a generic unit has a subprogram_default specified by the reserved word
>     null, and the corresponding actual parameter is omitted, then the calling
>     convention of the actual parameter is Intrinsic (see 6.3.1).

It might be better to say that "... the reserved word null, then in
an instance where the corresponding actual parameter is omitted, the
formal subprogram has convention Intrinsic (see 6.3.1)."   (It is
not possible to refer directly to the actual parameter.)

****************************************************************

From: Stephen W Baird
Sent: Friday, September 5, 2003  4:20 PM

> You may not be aware of this, but we do have
> narrative syntax rules.

I didn't know that. I agree, my proposed Legality
Rule should be a Syntax Rule instead.

> I presume you have defined "null procedure" somewhere.

Yeah. We're discussing the tail end of a larger AI in
which null procedures are defined.

> It might be better to say that "... the reserved word null, then in
> an instance where the corresponding actual parameter is omitted, the
> formal subprogram has convention Intrinsic (see 6.3.1)."   (It is
> not possible to refer directly to the actual parameter.)

Ok by me.

[These changes were made in version /04 - ED.]

****************************************************************


Questions? Ask the ACAA Technical Agent